{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @GskTransform@ structure contains only private data.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gsk.Structs.Transform
    ( 

-- * Exported types
    Transform(..)                           ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveTransformMethod                  ,
#endif


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    TransformEqualMethodInfo                ,
#endif
    transformEqual                          ,


-- ** getCategory #method:getCategory#

#if defined(ENABLE_OVERLOADING)
    TransformGetCategoryMethodInfo          ,
#endif
    transformGetCategory                    ,


-- ** invert #method:invert#

#if defined(ENABLE_OVERLOADING)
    TransformInvertMethodInfo               ,
#endif
    transformInvert                         ,


-- ** matrix #method:matrix#

#if defined(ENABLE_OVERLOADING)
    TransformMatrixMethodInfo               ,
#endif
    transformMatrix                         ,


-- ** new #method:new#

    transformNew                            ,


-- ** parse #method:parse#

    transformParse                          ,


-- ** perspective #method:perspective#

#if defined(ENABLE_OVERLOADING)
    TransformPerspectiveMethodInfo          ,
#endif
    transformPerspective                    ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    TransformPrintMethodInfo                ,
#endif
    transformPrint                          ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    TransformRefMethodInfo                  ,
#endif
    transformRef                            ,


-- ** rotate #method:rotate#

#if defined(ENABLE_OVERLOADING)
    TransformRotateMethodInfo               ,
#endif
    transformRotate                         ,


-- ** rotate3d #method:rotate3d#

#if defined(ENABLE_OVERLOADING)
    TransformRotate3dMethodInfo             ,
#endif
    transformRotate3d                       ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    TransformScaleMethodInfo                ,
#endif
    transformScale                          ,


-- ** scale3d #method:scale3d#

#if defined(ENABLE_OVERLOADING)
    TransformScale3dMethodInfo              ,
#endif
    transformScale3d                        ,


-- ** to2d #method:to2d#

#if defined(ENABLE_OVERLOADING)
    TransformTo2dMethodInfo                 ,
#endif
    transformTo2d                           ,


-- ** toAffine #method:toAffine#

#if defined(ENABLE_OVERLOADING)
    TransformToAffineMethodInfo             ,
#endif
    transformToAffine                       ,


-- ** toMatrix #method:toMatrix#

#if defined(ENABLE_OVERLOADING)
    TransformToMatrixMethodInfo             ,
#endif
    transformToMatrix                       ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    TransformToStringMethodInfo             ,
#endif
    transformToString                       ,


-- ** toTranslate #method:toTranslate#

#if defined(ENABLE_OVERLOADING)
    TransformToTranslateMethodInfo          ,
#endif
    transformToTranslate                    ,


-- ** transform #method:transform#

#if defined(ENABLE_OVERLOADING)
    TransformTransformMethodInfo            ,
#endif
    transformTransform                      ,


-- ** transformBounds #method:transformBounds#

#if defined(ENABLE_OVERLOADING)
    TransformTransformBoundsMethodInfo      ,
#endif
    transformTransformBounds                ,


-- ** transformPoint #method:transformPoint#

#if defined(ENABLE_OVERLOADING)
    TransformTransformPointMethodInfo       ,
#endif
    transformTransformPoint                 ,


-- ** translate #method:translate#

#if defined(ENABLE_OVERLOADING)
    TransformTranslateMethodInfo            ,
#endif
    transformTranslate                      ,


-- ** translate3d #method:translate3d#

#if defined(ENABLE_OVERLOADING)
    TransformTranslate3dMethodInfo          ,
#endif
    transformTranslate3d                    ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    TransformUnrefMethodInfo                ,
#endif
    transformUnref                          ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums

-- | Memory-managed wrapper type.
newtype Transform = Transform (SP.ManagedPtr Transform)
    deriving (Transform -> Transform -> Bool
(Transform -> Transform -> Bool)
-> (Transform -> Transform -> Bool) -> Eq Transform
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transform -> Transform -> Bool
$c/= :: Transform -> Transform -> Bool
== :: Transform -> Transform -> Bool
$c== :: Transform -> Transform -> Bool
Eq)

instance SP.ManagedPtrNewtype Transform where
    toManagedPtr :: Transform -> ManagedPtr Transform
toManagedPtr (Transform ManagedPtr Transform
p) = ManagedPtr Transform
p

foreign import ccall "gsk_transform_get_type" c_gsk_transform_get_type :: 
    IO GType

type instance O.ParentTypes Transform = '[]
instance O.HasParentTypes Transform

instance B.Types.TypedObject Transform where
    glibType :: IO GType
glibType = IO GType
c_gsk_transform_get_type

instance B.Types.GBoxed Transform

-- | Convert 'Transform' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Transform where
    toGValue :: Transform -> IO GValue
toGValue Transform
o = do
        GType
gtype <- IO GType
c_gsk_transform_get_type
        Transform -> (Ptr Transform -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Transform
o (GType
-> (GValue -> Ptr Transform -> IO ()) -> Ptr Transform -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Transform -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO Transform
fromGValue GValue
gv = do
        Ptr Transform
ptr <- GValue -> IO (Ptr Transform)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Transform)
        (ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Transform -> Transform
Transform Ptr Transform
ptr
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Transform
type instance O.AttributeList Transform = TransformAttributeList
type TransformAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method Transform::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_new" gsk_transform_new :: 
    IO (Ptr Transform)

-- | /No description available in the introspection data./
transformNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Transform
transformNew :: m Transform
transformNew  = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
result <- IO (Ptr Transform)
gsk_transform_new
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformNew" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Transform::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "first"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the first matrix" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "second"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the second matrix" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_equal" gsk_transform_equal :: 
    Ptr Transform ->                        -- first : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Transform ->                        -- second : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO CInt

-- | Checks two matrices for equality. Note that matrices need to be literally
-- identical in their operations, it is not enough that they return the
-- same result in 'GI.Gsk.Structs.Transform.transformToMatrix'.
transformEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@first@/: the first matrix
    -> Transform
    -- ^ /@second@/: the second matrix
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the two matrices can be proven to be equal
transformEqual :: Transform -> Transform -> m Bool
transformEqual Transform
first Transform
second = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
first' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
first
    Ptr Transform
second' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
second
    CInt
result <- Ptr Transform -> Ptr Transform -> IO CInt
gsk_transform_equal Ptr Transform
first' Ptr Transform
second'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
first
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
second
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TransformEqualMethodInfo
instance (signature ~ (Transform -> m Bool), MonadIO m) => O.MethodInfo TransformEqualMethodInfo Transform signature where
    overloadedMethod = transformEqual

#endif

-- method Transform::get_category
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gsk" , name = "TransformCategory" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_get_category" gsk_transform_get_category :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO CUInt

-- | Returns the category this transform belongs to.
transformGetCategory ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: A t'GI.Gsk.Structs.Transform.Transform'
    -> m Gsk.Enums.TransformCategory
    -- ^ __Returns:__ The category of the transform
transformGetCategory :: Transform -> m TransformCategory
transformGetCategory Transform
self = IO TransformCategory -> m TransformCategory
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TransformCategory -> m TransformCategory)
-> IO TransformCategory -> m TransformCategory
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    CUInt
result <- Ptr Transform -> IO CUInt
gsk_transform_get_category Ptr Transform
self'
    let result' :: TransformCategory
result' = (Int -> TransformCategory
forall a. Enum a => Int -> a
toEnum (Int -> TransformCategory)
-> (CUInt -> Int) -> CUInt -> TransformCategory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    TransformCategory -> IO TransformCategory
forall (m :: * -> *) a. Monad m => a -> m a
return TransformCategory
result'

#if defined(ENABLE_OVERLOADING)
data TransformGetCategoryMethodInfo
instance (signature ~ (m Gsk.Enums.TransformCategory), MonadIO m) => O.MethodInfo TransformGetCategoryMethodInfo Transform signature where
    overloadedMethod = transformGetCategory

#endif

-- method Transform::invert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Transform to invert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_invert" gsk_transform_invert :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO (Ptr Transform)

-- | Inverts the given transform.
-- 
-- If /@self@/ is not invertible, 'P.Nothing' is returned.
-- Note that inverting 'P.Nothing' also returns 'P.Nothing', which is
-- the correct inverse of 'P.Nothing'. If you need to differentiate
-- between those cases, you should check /@self@/ is not 'P.Nothing'
-- before calling this function.
transformInvert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: Transform to invert
    -> m Transform
    -- ^ __Returns:__ The inverted transform or 'P.Nothing' if the transform
    --     cannot be inverted.
transformInvert :: Transform -> m Transform
transformInvert Transform
self = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
self
    Ptr Transform
result <- Ptr Transform -> IO (Ptr Transform)
gsk_transform_invert Ptr Transform
self'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformInvert" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformInvertMethodInfo
instance (signature ~ (m Transform), MonadIO m) => O.MethodInfo TransformInvertMethodInfo Transform signature where
    overloadedMethod = transformInvert

#endif

-- method Transform::matrix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "matrix"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the matrix to multiply @next with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_matrix" gsk_transform_matrix :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Graphene.Matrix.Matrix ->           -- matrix : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO (Ptr Transform)

-- | Multiplies /@next@/ with the given /@matrix@/.
transformMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Graphene.Matrix.Matrix
    -- ^ /@matrix@/: the matrix to multiply /@next@/ with
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformMatrix :: Transform -> Matrix -> m Transform
transformMatrix Transform
next Matrix
matrix = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr Transform
result <- Ptr Transform -> Ptr Matrix -> IO (Ptr Transform)
gsk_transform_matrix Ptr Transform
next' Ptr Matrix
matrix'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformMatrix" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformMatrixMethodInfo
instance (signature ~ (Graphene.Matrix.Matrix -> m Transform), MonadIO m) => O.MethodInfo TransformMatrixMethodInfo Transform signature where
    overloadedMethod = transformMatrix

#endif

-- method Transform::perspective
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "depth"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "distance of the z=0 plane. Lower values give a more\n    flattened pyramid and therefore a more pronounced\n    perspective effect."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_perspective" gsk_transform_perspective :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    CFloat ->                               -- depth : TBasicType TFloat
    IO (Ptr Transform)

-- | Applies a perspective projection transform. This transform
-- scales points in X and Y based on their Z value, scaling
-- points with positive Z values away from the origin, and
-- those with negative Z values towards the origin. Points
-- on the z=0 plane are unchanged.
transformPerspective ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Float
    -- ^ /@depth@/: distance of the z=0 plane. Lower values give a more
    --     flattened pyramid and therefore a more pronounced
    --     perspective effect.
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformPerspective :: Transform -> Float -> m Transform
transformPerspective Transform
next Float
depth = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    let depth' :: CFloat
depth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
depth
    Ptr Transform
result <- Ptr Transform -> CFloat -> IO (Ptr Transform)
gsk_transform_perspective Ptr Transform
next' CFloat
depth'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformPerspective" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformPerspectiveMethodInfo
instance (signature ~ (Float -> m Transform), MonadIO m) => O.MethodInfo TransformPerspectiveMethodInfo Transform signature where
    overloadedMethod = transformPerspective

#endif

-- method Transform::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The string to print into"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_print" gsk_transform_print :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr GLib.String.String ->               -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO ()

-- | Converts /@self@/ into a human-readable string representation suitable
-- for printing that can later be parsed with 'GI.Gsk.Functions.transformParse'.
transformPrint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> GLib.String.String
    -- ^ /@string@/: The string to print into
    -> m ()
transformPrint :: Transform -> String -> m ()
transformPrint Transform
self String
string = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr Transform -> Ptr String -> IO ()
gsk_transform_print Ptr Transform
self' Ptr String
string'
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransformPrintMethodInfo
instance (signature ~ (GLib.String.String -> m ()), MonadIO m) => O.MethodInfo TransformPrintMethodInfo Transform signature where
    overloadedMethod = transformPrint

#endif

-- method Transform::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_ref" gsk_transform_ref :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO (Ptr Transform)

-- | Acquires a reference on the given t'GI.Gsk.Structs.Transform.Transform'.
transformRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> m Transform
    -- ^ __Returns:__ the t'GI.Gsk.Structs.Transform.Transform' with an additional reference
transformRef :: Transform -> m Transform
transformRef Transform
self = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr Transform
result <- Ptr Transform -> IO (Ptr Transform)
gsk_transform_ref Ptr Transform
self'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformRef" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformRefMethodInfo
instance (signature ~ (m Transform), MonadIO m) => O.MethodInfo TransformRefMethodInfo Transform signature where
    overloadedMethod = transformRef

#endif

-- method Transform::rotate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees (clockwise)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_rotate" gsk_transform_rotate :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    CFloat ->                               -- angle : TBasicType TFloat
    IO (Ptr Transform)

-- | Rotates /@next@/ /@angle@/ degrees in 2D - or in 3Dspeak, around the z axis.
transformRotate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees (clockwise)
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformRotate :: Transform -> Float -> m Transform
transformRotate Transform
next Float
angle = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
    Ptr Transform
result <- Ptr Transform -> CFloat -> IO (Ptr Transform)
gsk_transform_rotate Ptr Transform
next' CFloat
angle'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformRotate" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformRotateMethodInfo
instance (signature ~ (Float -> m Transform), MonadIO m) => O.MethodInfo TransformRotateMethodInfo Transform signature where
    overloadedMethod = transformRotate

#endif

-- method Transform::rotate_3d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees (clockwise)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "axis"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The rotation axis" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_rotate_3d" gsk_transform_rotate_3d :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    CFloat ->                               -- angle : TBasicType TFloat
    Ptr Graphene.Vec3.Vec3 ->               -- axis : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO (Ptr Transform)

-- | Rotates /@next@/ /@angle@/ degrees around /@axis@/.
-- 
-- For a rotation in 2D space, use 'GI.Gsk.Structs.Transform.transformRotate'.
transformRotate3d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees (clockwise)
    -> Graphene.Vec3.Vec3
    -- ^ /@axis@/: The rotation axis
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformRotate3d :: Transform -> Float -> Vec3 -> m Transform
transformRotate3d Transform
next Float
angle Vec3
axis = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
    Ptr Vec3
axis' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
axis
    Ptr Transform
result <- Ptr Transform -> CFloat -> Ptr Vec3 -> IO (Ptr Transform)
gsk_transform_rotate_3d Ptr Transform
next' CFloat
angle' Ptr Vec3
axis'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformRotate3d" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
axis
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformRotate3dMethodInfo
instance (signature ~ (Float -> Graphene.Vec3.Vec3 -> m Transform), MonadIO m) => O.MethodInfo TransformRotate3dMethodInfo Transform signature where
    overloadedMethod = transformRotate3d

#endif

-- method Transform::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "factor_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "scaling factor on the X axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "scaling factor on the Y axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_scale" gsk_transform_scale :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    CFloat ->                               -- factor_x : TBasicType TFloat
    CFloat ->                               -- factor_y : TBasicType TFloat
    IO (Ptr Transform)

-- | Scales /@next@/ in 2-dimensional space by the given factors.
-- Use 'GI.Gsk.Structs.Transform.transformScale3d' to scale in all 3 dimensions.
transformScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Float
    -- ^ /@factorX@/: scaling factor on the X axis
    -> Float
    -- ^ /@factorY@/: scaling factor on the Y axis
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformScale :: Transform -> Float -> Float -> m Transform
transformScale Transform
next Float
factorX Float
factorY = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    let factorX' :: CFloat
factorX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorX
    let factorY' :: CFloat
factorY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorY
    Ptr Transform
result <- Ptr Transform -> CFloat -> CFloat -> IO (Ptr Transform)
gsk_transform_scale Ptr Transform
next' CFloat
factorX' CFloat
factorY'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformScale" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformScaleMethodInfo
instance (signature ~ (Float -> Float -> m Transform), MonadIO m) => O.MethodInfo TransformScaleMethodInfo Transform signature where
    overloadedMethod = transformScale

#endif

-- method Transform::scale_3d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "factor_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "scaling factor on the X axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "scaling factor on the Y axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor_z"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "scaling factor on the Z axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_scale_3d" gsk_transform_scale_3d :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    CFloat ->                               -- factor_x : TBasicType TFloat
    CFloat ->                               -- factor_y : TBasicType TFloat
    CFloat ->                               -- factor_z : TBasicType TFloat
    IO (Ptr Transform)

-- | Scales /@next@/ by the given factors.
transformScale3d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Float
    -- ^ /@factorX@/: scaling factor on the X axis
    -> Float
    -- ^ /@factorY@/: scaling factor on the Y axis
    -> Float
    -- ^ /@factorZ@/: scaling factor on the Z axis
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformScale3d :: Transform -> Float -> Float -> Float -> m Transform
transformScale3d Transform
next Float
factorX Float
factorY Float
factorZ = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    let factorX' :: CFloat
factorX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorX
    let factorY' :: CFloat
factorY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorY
    let factorZ' :: CFloat
factorZ' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorZ
    Ptr Transform
result <- Ptr Transform -> CFloat -> CFloat -> CFloat -> IO (Ptr Transform)
gsk_transform_scale_3d Ptr Transform
next' CFloat
factorX' CFloat
factorY' CFloat
factorZ'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformScale3d" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformScale3dMethodInfo
instance (signature ~ (Float -> Float -> Float -> m Transform), MonadIO m) => O.MethodInfo TransformScale3dMethodInfo Transform signature where
    overloadedMethod = transformScale3d

#endif

-- method Transform::to_2d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a 2D #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_xx"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the xx member"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_yx"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the yx member"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_xy"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the xy member"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_yy"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the yy member"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_dx"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the x0 member"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_dy"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the y0 member"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_to_2d" gsk_transform_to_2d :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr CFloat ->                           -- out_xx : TBasicType TFloat
    Ptr CFloat ->                           -- out_yx : TBasicType TFloat
    Ptr CFloat ->                           -- out_xy : TBasicType TFloat
    Ptr CFloat ->                           -- out_yy : TBasicType TFloat
    Ptr CFloat ->                           -- out_dx : TBasicType TFloat
    Ptr CFloat ->                           -- out_dy : TBasicType TFloat
    IO ()

-- | Converts a t'GI.Gsk.Structs.Transform.Transform' to a 2D transformation
-- matrix.
-- /@self@/ must be a 2D transformation. If you are not
-- sure, use 'GI.Gsk.Structs.Transform.transformGetCategory' >=
-- 'GI.Gsk.Enums.TransformCategory2d' to check.
-- 
-- The returned values have the following layout:
-- 
-- 
-- === /plain code/
-- >
-- >  | xx yx |   |  a  b  0 |
-- >  | xy yy | = |  c  d  0 |
-- >  | dx dy |   | tx ty  1 |
-- 
-- 
-- This function can be used to convert between a t'GI.Gsk.Structs.Transform.Transform'
-- and a matrix type from other 2D drawing libraries, in particular
-- Cairo.
transformTo2d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a 2D t'GI.Gsk.Structs.Transform.Transform'
    -> m ((Float, Float, Float, Float, Float, Float))
transformTo2d :: Transform -> m (Float, Float, Float, Float, Float, Float)
transformTo2d Transform
self = IO (Float, Float, Float, Float, Float, Float)
-> m (Float, Float, Float, Float, Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float, Float, Float, Float, Float)
 -> m (Float, Float, Float, Float, Float, Float))
-> IO (Float, Float, Float, Float, Float, Float)
-> m (Float, Float, Float, Float, Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr CFloat
outXx <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outYx <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outXy <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outYy <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outDx <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outDy <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Transform
-> Ptr CFloat
-> Ptr CFloat
-> Ptr CFloat
-> Ptr CFloat
-> Ptr CFloat
-> Ptr CFloat
-> IO ()
gsk_transform_to_2d Ptr Transform
self' Ptr CFloat
outXx Ptr CFloat
outYx Ptr CFloat
outXy Ptr CFloat
outYy Ptr CFloat
outDx Ptr CFloat
outDy
    CFloat
outXx' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outXx
    let outXx'' :: Float
outXx'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outXx'
    CFloat
outYx' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outYx
    let outYx'' :: Float
outYx'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outYx'
    CFloat
outXy' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outXy
    let outXy'' :: Float
outXy'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outXy'
    CFloat
outYy' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outYy
    let outYy'' :: Float
outYy'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outYy'
    CFloat
outDx' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outDx
    let outDx'' :: Float
outDx'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outDx'
    CFloat
outDy' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outDy
    let outDy'' :: Float
outDy'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outDy'
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outXx
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outYx
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outXy
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outYy
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outDx
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outDy
    (Float, Float, Float, Float, Float, Float)
-> IO (Float, Float, Float, Float, Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
outXx'', Float
outYx'', Float
outXy'', Float
outYy'', Float
outDx'', Float
outDy'')

#if defined(ENABLE_OVERLOADING)
data TransformTo2dMethodInfo
instance (signature ~ (m ((Float, Float, Float, Float, Float, Float))), MonadIO m) => O.MethodInfo TransformTo2dMethodInfo Transform signature where
    overloadedMethod = transformTo2d

#endif

-- method Transform::to_affine
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_scale_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the scale\n    factor in the x direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_scale_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the scale\n    factor in the y direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_dx"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the translation\n    in the x direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_dy"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the translation\n    in the y direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_to_affine" gsk_transform_to_affine :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr CFloat ->                           -- out_scale_x : TBasicType TFloat
    Ptr CFloat ->                           -- out_scale_y : TBasicType TFloat
    Ptr CFloat ->                           -- out_dx : TBasicType TFloat
    Ptr CFloat ->                           -- out_dy : TBasicType TFloat
    IO ()

-- | Converts a t'GI.Gsk.Structs.Transform.Transform' to 2D affine transformation
-- factors.
-- /@self@/ must be a 2D transformation. If you are not
-- sure, use 'GI.Gsk.Structs.Transform.transformGetCategory' >=
-- 'GI.Gsk.Enums.TransformCategory2dAffine' to check.
transformToAffine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> m ((Float, Float, Float, Float))
transformToAffine :: Transform -> m (Float, Float, Float, Float)
transformToAffine Transform
self = IO (Float, Float, Float, Float) -> m (Float, Float, Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float, Float, Float) -> m (Float, Float, Float, Float))
-> IO (Float, Float, Float, Float)
-> m (Float, Float, Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr CFloat
outScaleX <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outScaleY <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outDx <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outDy <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Transform
-> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> IO ()
gsk_transform_to_affine Ptr Transform
self' Ptr CFloat
outScaleX Ptr CFloat
outScaleY Ptr CFloat
outDx Ptr CFloat
outDy
    CFloat
outScaleX' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outScaleX
    let outScaleX'' :: Float
outScaleX'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outScaleX'
    CFloat
outScaleY' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outScaleY
    let outScaleY'' :: Float
outScaleY'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outScaleY'
    CFloat
outDx' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outDx
    let outDx'' :: Float
outDx'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outDx'
    CFloat
outDy' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outDy
    let outDy'' :: Float
outDy'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outDy'
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outScaleX
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outScaleY
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outDx
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outDy
    (Float, Float, Float, Float) -> IO (Float, Float, Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
outScaleX'', Float
outScaleY'', Float
outDx'', Float
outDy'')

#if defined(ENABLE_OVERLOADING)
data TransformToAffineMethodInfo
instance (signature ~ (m ((Float, Float, Float, Float))), MonadIO m) => O.MethodInfo TransformToAffineMethodInfo Transform signature where
    overloadedMethod = transformToAffine

#endif

-- method Transform::to_matrix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_matrix"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The matrix to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_to_matrix" gsk_transform_to_matrix :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Graphene.Matrix.Matrix ->           -- out_matrix : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Computes the actual value of /@self@/ and stores it in /@outMatrix@/.
-- The previous value of /@outMatrix@/ will be ignored.
transformToMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> m (Graphene.Matrix.Matrix)
transformToMatrix :: Transform -> m Matrix
transformToMatrix Transform
self = IO Matrix -> m Matrix
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Matrix -> m Matrix) -> IO Matrix -> m Matrix
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr Matrix
outMatrix <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Graphene.Matrix.Matrix)
    Ptr Transform -> Ptr Matrix -> IO ()
gsk_transform_to_matrix Ptr Transform
self' Ptr Matrix
outMatrix
    Matrix
outMatrix' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Graphene.Matrix.Matrix) Ptr Matrix
outMatrix
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Matrix -> IO Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
outMatrix'

#if defined(ENABLE_OVERLOADING)
data TransformToMatrixMethodInfo
instance (signature ~ (m (Graphene.Matrix.Matrix)), MonadIO m) => O.MethodInfo TransformToMatrixMethodInfo Transform signature where
    overloadedMethod = transformToMatrix

#endif

-- method Transform::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_to_string" gsk_transform_to_string :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO CString

-- | Converts a matrix into a string that is suitable for
-- printing and can later be parsed with 'GI.Gsk.Functions.transformParse'.
-- 
-- This is a wrapper around 'GI.Gsk.Structs.Transform.transformPrint', see that function
-- for details.
transformToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> m T.Text
    -- ^ __Returns:__ A new string for /@self@/
transformToString :: Transform -> m Text
transformToString Transform
self = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    CString
result <- Ptr Transform -> IO CString
gsk_transform_to_string Ptr Transform
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data TransformToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo TransformToStringMethodInfo Transform signature where
    overloadedMethod = transformToString

#endif

-- method Transform::to_translate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_dx"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the translation\n    in the x direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "out_dy"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the translation\n    in the y direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_to_translate" gsk_transform_to_translate :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr CFloat ->                           -- out_dx : TBasicType TFloat
    Ptr CFloat ->                           -- out_dy : TBasicType TFloat
    IO ()

-- | Converts a t'GI.Gsk.Structs.Transform.Transform' to a translation operation.
-- /@self@/ must be a 2D transformation. If you are not
-- sure, use 'GI.Gsk.Structs.Transform.transformGetCategory' >=
-- 'GI.Gsk.Enums.TransformCategory2dTranslate' to check.
transformToTranslate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> m ((Float, Float))
transformToTranslate :: Transform -> m (Float, Float)
transformToTranslate Transform
self = IO (Float, Float) -> m (Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float) -> m (Float, Float))
-> IO (Float, Float) -> m (Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr CFloat
outDx <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
outDy <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Transform -> Ptr CFloat -> Ptr CFloat -> IO ()
gsk_transform_to_translate Ptr Transform
self' Ptr CFloat
outDx Ptr CFloat
outDy
    CFloat
outDx' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outDx
    let outDx'' :: Float
outDx'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outDx'
    CFloat
outDy' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
outDy
    let outDy'' :: Float
outDy'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
outDy'
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outDx
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
outDy
    (Float, Float) -> IO (Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
outDx'', Float
outDy'')

#if defined(ENABLE_OVERLOADING)
data TransformToTranslateMethodInfo
instance (signature ~ (m ((Float, Float))), MonadIO m) => O.MethodInfo TransformToTranslateMethodInfo Transform signature where
    overloadedMethod = transformToTranslate

#endif

-- method Transform::transform
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Transform to apply @other to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "other"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Transform to apply" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_transform" gsk_transform_transform :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Transform ->                        -- other : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO (Ptr Transform)

-- | Applies all the operations from /@other@/ to /@next@/.
transformTransform ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: Transform to apply /@other@/ to
    -> Maybe (Transform)
    -- ^ /@other@/: Transform to apply
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformTransform :: Transform -> Maybe Transform -> m Transform
transformTransform Transform
next Maybe Transform
other = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    Ptr Transform
maybeOther <- case Maybe Transform
other of
        Maybe Transform
Nothing -> Ptr Transform -> IO (Ptr Transform)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Transform
forall a. Ptr a
nullPtr
        Just Transform
jOther -> do
            Ptr Transform
jOther' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
jOther
            Ptr Transform -> IO (Ptr Transform)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Transform
jOther'
    Ptr Transform
result <- Ptr Transform -> Ptr Transform -> IO (Ptr Transform)
gsk_transform_transform Ptr Transform
next' Ptr Transform
maybeOther
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformTransform" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Maybe Transform -> (Transform -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Transform
other Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformTransformMethodInfo
instance (signature ~ (Maybe (Transform) -> m Transform), MonadIO m) => O.MethodInfo TransformTransformMethodInfo Transform signature where
    overloadedMethod = transformTransform

#endif

-- method Transform::transform_bounds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rect"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_rect"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the bounds\n  of the transformed rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_transform_bounds" gsk_transform_transform_bounds :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Graphene.Rect.Rect ->               -- rect : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Rect.Rect ->               -- out_rect : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Transforms a t'GI.Graphene.Structs.Rect.Rect' using the given transform /@self@/.
-- The result is the bounding box containing the coplanar quad.
transformTransformBounds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> Graphene.Rect.Rect
    -- ^ /@rect@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Rect.Rect)
