{-# LANGUAGE CApiFFI #-}
module OpenCascade.GP.Trsf2d
( Trsf2d
, new
, fromTrsf
, setMirrorAboutPnt2d
, setMirrorAboutAx2d
, setRotation
, setScale
, setTransformation
, setTransformationRelative
, setTranslation
, setScaleFactor
, setTranslationPart
, setTranslationRelative
, setValues
, isNegative
, scaleFactor
, value
, invert
, inverted
, multiply
, multiplied
, preMultiply
, power
, powered
) where

import OpenCascade.GP.Types
import OpenCascade.GP.Internal.Destructors
import Foreign.C
import Foreign.Ptr
import Data.Coerce (coerce)
import Data.Acquire 


-- new

foreign import capi unsafe "hs_gp_Trsf2d.h hs_new_gp_Trsf2d" rawNew ::IO (Ptr Trsf2d)

new :: Acquire (Ptr Trsf2d)
new :: Acquire (Ptr Trsf2d)
new = IO (Ptr Trsf2d) -> (Ptr Trsf2d -> IO ()) -> Acquire (Ptr Trsf2d)
forall a. IO a -> (a -> IO ()) -> Acquire a
mkAcquire IO (Ptr Trsf2d)
rawNew Ptr Trsf2d -> IO ()
deleteTrsf2d

foreign import capi unsafe "hs_gp_Trsf2d.h hs_new_gp_Trsf2d_fromTrsf" rawFromTrsf :: Ptr Trsf -> IO (Ptr Trsf2d)

fromTrsf :: Ptr Trsf -> Acquire (Ptr Trsf2d)
fromTrsf :: Ptr Trsf -> Acquire (Ptr Trsf2d)
fromTrsf Ptr Trsf
t = IO (Ptr Trsf2d) -> (Ptr Trsf2d -> IO ()) -> Acquire (Ptr Trsf2d)
forall a. IO a -> (a -> IO ()) -> Acquire a
mkAcquire (Ptr Trsf -> IO (Ptr Trsf2d)
rawFromTrsf Ptr Trsf
t) Ptr Trsf2d -> IO ()
deleteTrsf2d

-- mirror 

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetMirrorAboutPnt2d" setMirrorAboutPnt2d :: Ptr Trsf2d -> Ptr Pnt2d -> IO ()

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetMirrorAboutAx2d" setMirrorAboutAx2d :: Ptr Trsf2d -> Ptr Ax2d -> IO ()

-- rotate

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetRotation" rawSetRotation :: Ptr Trsf2d -> Ptr Pnt2d -> CDouble -> IO ()

setRotation :: Ptr Trsf2d -> Ptr Pnt2d -> Double -> IO ()
setRotation :: Ptr Trsf2d -> Ptr Pnt2d -> Double -> IO ()
setRotation = (Ptr Trsf2d -> Ptr Pnt2d -> CDouble -> IO ())
-> Ptr Trsf2d -> Ptr Pnt2d -> Double -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr Trsf2d -> Ptr Pnt2d -> CDouble -> IO ()
rawSetRotation

-- scale

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetScale" rawSetScale :: Ptr Trsf2d -> Ptr Pnt2d -> CDouble -> IO ()

setScale :: Ptr Trsf2d -> Ptr Pnt2d -> Double -> IO ()
setScale :: Ptr Trsf2d -> Ptr Pnt2d -> Double -> IO ()
setScale = (Ptr Trsf2d -> Ptr Pnt2d -> CDouble -> IO ())
-> Ptr Trsf2d -> Ptr Pnt2d -> Double -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr Trsf2d -> Ptr Pnt2d -> CDouble -> IO ()
rawSetScale

-- transformation

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetTransformation" setTransformation :: Ptr Trsf2d -> Ptr Ax2d -> IO ()

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetTransformationRelative" setTransformationRelative :: Ptr Trsf2d -> Ptr Ax2d -> Ptr Ax2d -> IO ()

-- translation

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetTranslation" setTranslation :: Ptr Trsf2d -> Ptr Vec2d -> IO ()

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetTranslationPart" setTranslationPart :: Ptr Trsf2d -> Ptr Vec2d -> IO ()

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetTranslationRelative" setTranslationRelative :: Ptr Trsf2d -> Ptr Pnt2d -> Ptr Pnt2d -> IO ()

-- scaleFactor

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetScaleFactor" rawSetScaleFactor :: Ptr Trsf2d -> CDouble -> IO ()

setScaleFactor :: Ptr Trsf2d -> Double -> IO ()
setScaleFactor :: Ptr Trsf2d -> Double -> IO ()
setScaleFactor = (Ptr Trsf2d -> CDouble -> IO ()) -> Ptr Trsf2d -> Double -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr Trsf2d -> CDouble -> IO ()
rawSetScaleFactor

-- setValues

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_SetValues" rawSetValues :: Ptr Trsf2d -> CDouble -> CDouble-> CDouble-> CDouble-> CDouble-> CDouble-> IO ()

setValues :: Ptr Trsf2d -> Double -> Double -> Double -> Double-> Double -> Double -> IO ()
setValues :: Ptr Trsf2d
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> IO ()
setValues = (Ptr Trsf2d
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> IO ())
-> Ptr Trsf2d
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr Trsf2d
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> IO ()
rawSetValues

-- tests 

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_IsNegative" rawIsNegative :: Ptr Trsf2d -> IO CBool

isNegative :: Ptr Trsf2d -> IO Bool
isNegative :: Ptr Trsf2d -> IO Bool
isNegative = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= CBool
0) (IO CBool -> IO Bool)
-> (Ptr Trsf2d -> IO CBool) -> Ptr Trsf2d -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Trsf2d -> IO CBool
rawIsNegative

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_ScaleFactor" rawScaleFactor :: Ptr Trsf2d -> IO CDouble

