module Waterfall.TwoD.Internal.Path2D
( Path2D (..)
, joinPaths
) where
import Data.Foldable (traverse_, toList)
import Waterfall.Internal.Finalizers (toAcquire, unsafeFromAcquire)
import Control.Monad ((<=<))
import Control.Monad.IO.Class (liftIO)
import qualified OpenCascade.TopoDS as TopoDS
import qualified OpenCascade.BRepBuilderAPI.MakeWire as MakeWire
import Foreign.Ptr
import Data.Semigroup (sconcat)
newtype Path2D = Path2D { Path2D -> Ptr Wire
rawPath :: Ptr TopoDS.Wire }
joinPaths :: [Path2D] -> Path2D
joinPaths :: [Path2D] -> Path2D
joinPaths [Path2D]
paths = Ptr Wire -> Path2D
Path2D (Ptr Wire -> Path2D)
-> (Acquire (Ptr Wire) -> Ptr Wire) -> Acquire (Ptr Wire) -> Path2D
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acquire (Ptr Wire) -> Ptr Wire
forall a. Acquire a -> a
unsafeFromAcquire (Acquire (Ptr Wire) -> Path2D) -> Acquire (Ptr Wire) -> Path2D
forall a b. (a -> b) -> a -> b
$ do
builder <- Acquire (Ptr MakeWire)
MakeWire.new
traverse_ (liftIO . MakeWire.addWire builder <=< toAcquire . rawPath) paths
MakeWire.wire builder
instance Semigroup Path2D where
sconcat :: NonEmpty Path2D -> Path2D
sconcat = [Path2D] -> Path2D
joinPaths ([Path2D] -> Path2D)
-> (NonEmpty Path2D -> [Path2D]) -> NonEmpty Path2D -> Path2D
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Path2D -> [Path2D]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
Path2D
a <> :: Path2D -> Path2D -> Path2D
<> Path2D
b = [Path2D] -> Path2D
joinPaths [Path2D
a, Path2D
b]
instance Monoid Path2D where
mempty :: Path2D
mempty = [Path2D] -> Path2D
joinPaths []
mconcat :: [Path2D] -> Path2D
mconcat = [Path2D] -> Path2D
joinPaths