module Waterfall.Revolution
( revolution
) where
import Waterfall.Internal.Solid (Solid (..), solidFromAcquire)
import Waterfall.TwoD.Internal.Path2D (Path2D (..))
import Waterfall.Internal.Finalizers (toAcquire)
import qualified OpenCascade.BRepPrimAPI.MakeRevol as MakeRevol
import qualified OpenCascade.BRepBuilderAPI.MakeSolid as MakeSolid
import qualified OpenCascade.BRepBuilderAPI.MakeShape as MakeShape
import qualified OpenCascade.GP as GP
import OpenCascade.Inheritance (upcast, unsafeDowncast)
import Waterfall.Transforms (rotate)
import Control.Monad.IO.Class (liftIO)
import Linear (unit, _x)
revolution :: Path2D -> Solid
revolution :: Path2D -> Solid
revolution (Path2D Ptr Wire
theRawPath) = V3 Double -> Double -> Solid -> Solid
forall a. Transformable a => V3 Double -> Double -> a -> a
rotate (ASetter' (V3 Double) Double -> V3 Double
forall (t :: * -> *) a.
(Additive t, Num a) =>
ASetter' (t a) a -> t a
unit ASetter' (V3 Double) Double
forall a. Lens' (V3 a) a
forall (t :: * -> *) a. R1 t => Lens' (t a) a
_x) (Double
forall a. Floating a => a
piDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2) (Solid -> Solid)
-> (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
p <- Ptr Wire -> Acquire (Ptr Wire)
forall a. a -> Acquire a
toAcquire Ptr Wire
theRawPath
axis <- GP.oy
revol <- MakeRevol.fromShapeAndAx1 (upcast p) axis True
shell <- MakeShape.shape (upcast revol)
solidBuilder <- MakeSolid.new
liftIO $ MakeSolid.add solidBuilder =<< unsafeDowncast shell
MakeShape.shape (upcast solidBuilder)