transformTransformBounds :: Transform -> Rect -> m Rect
transformTransformBounds Transform
self Rect
rect = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr Rect
rect' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
rect
    Ptr Rect
outRect <- Int -> IO (Ptr Rect)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Rect.Rect)
    Ptr Transform -> Ptr Rect -> Ptr Rect -> IO ()
gsk_transform_transform_bounds Ptr Transform
self' Ptr Rect
rect' Ptr Rect
outRect
    Rect
outRect' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Graphene.Rect.Rect) Ptr Rect
outRect
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
rect
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
outRect'

#if defined(ENABLE_OVERLOADING)
data TransformTransformBoundsMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m (Graphene.Rect.Rect)), MonadIO m) => O.MethodInfo TransformTransformBoundsMethodInfo Transform signature where
    overloadedMethod = transformTransformBounds

#endif

-- method Transform::transform_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for\n  the transformed point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_transform_point" gsk_transform_transform_point :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Graphene.Point.Point ->             -- point : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Graphene.Point.Point ->             -- out_point : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Transforms a t'GI.Graphene.Structs.Point.Point' using the given transform /@self@/.
transformTransformPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> Graphene.Point.Point
    -- ^ /@point@/: a t'GI.Graphene.Structs.Point.Point'
    -> m (Graphene.Point.Point)
