module Waterfall.Solids 
( Solid
, nowhere
, unitCube
, centeredCube
, box
, unitSphere
, unitCylinder
, prism
) where


import Waterfall.Internal.Solid(Solid(..), nowhere)
import Waterfall.TwoD.Internal.Shape (runShape)
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.GP as GP
import Linear (V3 (..))
import qualified OpenCascade.GP.Pnt as GP.Pnt
import qualified OpenCascade.GP.Vec as GP.Vec
import qualified OpenCascade.BRepPrimAPI.MakePrism as MakePrism
import qualified OpenCascade.Inheritance as Inheritance

-- | A cube with side lengths of 1, one vertex on the origin, another on \( (1, 1, 1) \)
unitCube :: Solid
unitCube :: Solid
unitCube = Acquire (Ptr Shape) -> Solid
Solid (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pnt
a <- Acquire (Ptr Pnt)
GP.origin
    Ptr Pnt
b <- Double -> Double -> Double -> Acquire (Ptr Pnt)
GP.Pnt.new Double
1 Double
1 Double
1
    Ptr MakeBox
builder <- Ptr Pnt -> Ptr Pnt -> Acquire (Ptr MakeBox)
MakeBox.fromPnts Ptr Pnt
a Ptr Pnt
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
<$> Ptr MakeBox -> Acquire (Ptr Solid)
MakeBox.solid Ptr MakeBox
builder

-- | A cube with side lengths of 1, centered on the origin
centeredCube :: Solid
centeredCube :: Solid
centeredCube = Acquire (Ptr Shape) -> Solid
Solid (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pnt
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)
    Ptr Pnt
b <- 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)
    Ptr MakeBox
builder <- Ptr Pnt -> Ptr Pnt -> Acquire (Ptr MakeBox)
MakeBox.fromPnts Ptr Pnt
a Ptr Pnt
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
<$> Ptr MakeBox -> Acquire (Ptr Solid)
MakeBox.solid Ptr MakeBox
builder

-- | A cuboid, one vertex on the origin, another on a given point
box :: V3 Double -> Solid
box :: V3 Double -> Solid
box (V3 Double
x Double
y Double
z) = Acquire (Ptr Shape) -> Solid
Solid (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pnt
a <- Acquire (Ptr Pnt)
GP.origin
    Ptr Pnt
b <- Double -> Double -> Double -> Acquire (Ptr Pnt)
GP.Pnt.new Double
x Double
y Double
z
    Ptr MakeBox
builder <- Ptr Pnt -> Ptr Pnt -> Acquire (Ptr MakeBox)
MakeBox.fromPnts Ptr Pnt
a Ptr Pnt
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
<$> Ptr MakeBox -> Acquire (Ptr Solid)
MakeBox.solid Ptr MakeBox
builder
    
-- | A sphere with radius of 1, centered on the origin
unitSphere :: Solid
unitSphere :: Solid
unitSphere = Acquire (Ptr Shape) -> Solid
Solid (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

-- | A cylinder with radius 1, length 1,
-- one of it's circular faces centered on the origin,
-- the other centered on \( (0, 0, 1) \)
unitCylinder :: Solid
unitCylinder :: Solid
unitCylinder = Acquire (Ptr Shape) -> Solid
Solid (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

-- | Extruded a 2D face into a prism with a given length \(len\).
--
-- One of the prisms faces lies on the plane \(z = 0\),
-- the other on the plane \(z = len\).
prism :: Double -> TwoD.Shape.Shape -> Solid
prism :: Double -> Shape -> Solid
prism Double
len Shape
face = Acquire (Ptr Shape) -> Solid
Solid (Acquire (Ptr Shape) -> Solid) -> Acquire (Ptr Shape) -> Solid
forall a b. (a -> b) -> a -> b
$ do
    Ptr Shape
p <- Shape -> Acquire (Ptr Shape)
runShape Shape
face
    Ptr Vec
v <- Double -> Double -> Double -> Acquire (Ptr Vec)
GP.Vec.new Double
0 Double
0 Double
len
    Ptr Shape -> Ptr Vec -> Bool -> Bool -> Acquire (Ptr Shape)
MakePrism.fromVec Ptr Shape
p Ptr Vec
v Bool
True Bool
True