module FilletExample (
filletExample
) where
import Waterfall.Solids( Solid, centeredCube )
import Waterfall.Transforms (translate)
import Waterfall.Fillet
( roundFillet
, roundConditionalFillet
, roundIndexedConditionalFillet
, chamfer
, conditionalChamfer
, indexedConditionalChamfer
)
import Control.Lens ((^.))
import Linear (V3 (..), _z)
import Control.Monad (guard)
filletExample :: Solid
filletExample :: Solid
filletExample =
let gridLayout :: [[Solid]] -> Solid
gridLayout =
[Solid] -> Solid
forall a. Monoid a => [a] -> a
mconcat ([Solid] -> Solid) -> ([[Solid]] -> [Solid]) -> [[Solid]] -> Solid
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Double -> Solid -> Solid) -> [Double] -> [Solid] -> [Solid]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(\Double
i -> V3 Double -> Solid -> Solid
forall a. Transformable a => V3 Double -> a -> a
translate (Double -> Double -> Double -> V3 Double
forall a. a -> a -> a -> V3 a
V3 Double
i Double
0 Double
0 ))
[Double
0, Double
2 ..]
([Solid] -> [Solid])
-> ([[Solid]] -> [Solid]) -> [[Solid]] -> [Solid]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Solid] -> Solid) -> [[Solid]] -> [Solid]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (
[Solid] -> Solid
forall a. Monoid a => [a] -> a
mconcat ([Solid] -> Solid) -> ([Solid] -> [Solid]) -> [Solid] -> Solid
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Double -> Solid -> Solid) -> [Double] -> [Solid] -> [Solid]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(\Double
i -> V3 Double -> Solid -> Solid
forall a. Transformable a => V3 Double -> a -> a
translate (Double -> Double -> Double -> V3 Double
forall a. a -> a -> a -> V3 a
V3 Double
0 Double
i Double
0 ))
[Double
0, Double
2 ..]
)
in [[Solid]] -> Solid
gridLayout
[[ Double -> Solid -> Solid
roundFillet Double
0.1 Solid
centeredCube
, ((V3 Double, V3 Double) -> Maybe Double) -> Solid -> Solid
roundConditionalFillet (\(V3 Double
s, V3 Double
e) -> if V3 Double
s V3 Double -> Getting Double (V3 Double) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (V3 Double) Double
forall a. Lens' (V3 a) a
forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== V3 Double
e V3 Double -> Getting Double (V3 Double) Double -> Double
forall s a. s -> Getting a s a -> a
^.Getting Double (V3 Double) Double
forall a. Lens' (V3 a) a
forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z then Maybe Double
forall a. Maybe a
Nothing else Double -> Maybe Double
forall a. a -> Maybe a
Just Double
0.1) Solid
centeredCube
, (Integer -> (V3 Double, V3 Double) -> Maybe Double)
-> Solid -> Solid
roundIndexedConditionalFillet (\Integer
i (V3 Double, V3 Double)
_ -> (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
0.04) Double -> Maybe () -> Maybe Double
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Integer -> Bool
forall a. Integral a => a -> Bool
odd Integer
i)) Solid
centeredCube
],
[ Double -> Solid -> Solid
chamfer Double
0.1 Solid
centeredCube
, ((V3 Double, V3 Double) -> Maybe Double) -> Solid -> Solid
conditionalChamfer (\(V3 Double
s, V3 Double
e) -> if V3 Double
s V3 Double -> Getting Double (V3 Double) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (V3 Double) Double
forall a. Lens' (V3 a) a
forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== V3 Double
e V3 Double -> Getting Double (V3 Double) Double -> Double
forall s a. s -> Getting a s a -> a
^.Getting Double (V3 Double) Double
forall a. Lens' (V3 a) a
forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z then Maybe Double
forall a. Maybe a
Nothing else Double -> Maybe Double
forall a. a -> Maybe a
Just Double
0.1) Solid
centeredCube
, (Integer -> (V3 Double, V3 Double) -> Maybe Double)
-> Solid -> Solid
indexedConditionalChamfer (\Integer
i (V3 Double, V3 Double)
_ -> (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
0.04) Double -> Maybe () -> Maybe Double
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Integer -> Bool
forall a. Integral a => a -> Bool
odd Integer
i)) Solid
centeredCube
]]