module Waterfall.Solids
( Solid
, nowhere
, unitCube
, centeredCube
, box
, unitSphere
, unitCylinder
, centeredCylinder
, unitCone
, prism
, volume
, centerOfMass
, momentOfInertia
) where
import Waterfall.Internal.Solid (Solid (..), solidFromAcquire, acquireSolid, nowhere)
import Waterfall.Internal.Finalizers (toAcquire, unsafeFromAcquire)
import Waterfall.TwoD.Internal.Shape (rawShape)
import Waterfall.Internal.FromOpenCascade (gpPntToV3)
import Waterfall.Transforms (translate)
import qualified Waterfall.TwoD.Shape as TwoD.Shape
import qualified OpenCascade.BRepPrimAPI.MakeBox as MakeBox
import qualified OpenCascade.BRepPrimAPI.MakeSphere as MakeSphere
import qualified OpenCascade.BRepPrimAPI.MakeCylinder as MakeCylinder
import qualified OpenCascade.BRepPrimAPI.MakeCone as MakeCone
import qualified OpenCascade.GProp.GProps as GProps
import qualified OpenCascade.BRepGProp as BRepGProp
import qualified OpenCascade.GP as GP
import Control.Lens ((^.))
import Linear (V3 (..), unit, _x, _y, _z, (^*))
import qualified OpenCascade.GP.Pnt as GP.Pnt
import qualified OpenCascade.GP.Vec as GP.Vec
import qualified OpenCascade.GP.Dir as GP.Dir
import qualified OpenCascade.GP.Ax1 as GP.Ax1
import qualified OpenCascade.BRepPrimAPI.MakePrism as MakePrism
import qualified OpenCascade.Inheritance as Inheritance
import Control.Monad.IO.Class (liftIO)
import Control.Monad ((<=<))
import Foreign.Ptr (Ptr)
import Data.Acquire (Acquire)
unitCube :: Solid
unitCube :: Solid
unitCube = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
a <- Acquire (Ptr Pnt)
GP.origin
b <- GP.Pnt.new 1 1 1
builder <- MakeBox.fromPnts a b
Inheritance.upcast <$> MakeBox.solid builder
centeredCube :: Solid
centeredCube :: Solid
centeredCube = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
a <- Double -> Double -> Double -> Acquire (Ptr Pnt)
GP.Pnt.new (-Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2) (-Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2) (-Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2)
b <- GP.Pnt.new (1/2) (1/2) (1/2)
builder <- MakeBox.fromPnts a b
Inheritance.upcast <$> MakeBox.solid builder
box :: V3 Double -> Solid
box :: V3 Double -> Solid
box (V3 Double
x Double
y Double
z) = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
a <- Acquire (Ptr Pnt)
GP.origin
b <- GP.Pnt.new x y z
builder <- MakeBox.fromPnts a b
Inheritance.upcast <$> MakeBox.solid builder
unitSphere :: Solid
unitSphere :: Solid
unitSphere = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ Ptr Solid -> Ptr Shape
forall a b. SubTypeOf a b => Ptr b -> Ptr a
Inheritance.upcast (Ptr Solid -> Ptr Shape)
-> Acquire (Ptr Solid) -> Acquire (Ptr Shape)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Double -> Acquire (Ptr Solid)
MakeSphere.fromRadius Double
1
unitCylinder :: Solid
unitCylinder :: Solid
unitCylinder = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ Ptr Solid -> Ptr Shape
forall a b. SubTypeOf a b => Ptr b -> Ptr a
Inheritance.upcast (Ptr Solid -> Ptr Shape)
-> Acquire (Ptr Solid) -> Acquire (Ptr Shape)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Double -> Double -> Acquire (Ptr Solid)
MakeCylinder.fromRadiusAndHeight Double
1 Double
1
centeredCylinder :: Solid
centeredCylinder :: Solid
centeredCylinder = V3 Double -> Solid -> Solid
forall a. Transformable a => V3 Double -> a -> a
translate (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. R3 t => Lens' (t a) a
_z V3 Double -> Double -> V3 Double
forall (f :: * -> *) a. (Functor f, Num a) => f a -> a -> f a
^* (-Double
0.5)) (Solid -> Solid) -> Solid -> Solid
forall a b. (a -> b) -> a -> b
$ Solid
unitCylinder
unitCone :: Solid
unitCone :: Solid
unitCone = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ Ptr Solid -> Ptr Shape
forall a b. SubTypeOf a b => Ptr b -> Ptr a
Inheritance.upcast (Ptr Solid -> Ptr Shape)
-> Acquire (Ptr Solid) -> Acquire (Ptr Shape)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Double -> Double -> Double -> Acquire (Ptr Solid)
MakeCone.fromTwoRadiiAndHeight Double
0 Double
1 Double
1
prism :: Double -> TwoD.Shape.Shape -> Solid
prism :: Double -> Shape -> Solid
prism Double
len Shape
face = Acquire (Ptr Shape) -> Solid
solidFromAcquire (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
p <- Ptr Shape -> Acquire (Ptr Shape)
forall a. a -> Acquire a
toAcquire (Ptr Shape -> Acquire (Ptr Shape))
-> (Shape -> Ptr Shape) -> Shape -> Acquire (Ptr Shape)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Shape -> Ptr Shape
rawShape (Shape -> Acquire (Ptr Shape)) -> Shape -> Acquire (Ptr Shape)
forall a b. (a -> b) -> a -> b
$ Shape
face
v <- GP.Vec.new 0 0 len
MakePrism.fromVec p v True True
gPropQuery :: (Ptr GProps.GProps -> Acquire a) -> Solid -> a
gPropQuery :: forall a. (Ptr GProps -> Acquire a) -> Solid -> a
gPropQuery Ptr GProps -> Acquire a
f Solid
s = Acquire a -> a
forall a. Acquire a -> a
unsafeFromAcquire (Acquire a -> a) -> Acquire a -> a
forall a b. (a -> b) -> a -> b
$ do
solid <- Solid -> Acquire (Ptr Shape)
acquireSolid Solid
s
gProp <- GProps.new
liftIO $ BRepGProp.volumeProperties solid gProp False False False
f gProp
volume :: Solid -> Double
volume :: Solid -> Double
volume = (Ptr GProps -> Acquire Double) -> Solid -> Double
forall a. (Ptr GProps -> Acquire a) -> Solid -> a
gPropQuery (IO Double -> Acquire Double
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> Acquire Double)
-> (Ptr GProps -> IO Double) -> Ptr GProps -> Acquire Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr GProps -> IO Double
GProps.mass)
centerOfMass :: Solid -> V3 Double
centerOfMass :: Solid -> V3 Double
centerOfMass = (Ptr GProps -> Acquire (V3 Double)) -> Solid -> V3 Double
forall a. (Ptr GProps -> Acquire a) -> Solid -> a
gPropQuery ((IO (V3 Double) -> Acquire (V3 Double)
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (V3 Double) -> Acquire (V3 Double))
-> (Ptr Pnt -> IO (V3 Double)) -> Ptr Pnt -> Acquire (V3 Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Pnt -> IO (V3 Double)
gpPntToV3) (Ptr Pnt -> Acquire (V3 Double))
-> (Ptr GProps -> Acquire (Ptr Pnt))
-> Ptr GProps
-> Acquire (V3 Double)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Ptr GProps -> Acquire (Ptr Pnt)
GProps.centreOfMass)
momentOfInertia :: V3 Double
-> V3 Double
-> Solid
-> Double
momentOfInertia :: V3 Double -> V3 Double -> Solid -> Double
momentOfInertia V3 Double
center V3 Double
axis = (Ptr GProps -> Acquire Double) -> Solid -> Double
forall a. (Ptr GProps -> Acquire a) -> Solid -> a
gPropQuery ((Ptr GProps -> Acquire Double) -> Solid -> Double)
-> (Ptr GProps -> Acquire Double) -> Solid -> Double
forall a b. (a -> b) -> a -> b
$ \Ptr GProps
gprop -> do
pnt <- Double -> Double -> Double -> Acquire (Ptr Pnt)
GP.Pnt.new (V3 Double
center 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. R1 t => Lens' (t a) a
_x) (V3 Double
center 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. R2 t => Lens' (t a) a
_y) (V3 Double
center 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)
dir <- GP.Dir.new (axis ^. _x) (axis ^. _y) (axis ^. _z)
ax1 <- GP.Ax1.new pnt dir
liftIO $ GProps.momentOfInertia gprop ax1