module SVG.ReadFileExample ( readFileExample ) where import qualified Waterfall.SVG import qualified Waterfall.Solids as Solids import qualified Waterfall.TwoD.Shape as Shape import qualified Waterfall.Transforms as Transforms import qualified Waterfall.Booleans as Booleans import Linear (V3 (..)) readFileExample :: FilePath -> IO Solids.Solid readFileExample :: FilePath -> IO Solid readFileExample FilePath filepath = let expandVertically :: Solid -> Solid expandVertically = V3 Double -> Solid -> Solid forall a. Transformable a => V3 Double -> a -> a Transforms.translate (Double -> Double -> Double -> V3 Double forall a. a -> a -> a -> V3 a V3 Double 0 Double 0 (-Double 0.5)) (Solid -> Solid) -> (Solid -> Solid) -> Solid -> Solid forall b c a. (b -> c) -> (a -> b) -> a -> c . V3 Double -> Solid -> Solid forall a. Transformable a => V3 Double -> a -> a Transforms.scale (Double -> Double -> Double -> V3 Double forall a. a -> a -> a -> V3 a V3 Double 1 Double 1 Double 2) xor :: Solid -> Solid -> Solid xor Solid a Solid b = (Solid a Solid -> Solid -> Solid `Booleans.difference` Solid -> Solid expandVertically Solid b) Solid -> Solid -> Solid forall a. Semigroup a => a -> a -> a <> (Solid b Solid -> Solid -> Solid `Booleans.difference` Solid -> Solid expandVertically Solid a) solidify :: [Path2D] -> Solid solidify = (Solid -> Solid -> Solid) -> Solid -> [Solid] -> Solid forall a b. (a -> b -> b) -> b -> [a] -> b forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b foldr Solid -> Solid -> Solid xor Solid Solids.nowhere ([Solid] -> Solid) -> ([Path2D] -> [Solid]) -> [Path2D] -> Solid forall b c a. (b -> c) -> (a -> b) -> a -> c . (Path2D -> Solid) -> [Path2D] -> [Solid] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Double -> Shape -> Solid Solids.prism Double 1 (Shape -> Solid) -> (Path2D -> Shape) -> Path2D -> Solid forall b c a. (b -> c) -> (a -> b) -> a -> c . Path2D -> Shape Shape.makeShape) in (SVGError -> Solid) -> ([Path2D] -> Solid) -> Either SVGError [Path2D] -> Solid forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (FilePath -> Solid forall a. HasCallStack => FilePath -> a error (FilePath -> Solid) -> (SVGError -> FilePath) -> SVGError -> Solid forall b c a. (b -> c) -> (a -> b) -> a -> c . SVGError -> FilePath forall a. Show a => a -> FilePath show) [Path2D] -> Solid solidify (Either SVGError [Path2D] -> Solid) -> IO (Either SVGError [Path2D]) -> IO Solid forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> FilePath -> IO (Either SVGError [Path2D]) Waterfall.SVG.readSVG FilePath filepath