transformTransformPoint :: Transform -> Point -> m Point
transformTransformPoint Transform
self Point
point = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr Point
point' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
point
    Ptr Point
outPoint <- Int -> IO (Ptr Point)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
8 :: IO (Ptr Graphene.Point.Point)
    Ptr Transform -> Ptr Point -> Ptr Point -> IO ()
gsk_transform_transform_point Ptr Transform
self' Ptr Point
point' Ptr Point
outPoint
    Point
outPoint' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
outPoint
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
point
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
outPoint'

#if defined(ENABLE_OVERLOADING)
data TransformTransformPointMethodInfo
instance (signature ~ (Graphene.Point.Point -> m (Graphene.Point.Point)), MonadIO m) => O.MethodInfo TransformTransformPointMethodInfo Transform signature where
    overloadedMethod = transformTransformPoint

#endif

-- method Transform::translate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the point to translate the matrix by"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_translate" gsk_transform_translate :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Graphene.Point.Point ->             -- point : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO (Ptr Transform)

-- | Translates /@next@/ in 2dimensional space by /@point@/.
transformTranslate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Graphene.Point.Point
    -- ^ /@point@/: the point to translate the matrix by
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformTranslate :: Transform -> Point -> m Transform
transformTranslate Transform
next Point
point = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    Ptr Point
point' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
point
    Ptr Transform
