{-# LANGUAGE CApiFFI #-} module OpenCascade.HLRBRep.HLRToShape ( HLRToShape , fromAlgo , compoundOfEdges ) where import OpenCascade.HLRBRep.Types (Algo, HLRToShape) import OpenCascade.HLRBRep.TypeOfResultingEdge (TypeOfResultingEdge) import qualified OpenCascade.TopoDS.Types as TopoDS import OpenCascade.TopoDS.Internal.Destructors (deleteShape) import OpenCascade.HLRBRep.Internal.Destructors (deleteHLRToShape) import Foreign.Ptr import Data.Acquire (mkAcquire, Acquire) import OpenCascade.Handle import Foreign.C (CInt (..), CBool (..)) import OpenCascade.Internal.Bool (boolToCBool) foreign import capi unsafe "hs_HLRBRep_HLRToShape.h hs_new_HLRBRep_HLRToShape_fromHandleAlgo" rawFromHandleAlgo :: Ptr (Handle Algo) -> IO (Ptr HLRToShape) fromAlgo :: Ptr (Handle Algo) -> Acquire (Ptr HLRToShape) fromAlgo :: Ptr (Handle Algo) -> Acquire (Ptr HLRToShape) fromAlgo Ptr (Handle Algo) algo = IO (Ptr HLRToShape) -> (Ptr HLRToShape -> IO ()) -> Acquire (Ptr HLRToShape) forall a. IO a -> (a -> IO ()) -> Acquire a mkAcquire (Ptr (Handle Algo) -> IO (Ptr HLRToShape) rawFromHandleAlgo Ptr (Handle Algo) algo) Ptr HLRToShape -> IO () deleteHLRToShape foreign import capi unsafe "hs_HLRBRep_HLRToShape.h hs_HLRBRep_HLRToShape_compoundOfEdges" rawCompoundOfEdges :: Ptr HLRToShape -> CInt -> CBool -> CBool -> IO (Ptr TopoDS.Shape) compoundOfEdges :: Ptr HLRToShape -> TypeOfResultingEdge -> Bool -> Bool -> Acquire (Ptr TopoDS.Shape) compoundOfEdges :: Ptr HLRToShape -> TypeOfResultingEdge -> Bool -> Bool -> Acquire (Ptr Shape) compoundOfEdges Ptr HLRToShape hlrToShape TypeOfResultingEdge typeOfEdge Bool visible Bool in3d = IO (Ptr Shape) -> (Ptr Shape -> IO ()) -> Acquire (Ptr Shape) forall a. IO a -> (a -> IO ()) -> Acquire a mkAcquire (Ptr HLRToShape -> CInt -> CBool -> CBool -> IO (Ptr Shape) rawCompoundOfEdges Ptr HLRToShape hlrToShape (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (TypeOfResultingEdge -> Int) -> TypeOfResultingEdge -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . TypeOfResultingEdge -> Int forall a. Enum a => a -> Int fromEnum (TypeOfResultingEdge -> CInt) -> TypeOfResultingEdge -> CInt forall a b. (a -> b) -> a -> b $ TypeOfResultingEdge typeOfEdge) (Bool -> CBool boolToCBool Bool visible) (Bool -> CBool boolToCBool Bool in3d)) Ptr Shape -> IO () deleteShape