scaleFactor :: Ptr Trsf2d -> IO Double
scaleFactor :: Ptr Trsf2d -> IO Double
scaleFactor = (Ptr Trsf2d -> IO CDouble) -> Ptr Trsf2d -> IO Double
forall a b. Coercible a b => a -> b
coerce Ptr Trsf2d -> IO CDouble
rawScaleFactor

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Value" rawValue :: Ptr Trsf2d -> CInt -> CInt -> IO CDouble

value :: Ptr Trsf2d -> Int -> Int -> IO Double
value :: Ptr Trsf2d -> Int -> Int -> IO Double
value Ptr Trsf2d
t Int
row Int
col = IO CDouble -> IO Double
forall a b. Coercible a b => a -> b
coerce (IO CDouble -> IO Double) -> IO CDouble -> IO Double
forall a b. (a -> b) -> a -> b
$ Ptr Trsf2d -> CInt -> CInt -> IO CDouble
rawValue Ptr Trsf2d
t (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
row) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
col)

-- invert/inverted

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Invert" invert :: Ptr Trsf2d-> IO ()

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Inverted" rawInverted :: Ptr Trsf2d-> IO (Ptr Trsf2d)

inverted :: Ptr Trsf2d -> Acquire (Ptr Trsf2d)
inverted :: Ptr Trsf2d -> Acquire (Ptr Trsf2d)
inverted Ptr Trsf2d
t = IO (Ptr Trsf2d) -> (Ptr Trsf2d -> IO ()) -> Acquire (Ptr Trsf2d)
forall a. IO a -> (a -> IO ()) -> Acquire a
mkAcquire (Ptr Trsf2d -> IO (Ptr Trsf2d)
rawInverted Ptr Trsf2d
t) Ptr Trsf2d -> IO ()
deleteTrsf2d

-- multiply/multiplied

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Multiply" multiply :: Ptr Trsf2d -> Ptr Trsf2d -> IO ()

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Multiplied" rawMultiplied :: Ptr Trsf2d -> Ptr Trsf2d -> IO (Ptr Trsf2d)

multiplied :: Ptr Trsf2d -> Ptr Trsf2d -> Acquire (Ptr Trsf2d)
multiplied :: Ptr Trsf2d -> Ptr Trsf2d -> Acquire (Ptr Trsf2d)
multiplied Ptr Trsf2d
a Ptr Trsf2d
b = IO (Ptr Trsf2d) -> (Ptr Trsf2d -> IO ()) -> Acquire (Ptr Trsf2d)
forall a. IO a -> (a -> IO ()) -> Acquire a
mkAcquire (Ptr Trsf2d -> Ptr Trsf2d -> IO (Ptr Trsf2d)
rawMultiplied Ptr Trsf2d
a Ptr Trsf2d
b) Ptr Trsf2d -> IO ()
deleteTrsf2d

-- PreMultiply

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_PreMultiply" preMultiply :: Ptr Trsf2d -> Ptr Trsf2d -> IO ()

-- power/powered

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Power" rawPower :: Ptr Trsf2d -> CInt -> IO ()

power :: Ptr Trsf2d -> Int -> IO ()
power :: Ptr Trsf2d -> Int -> IO ()
power Ptr Trsf2d
trsf Int
times = Ptr Trsf2d -> CInt -> IO ()
rawPower Ptr Trsf2d
trsf (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
times)

foreign import capi unsafe "hs_gp_Trsf2d.h hs_gp_Trsf2d_Powered" rawPowered :: Ptr Trsf2d -> CInt -> IO (Ptr Trsf2d)

powered :: Ptr Trsf2d -> Int -> Acquire (Ptr Trsf2d)
powered :: Ptr Trsf2d -> Int -> Acquire (Ptr Trsf2d)
powered Ptr Trsf2d
trsf Int
times = IO (Ptr Trsf2d) -> (Ptr Trsf2d -> IO ()) -> Acquire (Ptr Trsf2d)
forall a. IO a -> (a -> IO ()) -> Acquire a
mkAcquire (Ptr Trsf2d -> CInt -> IO (Ptr Trsf2d)
rawPowered Ptr Trsf2d
trsf (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
times)) Ptr Trsf2d -> IO ()
deleteTrsf2d