result <- Ptr Transform -> Ptr Point -> IO (Ptr Transform)
gsk_transform_translate Ptr Transform
next' Ptr Point
point'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformTranslate" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
point
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformTranslateMethodInfo
instance (signature ~ (Graphene.Point.Point -> m Transform), MonadIO m) => O.MethodInfo TransformTranslateMethodInfo Transform signature where
    overloadedMethod = transformTranslate

#endif

-- method Transform::translate_3d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "next"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the next transform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the point to translate the matrix by"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_translate_3d" gsk_transform_translate_3d :: 
    Ptr Transform ->                        -- next : TInterface (Name {namespace = "Gsk", name = "Transform"})
    Ptr Graphene.Point3D.Point3D ->         -- point : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO (Ptr Transform)

-- | Translates /@next@/ by /@point@/.
transformTranslate3d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@next@/: the next transform
    -> Graphene.Point3D.Point3D
    -- ^ /@point@/: the point to translate the matrix by
    -> m Transform
    -- ^ __Returns:__ The new matrix
transformTranslate3d :: Transform -> Point3D -> m Transform
transformTranslate3d Transform
next Point3D
point = IO Transform -> m Transform
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Transform -> m Transform) -> IO Transform -> m Transform
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
next' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Transform
next
    Ptr Point3D
point' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
point
    Ptr Transform
result <- Ptr Transform -> Ptr Point3D -> IO (Ptr Transform)
gsk_transform_translate_3d Ptr Transform
next' Ptr Point3D
point'
    Text -> Ptr Transform -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"transformTranslate3d" Ptr Transform
result
    Transform
result' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
result
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
next
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
point
    Transform -> IO Transform
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result'

#if defined(ENABLE_OVERLOADING)
data TransformTranslate3dMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m Transform), MonadIO m) => O.MethodInfo TransformTranslate3dMethodInfo Transform signature where
    overloadedMethod = transformTranslate3d

#endif

-- method Transform::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GskTransform" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_unref" gsk_transform_unref :: 
    Ptr Transform ->                        -- self : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO ()

-- | Releases a reference on the given t'GI.Gsk.Structs.Transform.Transform'.
-- 
-- If the reference was the last, the resources associated to the /@self@/ are
-- freed.
transformUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Transform
    -- ^ /@self@/: a t'GI.Gsk.Structs.Transform.Transform'
    -> m ()
transformUnref :: Transform -> m ()
transformUnref Transform
self = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Transform
self' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
self
    Ptr Transform -> IO ()
gsk_transform_unref Ptr Transform
self'
    Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Transform
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TransformUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TransformUnrefMethodInfo Transform signature where
    overloadedMethod = transformUnref

#endif

-- method Transform::parse
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_transform"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The location to put the transform in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gsk_transform_parse" gsk_transform_parse :: 
    CString ->                              -- string : TBasicType TUTF8
    Ptr (Ptr Transform) ->                  -- out_transform : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO CInt

-- | Parses the given /@string@/ into a transform and puts it in
-- /@outTransform@/. Strings printed via 'GI.Gsk.Structs.Transform.transformToString'
-- can be read in again successfully using this function.
-- 
-- If /@string@/ does not describe a valid transform, 'P.False' is
-- returned and 'P.Nothing' is put in /@outTransform@/.
transformParse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@string@/: the string to parse
    -> m ((Bool, Transform))
    -- ^ __Returns:__ 'P.True' if /@string@/ described a valid transform.
transformParse :: Text -> m (Bool, Transform)
transformParse Text
string = IO (Bool, Transform) -> m (Bool, Transform)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Transform) -> m (Bool, Transform))
-> IO (Bool, Transform) -> m (Bool, Transform)
forall a b. (a -> b) -> a -> b
$ do
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr (Ptr Transform)
outTransform <- IO (Ptr (Ptr Transform))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Transform))
    CInt
result <- CString -> Ptr (Ptr Transform) -> IO CInt
gsk_transform_parse CString
string' Ptr (Ptr Transform)
outTransform
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr Transform
outTransform' <- Ptr (Ptr Transform) -> IO (Ptr Transform)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Transform)
outTransform
    Transform
outTransform'' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Transform -> Transform
Transform) Ptr Transform
outTransform'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    Ptr (Ptr Transform) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Transform)
outTransform
    (Bool, Transform) -> IO (Bool, Transform)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Transform
outTransform'')

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTransformMethod (t :: Symbol) (o :: *) :: * where
    ResolveTransformMethod "equal" o = TransformEqualMethodInfo
    ResolveTransformMethod "invert" o = TransformInvertMethodInfo
    ResolveTransformMethod "matrix" o = TransformMatrixMethodInfo
    ResolveTransformMethod "perspective" o = TransformPerspectiveMethodInfo
    ResolveTransformMethod "print" o = TransformPrintMethodInfo
    ResolveTransformMethod "ref" o = TransformRefMethodInfo
    ResolveTransformMethod "rotate" o = TransformRotateMethodInfo
    ResolveTransformMethod "rotate3d" o = TransformRotate3dMethodInfo
    ResolveTransformMethod "scale" o = TransformScaleMethodInfo
    ResolveTransformMethod "scale3d" o = TransformScale3dMethodInfo
    ResolveTransformMethod "to2d" o = TransformTo2dMethodInfo
    ResolveTransformMethod "toAffine" o = TransformToAffineMethodInfo
    ResolveTransformMethod "toMatrix" o = TransformToMatrixMethodInfo
    ResolveTransformMethod "toString" o = TransformToStringMethodInfo
    ResolveTransformMethod "toTranslate" o = TransformToTranslateMethodInfo
    ResolveTransformMethod "transform" o = TransformTransformMethodInfo
    ResolveTransformMethod "transformBounds" o = TransformTransformBoundsMethodInfo
    ResolveTransformMethod "transformPoint" o = TransformTransformPointMethodInfo
    ResolveTransformMethod "translate" o = TransformTranslateMethodInfo
    ResolveTransformMethod "translate3d" o = TransformTranslate3dMethodInfo
    ResolveTransformMethod "unref" o = TransformUnrefMethodInfo
    ResolveTransformMethod "getCategory" o = TransformGetCategoryMethodInfo
    ResolveTransformMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTransformMethod t Transform, O.MethodInfo info Transform p) => OL.IsLabel t (Transform -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif