{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A structure capable of holding a 4x4 matrix.
-- 
-- The contents of the t'GI.Graphene.Structs.Matrix.Matrix' structure are private and
-- should never be accessed directly.

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

module GI.Graphene.Structs.Matrix
    ( 

-- * Exported types
    Matrix(..)                              ,
    newZeroMatrix                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [decompose]("GI.Graphene.Structs.Matrix#g:method:decompose"), [determinant]("GI.Graphene.Structs.Matrix#g:method:determinant"), [equal]("GI.Graphene.Structs.Matrix#g:method:equal"), [equalFast]("GI.Graphene.Structs.Matrix#g:method:equalFast"), [free]("GI.Graphene.Structs.Matrix#g:method:free"), [initFrom2d]("GI.Graphene.Structs.Matrix#g:method:initFrom2d"), [initFromFloat]("GI.Graphene.Structs.Matrix#g:method:initFromFloat"), [initFromMatrix]("GI.Graphene.Structs.Matrix#g:method:initFromMatrix"), [initFromVec4]("GI.Graphene.Structs.Matrix#g:method:initFromVec4"), [initFrustum]("GI.Graphene.Structs.Matrix#g:method:initFrustum"), [initIdentity]("GI.Graphene.Structs.Matrix#g:method:initIdentity"), [initLookAt]("GI.Graphene.Structs.Matrix#g:method:initLookAt"), [initOrtho]("GI.Graphene.Structs.Matrix#g:method:initOrtho"), [initPerspective]("GI.Graphene.Structs.Matrix#g:method:initPerspective"), [initRotate]("GI.Graphene.Structs.Matrix#g:method:initRotate"), [initScale]("GI.Graphene.Structs.Matrix#g:method:initScale"), [initSkew]("GI.Graphene.Structs.Matrix#g:method:initSkew"), [initTranslate]("GI.Graphene.Structs.Matrix#g:method:initTranslate"), [interpolate]("GI.Graphene.Structs.Matrix#g:method:interpolate"), [inverse]("GI.Graphene.Structs.Matrix#g:method:inverse"), [is2d]("GI.Graphene.Structs.Matrix#g:method:is2d"), [isBackfaceVisible]("GI.Graphene.Structs.Matrix#g:method:isBackfaceVisible"), [isIdentity]("GI.Graphene.Structs.Matrix#g:method:isIdentity"), [isSingular]("GI.Graphene.Structs.Matrix#g:method:isSingular"), [multiply]("GI.Graphene.Structs.Matrix#g:method:multiply"), [near]("GI.Graphene.Structs.Matrix#g:method:near"), [normalize]("GI.Graphene.Structs.Matrix#g:method:normalize"), [perspective]("GI.Graphene.Structs.Matrix#g:method:perspective"), [print]("GI.Graphene.Structs.Matrix#g:method:print"), [projectPoint]("GI.Graphene.Structs.Matrix#g:method:projectPoint"), [projectRect]("GI.Graphene.Structs.Matrix#g:method:projectRect"), [projectRectBounds]("GI.Graphene.Structs.Matrix#g:method:projectRectBounds"), [rotate]("GI.Graphene.Structs.Matrix#g:method:rotate"), [rotateEuler]("GI.Graphene.Structs.Matrix#g:method:rotateEuler"), [rotateQuaternion]("GI.Graphene.Structs.Matrix#g:method:rotateQuaternion"), [rotateX]("GI.Graphene.Structs.Matrix#g:method:rotateX"), [rotateY]("GI.Graphene.Structs.Matrix#g:method:rotateY"), [rotateZ]("GI.Graphene.Structs.Matrix#g:method:rotateZ"), [scale]("GI.Graphene.Structs.Matrix#g:method:scale"), [skewXy]("GI.Graphene.Structs.Matrix#g:method:skewXy"), [skewXz]("GI.Graphene.Structs.Matrix#g:method:skewXz"), [skewYz]("GI.Graphene.Structs.Matrix#g:method:skewYz"), [to2d]("GI.Graphene.Structs.Matrix#g:method:to2d"), [transformBounds]("GI.Graphene.Structs.Matrix#g:method:transformBounds"), [transformBox]("GI.Graphene.Structs.Matrix#g:method:transformBox"), [transformPoint]("GI.Graphene.Structs.Matrix#g:method:transformPoint"), [transformPoint3d]("GI.Graphene.Structs.Matrix#g:method:transformPoint3d"), [transformRay]("GI.Graphene.Structs.Matrix#g:method:transformRay"), [transformRect]("GI.Graphene.Structs.Matrix#g:method:transformRect"), [transformSphere]("GI.Graphene.Structs.Matrix#g:method:transformSphere"), [transformVec3]("GI.Graphene.Structs.Matrix#g:method:transformVec3"), [transformVec4]("GI.Graphene.Structs.Matrix#g:method:transformVec4"), [translate]("GI.Graphene.Structs.Matrix#g:method:translate"), [transpose]("GI.Graphene.Structs.Matrix#g:method:transpose"), [unprojectPoint3d]("GI.Graphene.Structs.Matrix#g:method:unprojectPoint3d"), [untransformBounds]("GI.Graphene.Structs.Matrix#g:method:untransformBounds"), [untransformPoint]("GI.Graphene.Structs.Matrix#g:method:untransformPoint").
-- 
-- ==== Getters
-- [getRow]("GI.Graphene.Structs.Matrix#g:method:getRow"), [getValue]("GI.Graphene.Structs.Matrix#g:method:getValue"), [getXScale]("GI.Graphene.Structs.Matrix#g:method:getXScale"), [getXTranslation]("GI.Graphene.Structs.Matrix#g:method:getXTranslation"), [getYScale]("GI.Graphene.Structs.Matrix#g:method:getYScale"), [getYTranslation]("GI.Graphene.Structs.Matrix#g:method:getYTranslation"), [getZScale]("GI.Graphene.Structs.Matrix#g:method:getZScale"), [getZTranslation]("GI.Graphene.Structs.Matrix#g:method:getZTranslation").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveMatrixMethod                     ,
#endif

-- ** alloc #method:alloc#

    matrixAlloc                             ,


-- ** decompose #method:decompose#

#if defined(ENABLE_OVERLOADING)
    MatrixDecomposeMethodInfo               ,
#endif
    matrixDecompose                         ,


-- ** determinant #method:determinant#

#if defined(ENABLE_OVERLOADING)
    MatrixDeterminantMethodInfo             ,
#endif
    matrixDeterminant                       ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    MatrixEqualMethodInfo                   ,
#endif
    matrixEqual                             ,


-- ** equalFast #method:equalFast#

#if defined(ENABLE_OVERLOADING)
    MatrixEqualFastMethodInfo               ,
#endif
    matrixEqualFast                         ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    MatrixFreeMethodInfo                    ,
#endif
    matrixFree                              ,


-- ** getRow #method:getRow#

#if defined(ENABLE_OVERLOADING)
    MatrixGetRowMethodInfo                  ,
#endif
    matrixGetRow                            ,


-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    MatrixGetValueMethodInfo                ,
#endif
    matrixGetValue                          ,


-- ** getXScale #method:getXScale#

#if defined(ENABLE_OVERLOADING)
    MatrixGetXScaleMethodInfo               ,
#endif
    matrixGetXScale                         ,


-- ** getXTranslation #method:getXTranslation#

#if defined(ENABLE_OVERLOADING)
    MatrixGetXTranslationMethodInfo         ,
#endif
    matrixGetXTranslation                   ,


-- ** getYScale #method:getYScale#

#if defined(ENABLE_OVERLOADING)
    MatrixGetYScaleMethodInfo               ,
#endif
    matrixGetYScale                         ,


-- ** getYTranslation #method:getYTranslation#

#if defined(ENABLE_OVERLOADING)
    MatrixGetYTranslationMethodInfo         ,
#endif
    matrixGetYTranslation                   ,


-- ** getZScale #method:getZScale#

#if defined(ENABLE_OVERLOADING)
    MatrixGetZScaleMethodInfo               ,
#endif
    matrixGetZScale                         ,


-- ** getZTranslation #method:getZTranslation#

#if defined(ENABLE_OVERLOADING)
    MatrixGetZTranslationMethodInfo         ,
#endif
    matrixGetZTranslation                   ,


-- ** initFrom2d #method:initFrom2d#

#if defined(ENABLE_OVERLOADING)
    MatrixInitFrom2dMethodInfo              ,
#endif
    matrixInitFrom2d                        ,


-- ** initFromFloat #method:initFromFloat#

#if defined(ENABLE_OVERLOADING)
    MatrixInitFromFloatMethodInfo           ,
#endif
    matrixInitFromFloat                     ,


-- ** initFromMatrix #method:initFromMatrix#

#if defined(ENABLE_OVERLOADING)
    MatrixInitFromMatrixMethodInfo          ,
#endif
    matrixInitFromMatrix                    ,


-- ** initFromVec4 #method:initFromVec4#

#if defined(ENABLE_OVERLOADING)
    MatrixInitFromVec4MethodInfo            ,
#endif
    matrixInitFromVec4                      ,


-- ** initFrustum #method:initFrustum#

#if defined(ENABLE_OVERLOADING)
    MatrixInitFrustumMethodInfo             ,
#endif
    matrixInitFrustum                       ,


-- ** initIdentity #method:initIdentity#

#if defined(ENABLE_OVERLOADING)
    MatrixInitIdentityMethodInfo            ,
#endif
    matrixInitIdentity                      ,


-- ** initLookAt #method:initLookAt#

#if defined(ENABLE_OVERLOADING)
    MatrixInitLookAtMethodInfo              ,
#endif
    matrixInitLookAt                        ,


-- ** initOrtho #method:initOrtho#

#if defined(ENABLE_OVERLOADING)
    MatrixInitOrthoMethodInfo               ,
#endif
    matrixInitOrtho                         ,


-- ** initPerspective #method:initPerspective#

#if defined(ENABLE_OVERLOADING)
    MatrixInitPerspectiveMethodInfo         ,
#endif
    matrixInitPerspective                   ,


-- ** initRotate #method:initRotate#

#if defined(ENABLE_OVERLOADING)
    MatrixInitRotateMethodInfo              ,
#endif
    matrixInitRotate                        ,


-- ** initScale #method:initScale#

#if defined(ENABLE_OVERLOADING)
    MatrixInitScaleMethodInfo               ,
#endif
    matrixInitScale                         ,


-- ** initSkew #method:initSkew#

#if defined(ENABLE_OVERLOADING)
    MatrixInitSkewMethodInfo                ,
#endif
    matrixInitSkew                          ,


-- ** initTranslate #method:initTranslate#

#if defined(ENABLE_OVERLOADING)
    MatrixInitTranslateMethodInfo           ,
#endif
    matrixInitTranslate                     ,


-- ** interpolate #method:interpolate#

#if defined(ENABLE_OVERLOADING)
    MatrixInterpolateMethodInfo             ,
#endif
    matrixInterpolate                       ,


-- ** inverse #method:inverse#

#if defined(ENABLE_OVERLOADING)
    MatrixInverseMethodInfo                 ,
#endif
    matrixInverse                           ,


-- ** is2d #method:is2d#

#if defined(ENABLE_OVERLOADING)
    MatrixIs2dMethodInfo                    ,
#endif
    matrixIs2d                              ,


-- ** isBackfaceVisible #method:isBackfaceVisible#

#if defined(ENABLE_OVERLOADING)
    MatrixIsBackfaceVisibleMethodInfo       ,
#endif
    matrixIsBackfaceVisible                 ,


-- ** isIdentity #method:isIdentity#

#if defined(ENABLE_OVERLOADING)
    MatrixIsIdentityMethodInfo              ,
#endif
    matrixIsIdentity                        ,


-- ** isSingular #method:isSingular#

#if defined(ENABLE_OVERLOADING)
    MatrixIsSingularMethodInfo              ,
#endif
    matrixIsSingular                        ,


-- ** multiply #method:multiply#

#if defined(ENABLE_OVERLOADING)
    MatrixMultiplyMethodInfo                ,
#endif
    matrixMultiply                          ,


-- ** near #method:near#

#if defined(ENABLE_OVERLOADING)
    MatrixNearMethodInfo                    ,
#endif
    matrixNear                              ,


-- ** normalize #method:normalize#

#if defined(ENABLE_OVERLOADING)
    MatrixNormalizeMethodInfo               ,
#endif
    matrixNormalize                         ,


-- ** perspective #method:perspective#

#if defined(ENABLE_OVERLOADING)
    MatrixPerspectiveMethodInfo             ,
#endif
    matrixPerspective                       ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    MatrixPrintMethodInfo                   ,
#endif
    matrixPrint                             ,


-- ** projectPoint #method:projectPoint#

#if defined(ENABLE_OVERLOADING)
    MatrixProjectPointMethodInfo            ,
#endif
    matrixProjectPoint                      ,


-- ** projectRect #method:projectRect#

#if defined(ENABLE_OVERLOADING)
    MatrixProjectRectMethodInfo             ,
#endif
    matrixProjectRect                       ,


-- ** projectRectBounds #method:projectRectBounds#

#if defined(ENABLE_OVERLOADING)
    MatrixProjectRectBoundsMethodInfo       ,
#endif
    matrixProjectRectBounds                 ,


-- ** rotate #method:rotate#

#if defined(ENABLE_OVERLOADING)
    MatrixRotateMethodInfo                  ,
#endif
    matrixRotate                            ,


-- ** rotateEuler #method:rotateEuler#

#if defined(ENABLE_OVERLOADING)
    MatrixRotateEulerMethodInfo             ,
#endif
    matrixRotateEuler                       ,


-- ** rotateQuaternion #method:rotateQuaternion#

#if defined(ENABLE_OVERLOADING)
    MatrixRotateQuaternionMethodInfo        ,
#endif
    matrixRotateQuaternion                  ,


-- ** rotateX #method:rotateX#

#if defined(ENABLE_OVERLOADING)
    MatrixRotateXMethodInfo                 ,
#endif
    matrixRotateX                           ,


-- ** rotateY #method:rotateY#

#if defined(ENABLE_OVERLOADING)
    MatrixRotateYMethodInfo                 ,
#endif
    matrixRotateY                           ,


-- ** rotateZ #method:rotateZ#

#if defined(ENABLE_OVERLOADING)
    MatrixRotateZMethodInfo                 ,
#endif
    matrixRotateZ                           ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    MatrixScaleMethodInfo                   ,
#endif
    matrixScale                             ,


-- ** skewXy #method:skewXy#

#if defined(ENABLE_OVERLOADING)
    MatrixSkewXyMethodInfo                  ,
#endif
    matrixSkewXy                            ,


-- ** skewXz #method:skewXz#

#if defined(ENABLE_OVERLOADING)
    MatrixSkewXzMethodInfo                  ,
#endif
    matrixSkewXz                            ,


-- ** skewYz #method:skewYz#

#if defined(ENABLE_OVERLOADING)
    MatrixSkewYzMethodInfo                  ,
#endif
    matrixSkewYz                            ,


-- ** to2d #method:to2d#

#if defined(ENABLE_OVERLOADING)
    MatrixTo2dMethodInfo                    ,
#endif
    matrixTo2d                              ,


-- ** transformBounds #method:transformBounds#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformBoundsMethodInfo         ,
#endif
    matrixTransformBounds                   ,


-- ** transformBox #method:transformBox#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformBoxMethodInfo            ,
#endif
    matrixTransformBox                      ,


-- ** transformPoint #method:transformPoint#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformPointMethodInfo          ,
#endif
    matrixTransformPoint                    ,


-- ** transformPoint3d #method:transformPoint3d#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformPoint3dMethodInfo        ,
#endif
    matrixTransformPoint3d                  ,


-- ** transformRay #method:transformRay#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformRayMethodInfo            ,
#endif
    matrixTransformRay                      ,


-- ** transformRect #method:transformRect#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformRectMethodInfo           ,
#endif
    matrixTransformRect                     ,


-- ** transformSphere #method:transformSphere#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformSphereMethodInfo         ,
#endif
    matrixTransformSphere                   ,


-- ** transformVec3 #method:transformVec3#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformVec3MethodInfo           ,
#endif
    matrixTransformVec3                     ,


-- ** transformVec4 #method:transformVec4#

#if defined(ENABLE_OVERLOADING)
    MatrixTransformVec4MethodInfo           ,
#endif
    matrixTransformVec4                     ,


-- ** translate #method:translate#

#if defined(ENABLE_OVERLOADING)
    MatrixTranslateMethodInfo               ,
#endif
    matrixTranslate                         ,


-- ** transpose #method:transpose#

#if defined(ENABLE_OVERLOADING)
    MatrixTransposeMethodInfo               ,
#endif
    matrixTranspose                         ,


-- ** unprojectPoint3d #method:unprojectPoint3d#

#if defined(ENABLE_OVERLOADING)
    MatrixUnprojectPoint3dMethodInfo        ,
#endif
    matrixUnprojectPoint3d                  ,


-- ** untransformBounds #method:untransformBounds#

#if defined(ENABLE_OVERLOADING)
    MatrixUntransformBoundsMethodInfo       ,
#endif
    matrixUntransformBounds                 ,


-- ** untransformPoint #method:untransformPoint#

#if defined(ENABLE_OVERLOADING)
    MatrixUntransformPointMethodInfo        ,
#endif
    matrixUntransformPoint                  ,




    ) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
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 GHC.Records as R

import {-# SOURCE #-} qualified GI.Graphene.Structs.Box as Graphene.Box
import {-# SOURCE #-} qualified GI.Graphene.Structs.Euler as Graphene.Euler
import {-# SOURCE #-} qualified GI.Graphene.Structs.Point as Graphene.Point
import {-# SOURCE #-} qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import {-# SOURCE #-} qualified GI.Graphene.Structs.Quad as Graphene.Quad
import {-# SOURCE #-} qualified GI.Graphene.Structs.Quaternion as Graphene.Quaternion
import {-# SOURCE #-} qualified GI.Graphene.Structs.Ray as Graphene.Ray
import {-# SOURCE #-} qualified GI.Graphene.Structs.Rect as Graphene.Rect
import {-# SOURCE #-} qualified GI.Graphene.Structs.Sphere as Graphene.Sphere
import {-# SOURCE #-} qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import {-# SOURCE #-} qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4

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

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

foreign import ccall "graphene_matrix_get_type" c_graphene_matrix_get_type :: 
    IO GType

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

instance B.Types.TypedObject Matrix where
    glibType :: IO GType
glibType = IO GType
c_graphene_matrix_get_type

instance B.Types.GBoxed Matrix

-- | Convert 'Matrix' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Matrix) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_graphene_matrix_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Matrix -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Matrix
P.Nothing = Ptr GValue -> Ptr Matrix -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Matrix
forall a. Ptr a
FP.nullPtr :: FP.Ptr Matrix)
    gvalueSet_ Ptr GValue
gv (P.Just Matrix
obj) = Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Matrix
obj (Ptr GValue -> Ptr Matrix -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Matrix)
gvalueGet_ Ptr GValue
gv = do
        Ptr Matrix
ptr <- Ptr GValue -> IO (Ptr Matrix)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Matrix)
        if Ptr Matrix
ptr Ptr Matrix -> Ptr Matrix -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Matrix
forall a. Ptr a
FP.nullPtr
        then Matrix -> Maybe Matrix
forall a. a -> Maybe a
P.Just (Matrix -> Maybe Matrix) -> IO Matrix -> IO (Maybe Matrix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Matrix -> Matrix
Matrix Ptr Matrix
ptr
        else Maybe Matrix -> IO (Maybe Matrix)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Matrix
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `Matrix` struct initialized to zero.
newZeroMatrix :: MonadIO m => m Matrix
newZeroMatrix :: forall (m :: * -> *). MonadIO m => m Matrix
newZeroMatrix = IO Matrix -> m Matrix
forall a. IO a -> m a
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
$ Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
64 IO (Ptr Matrix) -> (Ptr Matrix -> IO Matrix) -> IO Matrix
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix

instance tag ~ 'AttrSet => Constructible Matrix tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr Matrix -> Matrix) -> [AttrOp Matrix tag] -> m Matrix
new ManagedPtr Matrix -> Matrix
_ [AttrOp Matrix tag]
attrs = do
        Matrix
o <- m Matrix
forall (m :: * -> *). MonadIO m => m Matrix
newZeroMatrix
        Matrix -> [AttrOp Matrix 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Matrix
o [AttrOp Matrix tag]
[AttrOp Matrix 'AttrSet]
attrs
        Matrix -> m Matrix
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
o



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

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

foreign import ccall "graphene_matrix_alloc" graphene_matrix_alloc :: 
    IO (Ptr Matrix)

-- | Allocates a new t'GI.Graphene.Structs.Matrix.Matrix'.
-- 
-- /Since: 1.0/
matrixAlloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Matrix
    -- ^ __Returns:__ the newly allocated matrix
matrixAlloc :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Matrix
matrixAlloc  = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
result <- IO (Ptr Matrix)
graphene_matrix_alloc
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixAlloc" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Matrix::decompose
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "translate"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the translation vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale vector" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rotate"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation quaternion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shear"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the shear vector" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "perspective"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the perspective vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_decompose" graphene_matrix_decompose :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Vec3.Vec3 ->               -- translate : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec3.Vec3 ->               -- scale : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Quaternion.Quaternion ->   -- rotate : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Graphene.Vec3.Vec3 ->               -- shear : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec4.Vec4 ->               -- perspective : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO CInt

-- | Decomposes a transformation matrix into its component transformations.
-- 
-- The algorithm for decomposing a matrix is taken from the
-- <http://dev.w3.org/csswg/css-transforms/ CSS3 Transforms specification>;
-- specifically, the decomposition code is based on the equivalent code
-- published in \"Graphics Gems II\", edited by Jim Arvo, and
-- <http://web.archive.org/web/20150512160205/http://tog.acm.org/resources/GraphicsGems/gemsii/unmatrix.c available online>.
matrixDecompose ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m ((Bool, Graphene.Vec3.Vec3, Graphene.Vec3.Vec3, Graphene.Quaternion.Quaternion, Graphene.Vec3.Vec3, Graphene.Vec4.Vec4))
    -- ^ __Returns:__ @true@ if the matrix could be decomposed
matrixDecompose :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
matrixDecompose Matrix
m = IO (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
-> m (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
 -> m (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4))
-> IO (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
-> m (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Vec3
translate <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Vec3
scale <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Quaternion
rotate <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Quaternion.Quaternion)
    Ptr Vec3
shear <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Vec4
perspective <- Int -> IO (Ptr Vec4)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec4.Vec4)
    CInt
result <- Ptr Matrix
-> Ptr Vec3
-> Ptr Vec3
-> Ptr Quaternion
-> Ptr Vec3
-> Ptr Vec4
-> IO CInt
graphene_matrix_decompose Ptr Matrix
m' Ptr Vec3
translate Ptr Vec3
scale Ptr Quaternion
rotate Ptr Vec3
shear Ptr Vec4
perspective
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Vec3
translate' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Graphene.Vec3.Vec3) Ptr Vec3
translate
    Vec3
scale' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Graphene.Vec3.Vec3) Ptr Vec3
scale
    Quaternion
rotate' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Graphene.Quaternion.Quaternion) Ptr Quaternion
rotate
    Vec3
shear' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Graphene.Vec3.Vec3) Ptr Vec3
shear
    Vec4
perspective' <- ((ManagedPtr Vec4 -> Vec4) -> Ptr Vec4 -> IO Vec4
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec4 -> Vec4
Graphene.Vec4.Vec4) Ptr Vec4
perspective
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
-> IO (Bool, Vec3, Vec3, Quaternion, Vec3, Vec4)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Vec3
translate', Vec3
scale', Quaternion
rotate', Vec3
shear', Vec4
perspective')

#if defined(ENABLE_OVERLOADING)
data MatrixDecomposeMethodInfo
instance (signature ~ (m ((Bool, Graphene.Vec3.Vec3, Graphene.Vec3.Vec3, Graphene.Quaternion.Quaternion, Graphene.Vec3.Vec3, Graphene.Vec4.Vec4))), MonadIO m) => O.OverloadedMethod MatrixDecomposeMethodInfo Matrix signature where
    overloadedMethod = matrixDecompose

instance O.OverloadedMethodInfo MatrixDecomposeMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixDecompose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixDecompose"
        })


#endif

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

foreign import ccall "graphene_matrix_determinant" graphene_matrix_determinant :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Computes the determinant of the given matrix.
-- 
-- /Since: 1.0/
matrixDeterminant ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the value of the determinant
matrixDeterminant :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixDeterminant Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_determinant Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixDeterminantMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixDeterminantMethodInfo Matrix signature where
    overloadedMethod = matrixDeterminant

instance O.OverloadedMethodInfo MatrixDeterminantMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixDeterminant",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixDeterminant"
        })


#endif

-- method Matrix::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , 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 "graphene_matrix_equal" graphene_matrix_equal :: 
    Ptr Matrix ->                           -- a : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- b : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Checks whether the two given t'GI.Graphene.Structs.Matrix.Matrix' matrices are equal.
-- 
-- /Since: 1.10/
matrixEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@a@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Matrix
    -- ^ /@b@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Bool
    -- ^ __Returns:__ @true@ if the two matrices are equal, and @false@ otherwise
matrixEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> m Bool
matrixEqual Matrix
a Matrix
b = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
a' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
a
    Ptr Matrix
b' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
b
    CInt
result <- Ptr Matrix -> Ptr Matrix -> IO CInt
graphene_matrix_equal Ptr Matrix
a' Ptr Matrix
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
a
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixEqualMethodInfo
instance (signature ~ (Matrix -> m Bool), MonadIO m) => O.OverloadedMethod MatrixEqualMethodInfo Matrix signature where
    overloadedMethod = matrixEqual

instance O.OverloadedMethodInfo MatrixEqualMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixEqual",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixEqual"
        })


#endif

-- method Matrix::equal_fast
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , 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 "graphene_matrix_equal_fast" graphene_matrix_equal_fast :: 
    Ptr Matrix ->                           -- a : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- b : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Checks whether the two given t'GI.Graphene.Structs.Matrix.Matrix' matrices are
-- byte-by-byte equal.
-- 
-- While this function is faster than 'GI.Graphene.Structs.Matrix.matrixEqual', it
-- can also return false negatives, so it should be used in
-- conjuction with either 'GI.Graphene.Structs.Matrix.matrixEqual' or
-- 'GI.Graphene.Structs.Matrix.matrixNear'. For instance:
-- 
-- 
-- === /C code/
-- >
-- >  if (graphene_matrix_equal_fast (a, b))
-- >    {
-- >      // matrices are definitely the same
-- >    }
-- >  else
-- >    {
-- >      if (graphene_matrix_equal (a, b))
-- >        // matrices contain the same values within an epsilon of FLT_EPSILON
-- >      else if (graphene_matrix_near (a, b, 0.0001))
-- >        // matrices contain the same values within an epsilon of 0.0001
-- >      else
-- >        // matrices are not equal
-- >    }
-- 
-- 
-- /Since: 1.10/
matrixEqualFast ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@a@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Matrix
    -- ^ /@b@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Bool
    -- ^ __Returns:__ @true@ if the matrices are equal. and @false@ otherwise
matrixEqualFast :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> m Bool
matrixEqualFast Matrix
a Matrix
b = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
a' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
a
    Ptr Matrix
b' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
b
    CInt
result <- Ptr Matrix -> Ptr Matrix -> IO CInt
graphene_matrix_equal_fast Ptr Matrix
a' Ptr Matrix
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
a
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixEqualFastMethodInfo
instance (signature ~ (Matrix -> m Bool), MonadIO m) => O.OverloadedMethod MatrixEqualFastMethodInfo Matrix signature where
    overloadedMethod = matrixEqualFast

instance O.OverloadedMethodInfo MatrixEqualFastMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixEqualFast",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixEqualFast"
        })


#endif

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

foreign import ccall "graphene_matrix_free" graphene_matrix_free :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Frees the resources allocated by 'GI.Graphene.Structs.Matrix.matrixAlloc'.
-- 
-- /Since: 1.0/
matrixFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m ()
matrixFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Matrix -> m ()
matrixFree Matrix
m = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix -> IO ()
graphene_matrix_free Ptr Matrix
m'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MatrixFreeMethodInfo Matrix signature where
    overloadedMethod = matrixFree

instance O.OverloadedMethodInfo MatrixFreeMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixFree"
        })


#endif

-- method Matrix::get_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the row vector, between 0 and 3"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the #graphene_vec4_t\n  that is used to store the row vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_get_row" graphene_matrix_get_row :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Word32 ->                               -- index_ : TBasicType TUInt
    Ptr Graphene.Vec4.Vec4 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO ()

-- | Retrieves the given row vector at /@index_@/ inside a matrix.
-- 
-- /Since: 1.0/
matrixGetRow ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Word32
    -- ^ /@index_@/: the index of the row vector, between 0 and 3
    -> m (Graphene.Vec4.Vec4)
matrixGetRow :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Word32 -> m Vec4
matrixGetRow Matrix
m Word32
index_ = IO Vec4 -> m Vec4
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec4 -> m Vec4) -> IO Vec4 -> m Vec4
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Vec4
res <- Int -> IO (Ptr Vec4)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec4.Vec4)
    Ptr Matrix -> Word32 -> Ptr Vec4 -> IO ()
graphene_matrix_get_row Ptr Matrix
m' Word32
index_ Ptr Vec4
res
    Vec4
res' <- ((ManagedPtr Vec4 -> Vec4) -> Ptr Vec4 -> IO Vec4
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec4 -> Vec4
Graphene.Vec4.Vec4) Ptr Vec4
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec4 -> IO Vec4
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
res'

#if defined(ENABLE_OVERLOADING)
data MatrixGetRowMethodInfo
instance (signature ~ (Word32 -> m (Graphene.Vec4.Vec4)), MonadIO m) => O.OverloadedMethod MatrixGetRowMethodInfo Matrix signature where
    overloadedMethod = matrixGetRow

instance O.OverloadedMethodInfo MatrixGetRowMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetRow"
        })


#endif

-- method Matrix::get_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "row"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the row index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "col"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the column index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_get_value" graphene_matrix_get_value :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Word32 ->                               -- row : TBasicType TUInt
    Word32 ->                               -- col : TBasicType TUInt
    IO CFloat

-- | Retrieves the value at the given /@row@/ and /@col@/ index.
-- 
-- /Since: 1.0/
matrixGetValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Word32
    -- ^ /@row@/: the row index
    -> Word32
    -- ^ /@col@/: the column index
    -> m Float
    -- ^ __Returns:__ the value at the given indices
matrixGetValue :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Word32 -> Word32 -> m Float
matrixGetValue Matrix
m Word32
row Word32
col = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> Word32 -> Word32 -> IO CFloat
graphene_matrix_get_value Ptr Matrix
m' Word32
row Word32
col
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetValueMethodInfo
instance (signature ~ (Word32 -> Word32 -> m Float), MonadIO m) => O.OverloadedMethod MatrixGetValueMethodInfo Matrix signature where
    overloadedMethod = matrixGetValue

instance O.OverloadedMethodInfo MatrixGetValueMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetValue"
        })


#endif

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

foreign import ccall "graphene_matrix_get_x_scale" graphene_matrix_get_x_scale :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Retrieves the scaling factor on the X axis in /@m@/.
-- 
-- /Since: 1.0/
matrixGetXScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the value of the scaling factor
matrixGetXScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixGetXScale Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_get_x_scale Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetXScaleMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixGetXScaleMethodInfo Matrix signature where
    overloadedMethod = matrixGetXScale

instance O.OverloadedMethodInfo MatrixGetXScaleMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetXScale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetXScale"
        })


#endif

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

foreign import ccall "graphene_matrix_get_x_translation" graphene_matrix_get_x_translation :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Retrieves the translation component on the X axis from /@m@/.
-- 
-- /Since: 1.10/
matrixGetXTranslation ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the translation component
matrixGetXTranslation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixGetXTranslation Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_get_x_translation Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetXTranslationMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixGetXTranslationMethodInfo Matrix signature where
    overloadedMethod = matrixGetXTranslation

instance O.OverloadedMethodInfo MatrixGetXTranslationMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetXTranslation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetXTranslation"
        })


#endif

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

foreign import ccall "graphene_matrix_get_y_scale" graphene_matrix_get_y_scale :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Retrieves the scaling factor on the Y axis in /@m@/.
-- 
-- /Since: 1.0/
matrixGetYScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the value of the scaling factor
matrixGetYScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixGetYScale Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_get_y_scale Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetYScaleMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixGetYScaleMethodInfo Matrix signature where
    overloadedMethod = matrixGetYScale

instance O.OverloadedMethodInfo MatrixGetYScaleMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetYScale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetYScale"
        })


#endif

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

foreign import ccall "graphene_matrix_get_y_translation" graphene_matrix_get_y_translation :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Retrieves the translation component on the Y axis from /@m@/.
-- 
-- /Since: 1.10/
matrixGetYTranslation ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the translation component
matrixGetYTranslation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixGetYTranslation Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_get_y_translation Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetYTranslationMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixGetYTranslationMethodInfo Matrix signature where
    overloadedMethod = matrixGetYTranslation

instance O.OverloadedMethodInfo MatrixGetYTranslationMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetYTranslation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetYTranslation"
        })


#endif

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

foreign import ccall "graphene_matrix_get_z_scale" graphene_matrix_get_z_scale :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Retrieves the scaling factor on the Z axis in /@m@/.
-- 
-- /Since: 1.0/
matrixGetZScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the value of the scaling factor
matrixGetZScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixGetZScale Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_get_z_scale Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetZScaleMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixGetZScaleMethodInfo Matrix signature where
    overloadedMethod = matrixGetZScale

instance O.OverloadedMethodInfo MatrixGetZScaleMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetZScale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetZScale"
        })


#endif

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

foreign import ccall "graphene_matrix_get_z_translation" graphene_matrix_get_z_translation :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CFloat

-- | Retrieves the translation component on the Z axis from /@m@/.
-- 
-- /Since: 1.10/
matrixGetZTranslation ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Float
    -- ^ __Returns:__ the translation component
matrixGetZTranslation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Float
matrixGetZTranslation Matrix
m = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CFloat
result <- Ptr Matrix -> IO CFloat
graphene_matrix_get_z_translation Ptr Matrix
m'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data MatrixGetZTranslationMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod MatrixGetZTranslationMethodInfo Matrix signature where
    overloadedMethod = matrixGetZTranslation

instance O.OverloadedMethodInfo MatrixGetZTranslationMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixGetZTranslation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixGetZTranslation"
        })


#endif

-- method Matrix::init_from_2d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "xx"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the xx member" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "yx"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the yx member" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "xy"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the xy member" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "yy"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the yy member" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_0"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the x0 member" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y_0"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the y0 member" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_from_2d" graphene_matrix_init_from_2d :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CDouble ->                              -- xx : TBasicType TDouble
    CDouble ->                              -- yx : TBasicType TDouble
    CDouble ->                              -- xy : TBasicType TDouble
    CDouble ->                              -- yy : TBasicType TDouble
    CDouble ->                              -- x_0 : TBasicType TDouble
    CDouble ->                              -- y_0 : TBasicType TDouble
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' from the values of an affine
-- transformation matrix.
-- 
-- The arguments map to the following matrix layout:
-- 
-- 
-- === /plain code/
-- >
-- >  ⎛ xx  yx ⎞   ⎛  a   b  0 ⎞
-- >  ⎜ xy  yy ⎟ = ⎜  c   d  0 ⎟
-- >  ⎝ x0  y0 ⎠   ⎝ tx  ty  1 ⎠
-- 
-- 
-- This function can be used to convert between an affine matrix type
-- from other libraries and a t'GI.Graphene.Structs.Matrix.Matrix'.
-- 
-- /Since: 1.0/
matrixInitFrom2d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Double
    -- ^ /@xx@/: the xx member
    -> Double
    -- ^ /@yx@/: the yx member
    -> Double
    -- ^ /@xy@/: the xy member
    -> Double
    -- ^ /@yy@/: the yy member
    -> Double
    -- ^ /@x0@/: the x0 member
    -> Double
    -- ^ /@y0@/: the y0 member
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitFrom2d :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> m Matrix
matrixInitFrom2d Matrix
m Double
xx Double
yx Double
xy Double
yy Double
x0 Double
y0 = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let xx' :: CDouble
xx' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
xx
    let yx' :: CDouble
yx' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
yx
    let xy' :: CDouble
xy' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
xy
    let yy' :: CDouble
yy' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
yy
    let x0' :: CDouble
x0' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x0
    let y0' :: CDouble
y0' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y0
    Ptr Matrix
result <- Ptr Matrix
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Matrix)
graphene_matrix_init_from_2d Ptr Matrix
m' CDouble
xx' CDouble
yx' CDouble
xy' CDouble
yy' CDouble
x0' CDouble
y0'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitFrom2d" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitFrom2dMethodInfo
instance (signature ~ (Double -> Double -> Double -> Double -> Double -> Double -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitFrom2dMethodInfo Matrix signature where
    overloadedMethod = matrixInitFrom2d

instance O.OverloadedMethodInfo MatrixInitFrom2dMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitFrom2d",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitFrom2d"
        })


#endif

-- method Matrix::init_from_float
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v"
--           , argType = TCArray False 16 (-1) (TBasicType TFloat)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an array of at least 16 floating\n  point values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_from_float" graphene_matrix_init_from_float :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr CFloat ->                           -- v : TCArray False 16 (-1) (TBasicType TFloat)
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with the given array of floating
-- point values.
-- 
-- /Since: 1.0/
matrixInitFromFloat ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> [Float]
    -- ^ /@v@/: an array of at least 16 floating
    --   point values
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitFromFloat :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> [Float] -> m Matrix
matrixInitFromFloat Matrix
m [Float]
v = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr CFloat
v' <- ((Float -> CFloat) -> [Float] -> IO (Ptr CFloat)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac) [Float]
v
    Ptr Matrix
result <- Ptr Matrix -> Ptr CFloat -> IO (Ptr Matrix)
graphene_matrix_init_from_float Ptr Matrix
m' Ptr CFloat
v'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitFromFloat" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
v'
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitFromFloatMethodInfo
instance (signature ~ ([Float] -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitFromFloatMethodInfo Matrix signature where
    overloadedMethod = matrixInitFromFloat

instance O.OverloadedMethodInfo MatrixInitFromFloatMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitFromFloat",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitFromFloat"
        })


#endif

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

foreign import ccall "graphene_matrix_init_from_matrix" graphene_matrix_init_from_matrix :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- src : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' using the values of the
-- given matrix.
-- 
-- /Since: 1.0/
matrixInitFromMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Matrix
    -- ^ /@src@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitFromMatrix :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> m Matrix
matrixInitFromMatrix Matrix
m Matrix
src = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix
src' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
src
    Ptr Matrix
result <- Ptr Matrix -> Ptr Matrix -> IO (Ptr Matrix)
graphene_matrix_init_from_matrix Ptr Matrix
m' Ptr Matrix
src'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitFromMatrix" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
src
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitFromMatrixMethodInfo
instance (signature ~ (Matrix -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitFromMatrixMethodInfo Matrix signature where
    overloadedMethod = matrixInitFromMatrix

instance O.OverloadedMethodInfo MatrixInitFromMatrixMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitFromMatrix",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitFromMatrix"
        })


#endif

-- method Matrix::init_from_vec4
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v0"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the first row vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v1"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the second row vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v2"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the third row vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v3"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the fourth row vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_from_vec4" graphene_matrix_init_from_vec4 :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Vec4.Vec4 ->               -- v0 : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    Ptr Graphene.Vec4.Vec4 ->               -- v1 : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    Ptr Graphene.Vec4.Vec4 ->               -- v2 : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    Ptr Graphene.Vec4.Vec4 ->               -- v3 : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with the given four row
-- vectors.
-- 
-- /Since: 1.0/
matrixInitFromVec4 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Vec4.Vec4
    -- ^ /@v0@/: the first row vector
    -> Graphene.Vec4.Vec4
    -- ^ /@v1@/: the second row vector
    -> Graphene.Vec4.Vec4
    -- ^ /@v2@/: the third row vector
    -> Graphene.Vec4.Vec4
    -- ^ /@v3@/: the fourth row vector
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitFromVec4 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Vec4 -> Vec4 -> Vec4 -> Vec4 -> m Matrix
matrixInitFromVec4 Matrix
m Vec4
v0 Vec4
v1 Vec4
v2 Vec4
v3 = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Vec4
v0' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
v0
    Ptr Vec4
v1' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
v1
    Ptr Vec4
v2' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
v2
    Ptr Vec4
v3' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
v3
    Ptr Matrix
result <- Ptr Matrix
-> Ptr Vec4 -> Ptr Vec4 -> Ptr Vec4 -> Ptr Vec4 -> IO (Ptr Matrix)
graphene_matrix_init_from_vec4 Ptr Matrix
m' Ptr Vec4
v0' Ptr Vec4
v1' Ptr Vec4
v2' Ptr Vec4
v3'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitFromVec4" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
v0
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
v1
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
v2
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
v3
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitFromVec4MethodInfo
instance (signature ~ (Graphene.Vec4.Vec4 -> Graphene.Vec4.Vec4 -> Graphene.Vec4.Vec4 -> Graphene.Vec4.Vec4 -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitFromVec4MethodInfo Matrix signature where
    overloadedMethod = matrixInitFromVec4

instance O.OverloadedMethodInfo MatrixInitFromVec4MethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitFromVec4",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitFromVec4"
        })


#endif

-- method Matrix::init_frustum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "left"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance of the left clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "right"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance of the right clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bottom"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance of the bottom clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "top"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance of the top clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z_near"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance of the near clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z_far"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance of the far clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_frustum" graphene_matrix_init_frustum :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- left : TBasicType TFloat
    CFloat ->                               -- right : TBasicType TFloat
    CFloat ->                               -- bottom : TBasicType TFloat
    CFloat ->                               -- top : TBasicType TFloat
    CFloat ->                               -- z_near : TBasicType TFloat
    CFloat ->                               -- z_far : TBasicType TFloat
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' compatible with t'GI.Graphene.Structs.Frustum.Frustum'.
-- 
-- See also: 'GI.Graphene.Structs.Frustum.frustumInitFromMatrix'
-- 
-- /Since: 1.2/
matrixInitFrustum ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@left@/: distance of the left clipping plane
    -> Float
    -- ^ /@right@/: distance of the right clipping plane
    -> Float
    -- ^ /@bottom@/: distance of the bottom clipping plane
    -> Float
    -- ^ /@top@/: distance of the top clipping plane
    -> Float
    -- ^ /@zNear@/: distance of the near clipping plane
    -> Float
    -- ^ /@zFar@/: distance of the far clipping plane
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitFrustum :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix
-> Float -> Float -> Float -> Float -> Float -> Float -> m Matrix
matrixInitFrustum Matrix
m Float
left Float
right Float
bottom Float
top Float
zNear Float
zFar = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let left' :: CFloat
left' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
left
    let right' :: CFloat
right' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
right
    let bottom' :: CFloat
bottom' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
bottom
    let top' :: CFloat
top' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
top
    let zNear' :: CFloat
zNear' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
zNear
    let zFar' :: CFloat
zFar' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
zFar
    Ptr Matrix
result <- Ptr Matrix
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> IO (Ptr Matrix)
graphene_matrix_init_frustum Ptr Matrix
m' CFloat
left' CFloat
right' CFloat
bottom' CFloat
top' CFloat
zNear' CFloat
zFar'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitFrustum" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitFrustumMethodInfo
instance (signature ~ (Float -> Float -> Float -> Float -> Float -> Float -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitFrustumMethodInfo Matrix signature where
    overloadedMethod = matrixInitFrustum

instance O.OverloadedMethodInfo MatrixInitFrustumMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitFrustum",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitFrustum"
        })


#endif

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

foreign import ccall "graphene_matrix_init_identity" graphene_matrix_init_identity :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with the identity matrix.
-- 
-- /Since: 1.0/
matrixInitIdentity ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitIdentity :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Matrix
matrixInitIdentity Matrix
m = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix
result <- Ptr Matrix -> IO (Ptr Matrix)
graphene_matrix_init_identity Ptr Matrix
m'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitIdentity" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitIdentityMethodInfo
instance (signature ~ (m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitIdentityMethodInfo Matrix signature where
    overloadedMethod = matrixInitIdentity

instance O.OverloadedMethodInfo MatrixInitIdentityMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitIdentity",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitIdentity"
        })


#endif

-- method Matrix::init_look_at
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "eye"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the vector describing the position to look from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "center"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vector describing the position to look at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "up"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the vector describing the world's upward direction; usually,\n  this is the graphene_vec3_y_axis() vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_look_at" graphene_matrix_init_look_at :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Vec3.Vec3 ->               -- eye : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec3.Vec3 ->               -- center : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec3.Vec3 ->               -- up : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' so that it positions the \"camera\"
-- at the given /@eye@/ coordinates towards an object at the /@center@/
-- coordinates. The top of the camera is aligned to the direction
-- of the /@up@/ vector.
-- 
-- Before the transform, the camera is assumed to be placed at the
-- origin, looking towards the negative Z axis, with the top side of
-- the camera facing in the direction of the Y axis and the right
-- side in the direction of the X axis.
-- 
-- In theory, one could use /@m@/ to transform a model of such a camera
-- into world-space. However, it is more common to use the inverse of
-- /@m@/ to transform another object from world coordinates to the view
-- coordinates of the camera. Typically you would then apply the
-- camera projection transform to get from view to screen
-- coordinates.
-- 
-- /Since: 1.0/
matrixInitLookAt ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Vec3.Vec3
    -- ^ /@eye@/: the vector describing the position to look from
    -> Graphene.Vec3.Vec3
    -- ^ /@center@/: the vector describing the position to look at
    -> Graphene.Vec3.Vec3
    -- ^ /@up@/: the vector describing the world\'s upward direction; usually,
    --   this is the 'GI.Graphene.Functions.vec3YAxis' vector
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitLookAt :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Vec3 -> Vec3 -> Vec3 -> m Matrix
matrixInitLookAt Matrix
m Vec3
eye Vec3
center Vec3
up = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Vec3
eye' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
eye
    Ptr Vec3
center' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
center
    Ptr Vec3
up' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
up
    Ptr Matrix
result <- Ptr Matrix -> Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO (Ptr Matrix)
graphene_matrix_init_look_at Ptr Matrix
m' Ptr Vec3
eye' Ptr Vec3
center' Ptr Vec3
up'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitLookAt" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
eye
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
center
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
up
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitLookAtMethodInfo
instance (signature ~ (Graphene.Vec3.Vec3 -> Graphene.Vec3.Vec3 -> Graphene.Vec3.Vec3 -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitLookAtMethodInfo Matrix signature where
    overloadedMethod = matrixInitLookAt

instance O.OverloadedMethodInfo MatrixInitLookAtMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitLookAt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitLookAt"
        })


#endif

-- method Matrix::init_ortho
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "left"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the left edge of the clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "right"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the right edge of the clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "top"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the top edge of the clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bottom"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the bottom edge of the clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z_near"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the distance of the near clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z_far"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the distance of the far clipping plane"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_ortho" graphene_matrix_init_ortho :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- left : TBasicType TFloat
    CFloat ->                               -- right : TBasicType TFloat
    CFloat ->                               -- top : TBasicType TFloat
    CFloat ->                               -- bottom : TBasicType TFloat
    CFloat ->                               -- z_near : TBasicType TFloat
    CFloat ->                               -- z_far : TBasicType TFloat
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with an orthographic projection.
-- 
-- /Since: 1.0/
matrixInitOrtho ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@left@/: the left edge of the clipping plane
    -> Float
    -- ^ /@right@/: the right edge of the clipping plane
    -> Float
    -- ^ /@top@/: the top edge of the clipping plane
    -> Float
    -- ^ /@bottom@/: the bottom edge of the clipping plane
    -> Float
    -- ^ /@zNear@/: the distance of the near clipping plane
    -> Float
    -- ^ /@zFar@/: the distance of the far clipping plane
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitOrtho :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix
-> Float -> Float -> Float -> Float -> Float -> Float -> m Matrix
matrixInitOrtho Matrix
m Float
left Float
right Float
top Float
bottom Float
zNear Float
zFar = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let left' :: CFloat
left' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
left
    let right' :: CFloat
right' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
right
    let top' :: CFloat
top' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
top
    let bottom' :: CFloat
bottom' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
bottom
    let zNear' :: CFloat
zNear' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
zNear
    let zFar' :: CFloat
zFar' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
zFar
    Ptr Matrix
result <- Ptr Matrix
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> IO (Ptr Matrix)
graphene_matrix_init_ortho Ptr Matrix
m' CFloat
left' CFloat
right' CFloat
top' CFloat
bottom' CFloat
zNear' CFloat
zFar'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitOrtho" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitOrthoMethodInfo
instance (signature ~ (Float -> Float -> Float -> Float -> Float -> Float -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitOrthoMethodInfo Matrix signature where
    overloadedMethod = matrixInitOrtho

instance O.OverloadedMethodInfo MatrixInitOrthoMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitOrtho",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitOrtho"
        })


#endif

-- method Matrix::init_perspective
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fovy"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the field of view angle, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "aspect"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the aspect value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z_near"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the near Z plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z_far"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the far Z plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_perspective" graphene_matrix_init_perspective :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- fovy : TBasicType TFloat
    CFloat ->                               -- aspect : TBasicType TFloat
    CFloat ->                               -- z_near : TBasicType TFloat
    CFloat ->                               -- z_far : TBasicType TFloat
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with a perspective projection.
-- 
-- /Since: 1.0/
matrixInitPerspective ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@fovy@/: the field of view angle, in degrees
    -> Float
    -- ^ /@aspect@/: the aspect value
    -> Float
    -- ^ /@zNear@/: the near Z plane
    -> Float
    -- ^ /@zFar@/: the far Z plane
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitPerspective :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> Float -> Float -> Float -> m Matrix
matrixInitPerspective Matrix
m Float
fovy Float
aspect Float
zNear Float
zFar = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let fovy' :: CFloat
fovy' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
fovy
    let aspect' :: CFloat
aspect' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
aspect
    let zNear' :: CFloat
zNear' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
zNear
    let zFar' :: CFloat
zFar' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
zFar
    Ptr Matrix
result <- Ptr Matrix
-> CFloat -> CFloat -> CFloat -> CFloat -> IO (Ptr Matrix)
graphene_matrix_init_perspective Ptr Matrix
m' CFloat
fovy' CFloat
aspect' CFloat
zNear' CFloat
zFar'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitPerspective" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitPerspectiveMethodInfo
instance (signature ~ (Float -> Float -> Float -> Float -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitPerspectiveMethodInfo Matrix signature where
    overloadedMethod = matrixInitPerspective

instance O.OverloadedMethodInfo MatrixInitPerspectiveMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitPerspective",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitPerspective"
        })


#endif

-- method Matrix::init_rotate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees"
--                 , 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 axis vector as a #graphene_vec3_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_rotate" graphene_matrix_init_rotate :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- angle : TBasicType TFloat
    Ptr Graphene.Vec3.Vec3 ->               -- axis : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO (Ptr Matrix)

-- | Initializes /@m@/ to represent a rotation of /@angle@/ degrees on
-- the axis represented by the /@axis@/ vector.
-- 
-- /Since: 1.0/
matrixInitRotate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees
    -> Graphene.Vec3.Vec3
    -- ^ /@axis@/: the axis vector as a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitRotate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> Vec3 -> m Matrix
matrixInitRotate Matrix
m Float
angle Vec3
axis = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    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 Matrix
result <- Ptr Matrix -> CFloat -> Ptr Vec3 -> IO (Ptr Matrix)
graphene_matrix_init_rotate Ptr Matrix
m' CFloat
angle' Ptr Vec3
axis'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitRotate" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
axis
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitRotateMethodInfo
instance (signature ~ (Float -> Graphene.Vec3.Vec3 -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitRotateMethodInfo Matrix signature where
    overloadedMethod = matrixInitRotate

instance O.OverloadedMethodInfo MatrixInitRotateMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitRotate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitRotate"
        })


#endif

-- method Matrix::init_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor on the X axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor on the Y axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "z"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor on the Z axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_scale" graphene_matrix_init_scale :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- x : TBasicType TFloat
    CFloat ->                               -- y : TBasicType TFloat
    CFloat ->                               -- z : TBasicType TFloat
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with the given scaling factors.
-- 
-- /Since: 1.0/
matrixInitScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@x@/: the scale factor on the X axis
    -> Float
    -- ^ /@y@/: the scale factor on the Y axis
    -> Float
    -- ^ /@z@/: the scale factor on the Z axis
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> Float -> Float -> m Matrix
matrixInitScale Matrix
m Float
x Float
y Float
z = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let x' :: CFloat
x' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x
    let y' :: CFloat
y' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y
    let z' :: CFloat
z' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
z
    Ptr Matrix
result <- Ptr Matrix -> CFloat -> CFloat -> CFloat -> IO (Ptr Matrix)
graphene_matrix_init_scale Ptr Matrix
m' CFloat
x' CFloat
y' CFloat
z'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitScale" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitScaleMethodInfo
instance (signature ~ (Float -> Float -> Float -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitScaleMethodInfo Matrix signature where
    overloadedMethod = matrixInitScale

instance O.OverloadedMethodInfo MatrixInitScaleMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitScale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitScale"
        })


#endif

-- method Matrix::init_skew
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_skew"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "skew factor, in radians, on the X axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y_skew"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "skew factor, in radians, on the Y axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_skew" graphene_matrix_init_skew :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- x_skew : TBasicType TFloat
    CFloat ->                               -- y_skew : TBasicType TFloat
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with a skew transformation
-- with the given factors.
-- 
-- /Since: 1.0/
matrixInitSkew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@xSkew@/: skew factor, in radians, on the X axis
    -> Float
    -- ^ /@ySkew@/: skew factor, in radians, on the Y axis
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitSkew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> Float -> m Matrix
matrixInitSkew Matrix
m Float
xSkew Float
ySkew = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let xSkew' :: CFloat
xSkew' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
xSkew
    let ySkew' :: CFloat
ySkew' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
ySkew
    Ptr Matrix
result <- Ptr Matrix -> CFloat -> CFloat -> IO (Ptr Matrix)
graphene_matrix_init_skew Ptr Matrix
m' CFloat
xSkew' CFloat
ySkew'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitSkew" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitSkewMethodInfo
instance (signature ~ (Float -> Float -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitSkewMethodInfo Matrix signature where
    overloadedMethod = matrixInitSkew

instance O.OverloadedMethodInfo MatrixInitSkewMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitSkew",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitSkew"
        })


#endif

-- method Matrix::init_translate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the translation coordinates"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Matrix" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_init_translate" graphene_matrix_init_translate :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point3D.Point3D ->         -- p : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO (Ptr Matrix)

-- | Initializes a t'GI.Graphene.Structs.Matrix.Matrix' with a translation to the
-- given coordinates.
-- 
-- /Since: 1.0/
matrixInitTranslate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Point3D.Point3D
    -- ^ /@p@/: the translation coordinates
    -> m Matrix
    -- ^ __Returns:__ the initialized matrix
matrixInitTranslate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Point3D -> m Matrix
matrixInitTranslate Matrix
m Point3D
p = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Point3D
p' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
p
    Ptr Matrix
result <- Ptr Matrix -> Ptr Point3D -> IO (Ptr Matrix)
graphene_matrix_init_translate Ptr Matrix
m' Ptr Point3D
p'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"matrixInitTranslate" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
p
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data MatrixInitTranslateMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m Matrix), MonadIO m) => O.OverloadedMethod MatrixInitTranslateMethodInfo Matrix signature where
    overloadedMethod = matrixInitTranslate

instance O.OverloadedMethodInfo MatrixInitTranslateMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInitTranslate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInitTranslate"
        })


#endif

-- method Matrix::interpolate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the linear interpolation factor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  interpolated matrix"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_interpolate" graphene_matrix_interpolate :: 
    Ptr Matrix ->                           -- a : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- b : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CDouble ->                              -- factor : TBasicType TDouble
    Ptr Matrix ->                           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Linearly interpolates the two given t'GI.Graphene.Structs.Matrix.Matrix' by
-- interpolating the decomposed transformations separately.
-- 
-- If either matrix cannot be reduced to their transformations
-- then the interpolation cannot be performed, and this function
-- will return an identity matrix.
-- 
-- /Since: 1.0/
matrixInterpolate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@a@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Matrix
    -- ^ /@b@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Double
    -- ^ /@factor@/: the linear interpolation factor
    -> m (Matrix)
matrixInterpolate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> Double -> m Matrix
matrixInterpolate Matrix
a Matrix
b Double
factor = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
a' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
a
    Ptr Matrix
b' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
b
    let factor' :: CDouble
factor' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
factor
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Matrix)
    Ptr Matrix -> Ptr Matrix -> CDouble -> Ptr Matrix -> IO ()
graphene_matrix_interpolate Ptr Matrix
a' Ptr Matrix
b' CDouble
factor' Ptr Matrix
res
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
a
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
b
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
res'

#if defined(ENABLE_OVERLOADING)
data MatrixInterpolateMethodInfo
instance (signature ~ (Matrix -> Double -> m (Matrix)), MonadIO m) => O.OverloadedMethod MatrixInterpolateMethodInfo Matrix signature where
    overloadedMethod = matrixInterpolate

instance O.OverloadedMethodInfo MatrixInterpolateMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInterpolate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInterpolate"
        })


#endif

-- method Matrix::inverse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  inverse matrix"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_inverse" graphene_matrix_inverse :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Inverts the given matrix.
-- 
-- /Since: 1.0/
matrixInverse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m ((Bool, Matrix))
    -- ^ __Returns:__ @true@ if the matrix is invertible
matrixInverse :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m (Bool, Matrix)
matrixInverse Matrix
m = IO (Bool, Matrix) -> m (Bool, Matrix)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Matrix) -> m (Bool, Matrix))
-> IO (Bool, Matrix) -> m (Bool, Matrix)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Matrix)
    CInt
result <- Ptr Matrix -> Ptr Matrix -> IO CInt
graphene_matrix_inverse Ptr Matrix
m' Ptr Matrix
res
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    (Bool, Matrix) -> IO (Bool, Matrix)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Matrix
res')

#if defined(ENABLE_OVERLOADING)
data MatrixInverseMethodInfo
instance (signature ~ (m ((Bool, Matrix))), MonadIO m) => O.OverloadedMethod MatrixInverseMethodInfo Matrix signature where
    overloadedMethod = matrixInverse

instance O.OverloadedMethodInfo MatrixInverseMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixInverse",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixInverse"
        })


#endif

-- method Matrix::is_2d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , 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 "graphene_matrix_is_2d" graphene_matrix_is_2d :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Checks whether the given t'GI.Graphene.Structs.Matrix.Matrix' is compatible with an
-- a 2D affine transformation matrix.
-- 
-- /Since: 1.0/
matrixIs2d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Bool
    -- ^ __Returns:__ @true@ if the matrix is compatible with an affine
    --   transformation matrix
matrixIs2d :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Matrix -> m Bool
matrixIs2d Matrix
m = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CInt
result <- Ptr Matrix -> IO CInt
graphene_matrix_is_2d Ptr Matrix
m'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixIs2dMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod MatrixIs2dMethodInfo Matrix signature where
    overloadedMethod = matrixIs2d

instance O.OverloadedMethodInfo MatrixIs2dMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixIs2d",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixIs2d"
        })


#endif

-- method Matrix::is_backface_visible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , 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 "graphene_matrix_is_backface_visible" graphene_matrix_is_backface_visible :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Checks whether a t'GI.Graphene.Structs.Matrix.Matrix' has a visible back face.
-- 
-- /Since: 1.0/
matrixIsBackfaceVisible ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Bool
    -- ^ __Returns:__ @true@ if the back face of the matrix is visible
matrixIsBackfaceVisible :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Matrix -> m Bool
matrixIsBackfaceVisible Matrix
m = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CInt
result <- Ptr Matrix -> IO CInt
graphene_matrix_is_backface_visible Ptr Matrix
m'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixIsBackfaceVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod MatrixIsBackfaceVisibleMethodInfo Matrix signature where
    overloadedMethod = matrixIsBackfaceVisible

instance O.OverloadedMethodInfo MatrixIsBackfaceVisibleMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixIsBackfaceVisible",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixIsBackfaceVisible"
        })


#endif

-- method Matrix::is_identity
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , 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 "graphene_matrix_is_identity" graphene_matrix_is_identity :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Checks whether the given t'GI.Graphene.Structs.Matrix.Matrix' is the identity matrix.
-- 
-- /Since: 1.0/
matrixIsIdentity ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Bool
    -- ^ __Returns:__ @true@ if the matrix is the identity matrix
matrixIsIdentity :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Matrix -> m Bool
matrixIsIdentity Matrix
m = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CInt
result <- Ptr Matrix -> IO CInt
graphene_matrix_is_identity Ptr Matrix
m'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixIsIdentityMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod MatrixIsIdentityMethodInfo Matrix signature where
    overloadedMethod = matrixIsIdentity

instance O.OverloadedMethodInfo MatrixIsIdentityMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixIsIdentity",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixIsIdentity"
        })


#endif

-- method Matrix::is_singular
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , 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 "graphene_matrix_is_singular" graphene_matrix_is_singular :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO CInt

-- | Checks whether a matrix is singular.
-- 
-- /Since: 1.0/
matrixIsSingular ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Bool
    -- ^ __Returns:__ @true@ if the matrix is singular
matrixIsSingular :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Matrix -> m Bool
matrixIsSingular Matrix
m = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    CInt
result <- Ptr Matrix -> IO CInt
graphene_matrix_is_singular Ptr Matrix
m'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixIsSingularMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod MatrixIsSingularMethodInfo Matrix signature where
    overloadedMethod = matrixIsSingular

instance O.OverloadedMethodInfo MatrixIsSingularMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixIsSingular",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixIsSingular"
        })


#endif

-- method Matrix::multiply
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the matrix\n  result"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_multiply" graphene_matrix_multiply :: 
    Ptr Matrix ->                           -- a : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- b : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Multiplies two t'GI.Graphene.Structs.Matrix.Matrix'.
-- 
-- Matrix multiplication is not commutative in general; the order of the factors matters.
-- The product of this multiplication is (/@a@/ × /@b@/)
-- 
-- /Since: 1.0/
matrixMultiply ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@a@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Matrix
    -- ^ /@b@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m (Matrix)
matrixMultiply :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> m Matrix
matrixMultiply Matrix
a Matrix
b = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
a' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
a
    Ptr Matrix
b' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
b
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Matrix)
    Ptr Matrix -> Ptr Matrix -> Ptr Matrix -> IO ()
graphene_matrix_multiply Ptr Matrix
a' Ptr Matrix
b' Ptr Matrix
res
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
a
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
b
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
res'

#if defined(ENABLE_OVERLOADING)
data MatrixMultiplyMethodInfo
instance (signature ~ (Matrix -> m (Matrix)), MonadIO m) => O.OverloadedMethod MatrixMultiplyMethodInfo Matrix signature where
    overloadedMethod = matrixMultiply

instance O.OverloadedMethodInfo MatrixMultiplyMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixMultiply",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixMultiply"
        })


#endif

-- method Matrix::near
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "epsilon"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the threshold between the two matrices"
--                 , 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 "graphene_matrix_near" graphene_matrix_near :: 
    Ptr Matrix ->                           -- a : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- b : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- epsilon : TBasicType TFloat
    IO CInt

-- | Compares the two given t'GI.Graphene.Structs.Matrix.Matrix' matrices and checks
-- whether their values are within the given /@epsilon@/ of each
-- other.
-- 
-- /Since: 1.10/
matrixNear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@a@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Matrix
    -- ^ /@b@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@epsilon@/: the threshold between the two matrices
    -> m Bool
    -- ^ __Returns:__ @true@ if the two matrices are near each other, and
    --   @false@ otherwise
matrixNear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> Float -> m Bool
matrixNear Matrix
a Matrix
b Float
epsilon = IO Bool -> m Bool
forall a. IO a -> m a
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 Matrix
a' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
a
    Ptr Matrix
b' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
b
    let epsilon' :: CFloat
epsilon' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
epsilon
    CInt
result <- Ptr Matrix -> Ptr Matrix -> CFloat -> IO CInt
graphene_matrix_near Ptr Matrix
a' Ptr Matrix
b' CFloat
epsilon'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
a
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MatrixNearMethodInfo
instance (signature ~ (Matrix -> Float -> m Bool), MonadIO m) => O.OverloadedMethod MatrixNearMethodInfo Matrix signature where
    overloadedMethod = matrixNear

instance O.OverloadedMethodInfo MatrixNearMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixNear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixNear"
        })


#endif

-- method Matrix::normalize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the normalized matrix"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_normalize" graphene_matrix_normalize :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Normalizes the given t'GI.Graphene.Structs.Matrix.Matrix'.
-- 
-- /Since: 1.0/
matrixNormalize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m (Matrix)
matrixNormalize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Matrix
matrixNormalize Matrix
m = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Matrix)
    Ptr Matrix -> Ptr Matrix -> IO ()
graphene_matrix_normalize Ptr Matrix
m' Ptr Matrix
res
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
res'

#if defined(ENABLE_OVERLOADING)
data MatrixNormalizeMethodInfo
instance (signature ~ (m (Matrix)), MonadIO m) => O.OverloadedMethod MatrixNormalizeMethodInfo Matrix signature where
    overloadedMethod = matrixNormalize

instance O.OverloadedMethodInfo MatrixNormalizeMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixNormalize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixNormalize"
        })


#endif

-- method Matrix::perspective
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "depth"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the depth of the perspective"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  perspective matrix"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_perspective" graphene_matrix_perspective :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- depth : TBasicType TFloat
    Ptr Matrix ->                           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Applies a perspective of /@depth@/ to the matrix.
-- 
-- /Since: 1.0/
matrixPerspective ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@depth@/: the depth of the perspective
    -> m (Matrix)
matrixPerspective :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m Matrix
matrixPerspective Matrix
m Float
depth = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let depth' :: CFloat
depth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
depth
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Matrix)
    Ptr Matrix -> CFloat -> Ptr Matrix -> IO ()
graphene_matrix_perspective Ptr Matrix
m' CFloat
depth' Ptr Matrix
res
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
res'

#if defined(ENABLE_OVERLOADING)
data MatrixPerspectiveMethodInfo
instance (signature ~ (Float -> m (Matrix)), MonadIO m) => O.OverloadedMethod MatrixPerspectiveMethodInfo Matrix signature where
    overloadedMethod = matrixPerspective

instance O.OverloadedMethodInfo MatrixPerspectiveMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixPerspective",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixPerspective"
        })


#endif

-- method Matrix::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The matrix to print"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_print" graphene_matrix_print :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Prints the contents of a matrix to the standard error stream.
-- 
-- This function is only useful for debugging; there are no guarantees
-- made on the format of the output.
-- 
-- /Since: 1.0/
matrixPrint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: The matrix to print
    -> m ()
matrixPrint :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Matrix -> m ()
matrixPrint Matrix
m = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix -> IO ()
graphene_matrix_print Ptr Matrix
m'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixPrintMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MatrixPrintMethodInfo Matrix signature where
    overloadedMethod = matrixPrint

instance O.OverloadedMethodInfo MatrixPrintMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixPrint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixPrint"
        })


#endif

-- method Matrix::project_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the projected\n  point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_project_point" graphene_matrix_project_point :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Graphene.Point.Point ->             -- res : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Projects a t'GI.Graphene.Structs.Point.Point' using the matrix /@m@/.
-- 
-- /Since: 1.0/
matrixProjectPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Point.Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> m (Graphene.Point.Point)
matrixProjectPoint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Point -> m Point
matrixProjectPoint Matrix
m Point
p = IO Point -> m Point
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Point
res <- Int -> IO (Ptr Point)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
8 :: IO (Ptr Graphene.Point.Point)
    Ptr Matrix -> Ptr Point -> Ptr Point -> IO ()
graphene_matrix_project_point Ptr Matrix
m' Ptr Point
p' Ptr Point
res
    Point
res' <- ((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
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
res'

#if defined(ENABLE_OVERLOADING)
data MatrixProjectPointMethodInfo
instance (signature ~ (Graphene.Point.Point -> m (Graphene.Point.Point)), MonadIO m) => O.OverloadedMethod MatrixProjectPointMethodInfo Matrix signature where
    overloadedMethod = matrixProjectPoint

instance O.OverloadedMethodInfo MatrixProjectPointMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixProjectPoint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixProjectPoint"
        })


#endif

-- method Matrix::project_rect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quad" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the projected\n  rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_project_rect" graphene_matrix_project_rect :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Rect.Rect ->               -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Quad.Quad ->               -- res : TInterface (Name {namespace = "Graphene", name = "Quad"})
    IO ()

-- | Projects all corners of a t'GI.Graphene.Structs.Rect.Rect' using the given matrix.
-- 
-- See also: 'GI.Graphene.Structs.Matrix.matrixProjectPoint'
-- 
-- /Since: 1.2/
matrixProjectRect ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Rect.Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Quad.Quad)
matrixProjectRect :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Rect -> m Quad
matrixProjectRect Matrix
m Rect
r = IO Quad -> m Quad
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quad -> m Quad) -> IO Quad -> m Quad
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Quad
res <- Int -> IO (Ptr Quad)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
32 :: IO (Ptr Graphene.Quad.Quad)
    Ptr Matrix -> Ptr Rect -> Ptr Quad -> IO ()
graphene_matrix_project_rect Ptr Matrix
m' Ptr Rect
r' Ptr Quad
res
    Quad
res' <- ((ManagedPtr Quad -> Quad) -> Ptr Quad -> IO Quad
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quad -> Quad
Graphene.Quad.Quad) Ptr Quad
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Quad -> IO Quad
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Quad
res'

#if defined(ENABLE_OVERLOADING)
data MatrixProjectRectMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m (Graphene.Quad.Quad)), MonadIO m) => O.OverloadedMethod MatrixProjectRectMethodInfo Matrix signature where
    overloadedMethod = matrixProjectRect

instance O.OverloadedMethodInfo MatrixProjectRectMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixProjectRect",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixProjectRect"
        })


#endif

-- method Matrix::project_rect_bounds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the projected\n  rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_project_rect_bounds" graphene_matrix_project_rect_bounds :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Rect.Rect ->               -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Rect.Rect ->               -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Projects a t'GI.Graphene.Structs.Rect.Rect' using the given matrix.
-- 
-- The resulting rectangle is the axis aligned bounding rectangle capable
-- of fully containing the projected rectangle.
-- 
-- /Since: 1.0/
matrixProjectRectBounds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Rect.Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Rect.Rect)
matrixProjectRectBounds :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Rect -> m Rect
matrixProjectRectBounds Matrix
m Rect
r = IO Rect -> m Rect
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Rect.Rect)
    Ptr Matrix -> Ptr Rect -> Ptr Rect -> IO ()
graphene_matrix_project_rect_bounds Ptr Matrix
m' Ptr Rect
r' Ptr Rect
res
    Rect
res' <- ((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
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data MatrixProjectRectBoundsMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m (Graphene.Rect.Rect)), MonadIO m) => O.OverloadedMethod MatrixProjectRectBoundsMethodInfo Matrix signature where
    overloadedMethod = matrixProjectRectBounds

instance O.OverloadedMethodInfo MatrixProjectRectBoundsMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixProjectRectBounds",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixProjectRectBounds"
        })


#endif

-- method Matrix::rotate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees"
--                 , 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, as a #graphene_vec3_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_rotate" graphene_matrix_rotate :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- angle : TBasicType TFloat
    Ptr Graphene.Vec3.Vec3 ->               -- axis : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO ()

-- | Adds a rotation transformation to /@m@/, using the given /@angle@/
-- and /@axis@/ vector.
-- 
-- This is the equivalent of calling 'GI.Graphene.Structs.Matrix.matrixInitRotate' and
-- then multiplying the matrix /@m@/ with the rotation matrix.
-- 
-- /Since: 1.0/
matrixRotate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees
    -> Graphene.Vec3.Vec3
    -- ^ /@axis@/: the rotation axis, as a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m ()
matrixRotate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> Vec3 -> m ()
matrixRotate Matrix
m Float
angle Vec3
axis = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    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 Matrix -> CFloat -> Ptr Vec3 -> IO ()
graphene_matrix_rotate Ptr Matrix
m' CFloat
angle' Ptr Vec3
axis'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
axis
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixRotateMethodInfo
instance (signature ~ (Float -> Graphene.Vec3.Vec3 -> m ()), MonadIO m) => O.OverloadedMethod MatrixRotateMethodInfo Matrix signature where
    overloadedMethod = matrixRotate

instance O.OverloadedMethodInfo MatrixRotateMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixRotate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixRotate"
        })


#endif

-- method Matrix::rotate_euler
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "e"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Euler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a rotation described by a #graphene_euler_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_rotate_euler" graphene_matrix_rotate_euler :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Euler.Euler ->             -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO ()

-- | Adds a rotation transformation to /@m@/, using the given
-- t'GI.Graphene.Structs.Euler.Euler'.
-- 
-- /Since: 1.2/
matrixRotateEuler ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Euler.Euler
    -- ^ /@e@/: a rotation described by a t'GI.Graphene.Structs.Euler.Euler'
    -> m ()
matrixRotateEuler :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Euler -> m ()
matrixRotateEuler Matrix
m Euler
e = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Matrix -> Ptr Euler -> IO ()
graphene_matrix_rotate_euler Ptr Matrix
m' Ptr Euler
e'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixRotateEulerMethodInfo
instance (signature ~ (Graphene.Euler.Euler -> m ()), MonadIO m) => O.OverloadedMethod MatrixRotateEulerMethodInfo Matrix signature where
    overloadedMethod = matrixRotateEuler

instance O.OverloadedMethodInfo MatrixRotateEulerMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixRotateEuler",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixRotateEuler"
        })


#endif

-- method Matrix::rotate_quaternion
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a rotation described by a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_rotate_quaternion" graphene_matrix_rotate_quaternion :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Quaternion.Quaternion ->   -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Adds a rotation transformation to /@m@/, using the given
-- t'GI.Graphene.Structs.Quaternion.Quaternion'.
-- 
-- This is the equivalent of calling 'GI.Graphene.Structs.Quaternion.quaternionToMatrix' and
-- then multiplying /@m@/ with the rotation matrix.
-- 
-- /Since: 1.2/
matrixRotateQuaternion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Quaternion.Quaternion
    -- ^ /@q@/: a rotation described by a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m ()
matrixRotateQuaternion :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Quaternion -> m ()
matrixRotateQuaternion Matrix
m Quaternion
q = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Matrix -> Ptr Quaternion -> IO ()
graphene_matrix_rotate_quaternion Ptr Matrix
m' Ptr Quaternion
q'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixRotateQuaternionMethodInfo
instance (signature ~ (Graphene.Quaternion.Quaternion -> m ()), MonadIO m) => O.OverloadedMethod MatrixRotateQuaternionMethodInfo Matrix signature where
    overloadedMethod = matrixRotateQuaternion

instance O.OverloadedMethodInfo MatrixRotateQuaternionMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixRotateQuaternion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixRotateQuaternion"
        })


#endif

-- method Matrix::rotate_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_rotate_x" graphene_matrix_rotate_x :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- angle : TBasicType TFloat
    IO ()

-- | Adds a rotation transformation around the X axis to /@m@/, using
-- the given /@angle@/.
-- 
-- See also: 'GI.Graphene.Structs.Matrix.matrixRotate'
-- 
-- /Since: 1.0/
matrixRotateX ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees
    -> m ()
matrixRotateX :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m ()
matrixRotateX Matrix
m Float
angle = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
    Ptr Matrix -> CFloat -> IO ()
graphene_matrix_rotate_x Ptr Matrix
m' CFloat
angle'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixRotateXMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixRotateXMethodInfo Matrix signature where
    overloadedMethod = matrixRotateX

instance O.OverloadedMethodInfo MatrixRotateXMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixRotateX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixRotateX"
        })


#endif

-- method Matrix::rotate_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_rotate_y" graphene_matrix_rotate_y :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- angle : TBasicType TFloat
    IO ()

-- | Adds a rotation transformation around the Y axis to /@m@/, using
-- the given /@angle@/.
-- 
-- See also: 'GI.Graphene.Structs.Matrix.matrixRotate'
-- 
-- /Since: 1.0/
matrixRotateY ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees
    -> m ()
matrixRotateY :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m ()
matrixRotateY Matrix
m Float
angle = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
    Ptr Matrix -> CFloat -> IO ()
graphene_matrix_rotate_y Ptr Matrix
m' CFloat
angle'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixRotateYMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixRotateYMethodInfo Matrix signature where
    overloadedMethod = matrixRotateY

instance O.OverloadedMethodInfo MatrixRotateYMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixRotateY",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixRotateY"
        })


#endif

-- method Matrix::rotate_z
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation angle, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_rotate_z" graphene_matrix_rotate_z :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- angle : TBasicType TFloat
    IO ()

-- | Adds a rotation transformation around the Z axis to /@m@/, using
-- the given /@angle@/.
-- 
-- See also: 'GI.Graphene.Structs.Matrix.matrixRotate'
-- 
-- /Since: 1.0/
matrixRotateZ ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@angle@/: the rotation angle, in degrees
    -> m ()
matrixRotateZ :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m ()
matrixRotateZ Matrix
m Float
angle = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
    Ptr Matrix -> CFloat -> IO ()
graphene_matrix_rotate_z Ptr Matrix
m' CFloat
angle'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixRotateZMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixRotateZMethodInfo Matrix signature where
    overloadedMethod = matrixRotateZ

instance O.OverloadedMethodInfo MatrixRotateZMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixRotateZ",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixRotateZ"
        })


#endif

-- method Matrix::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_scale" graphene_matrix_scale :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- factor_x : TBasicType TFloat
    CFloat ->                               -- factor_y : TBasicType TFloat
    CFloat ->                               -- factor_z : TBasicType TFloat
    IO ()

-- | Adds a scaling transformation to /@m@/, using the three
-- given factors.
-- 
-- This is the equivalent of calling 'GI.Graphene.Structs.Matrix.matrixInitScale' and then
-- multiplying the matrix /@m@/ with the scale matrix.
-- 
-- /Since: 1.0/
matrixScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> 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 ()
matrixScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> Float -> Float -> m ()
matrixScale Matrix
m Float
factorX Float
factorY Float
factorZ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    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 Matrix -> CFloat -> CFloat -> CFloat -> IO ()
graphene_matrix_scale Ptr Matrix
m' CFloat
factorX' CFloat
factorY' CFloat
factorZ'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixScaleMethodInfo
instance (signature ~ (Float -> Float -> Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixScaleMethodInfo Matrix signature where
    overloadedMethod = matrixScale

instance O.OverloadedMethodInfo MatrixScaleMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixScale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixScale"
        })


#endif

-- method Matrix::skew_xy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "skew factor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_skew_xy" graphene_matrix_skew_xy :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- factor : TBasicType TFloat
    IO ()

-- | Adds a skew of /@factor@/ on the X and Y axis to the given matrix.
-- 
-- /Since: 1.0/
matrixSkewXy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@factor@/: skew factor
    -> m ()
matrixSkewXy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m ()
matrixSkewXy Matrix
m Float
factor = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Matrix -> CFloat -> IO ()
graphene_matrix_skew_xy Ptr Matrix
m' CFloat
factor'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixSkewXyMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixSkewXyMethodInfo Matrix signature where
    overloadedMethod = matrixSkewXy

instance O.OverloadedMethodInfo MatrixSkewXyMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixSkewXy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixSkewXy"
        })


#endif

-- method Matrix::skew_xz
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "skew factor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_skew_xz" graphene_matrix_skew_xz :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- factor : TBasicType TFloat
    IO ()

-- | Adds a skew of /@factor@/ on the X and Z axis to the given matrix.
-- 
-- /Since: 1.0/
matrixSkewXz ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@factor@/: skew factor
    -> m ()
matrixSkewXz :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m ()
matrixSkewXz Matrix
m Float
factor = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Matrix -> CFloat -> IO ()
graphene_matrix_skew_xz Ptr Matrix
m' CFloat
factor'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixSkewXzMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixSkewXzMethodInfo Matrix signature where
    overloadedMethod = matrixSkewXz

instance O.OverloadedMethodInfo MatrixSkewXzMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixSkewXz",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixSkewXz"
        })


#endif

-- method Matrix::skew_yz
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "skew factor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_skew_yz" graphene_matrix_skew_yz :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    CFloat ->                               -- factor : TBasicType TFloat
    IO ()

-- | Adds a skew of /@factor@/ on the Y and Z axis to the given matrix.
-- 
-- /Since: 1.0/
matrixSkewYz ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Float
    -- ^ /@factor@/: skew factor
    -> m ()
matrixSkewYz :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Float -> m ()
matrixSkewYz Matrix
m Float
factor = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Matrix -> CFloat -> IO ()
graphene_matrix_skew_yz Ptr Matrix
m' CFloat
factor'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixSkewYzMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod MatrixSkewYzMethodInfo Matrix signature where
    overloadedMethod = matrixSkewYz

instance O.OverloadedMethodInfo MatrixSkewYzMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixSkewYz",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixSkewYz"
        })


#endif

-- method Matrix::to_2d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "xx"
--           , argType = TBasicType TDouble
--           , 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 = "yx"
--           , argType = TBasicType TDouble
--           , 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 = "xy"
--           , argType = TBasicType TDouble
--           , 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 = "yy"
--           , argType = TBasicType TDouble
--           , 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 = "x_0"
--           , argType = TBasicType TDouble
--           , 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 = "y_0"
--           , argType = TBasicType TDouble
--           , 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: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_to_2d" graphene_matrix_to_2d :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr CDouble ->                          -- xx : TBasicType TDouble
    Ptr CDouble ->                          -- yx : TBasicType TDouble
    Ptr CDouble ->                          -- xy : TBasicType TDouble
    Ptr CDouble ->                          -- yy : TBasicType TDouble
    Ptr CDouble ->                          -- x_0 : TBasicType TDouble
    Ptr CDouble ->                          -- y_0 : TBasicType TDouble
    IO CInt

-- | Converts a t'GI.Graphene.Structs.Matrix.Matrix' to an affine transformation
-- matrix, if the given matrix is compatible.
-- 
-- The returned values have the following layout:
-- 
-- 
-- === /plain code/
-- >
-- >  ⎛ xx  yx ⎞   ⎛  a   b  0 ⎞
-- >  ⎜ xy  yy ⎟ = ⎜  c   d  0 ⎟
-- >  ⎝ x0  y0 ⎠   ⎝ tx  ty  1 ⎠
-- 
-- 
-- This function can be used to convert between a t'GI.Graphene.Structs.Matrix.Matrix'
-- and an affine matrix type from other libraries.
-- 
-- /Since: 1.0/
matrixTo2d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m ((Bool, Double, Double, Double, Double, Double, Double))
    -- ^ __Returns:__ @true@ if the matrix is compatible with an affine
    --   transformation matrix
matrixTo2d :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m (Bool, Double, Double, Double, Double, Double, Double)
matrixTo2d Matrix
m = IO (Bool, Double, Double, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double, Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double, Double, Double, Double, Double, Double)
 -> m (Bool, Double, Double, Double, Double, Double, Double))
-> IO (Bool, Double, Double, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr CDouble
xx <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
yx <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
xy <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
yy <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
x0 <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
y0 <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    CInt
result <- Ptr Matrix
-> Ptr CDouble
-> Ptr CDouble
-> Ptr CDouble
-> Ptr CDouble
-> Ptr CDouble
-> Ptr CDouble
-> IO CInt
graphene_matrix_to_2d Ptr Matrix
m' Ptr CDouble
xx Ptr CDouble
yx Ptr CDouble
xy Ptr CDouble
yy Ptr CDouble
x0 Ptr CDouble
y0
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CDouble
xx' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
xx
    let xx'' :: Double
xx'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
xx'
    CDouble
yx' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
yx
    let yx'' :: Double
yx'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
yx'
    CDouble
xy' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
xy
    let xy'' :: Double
xy'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
xy'
    CDouble
yy' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
yy
    let yy'' :: Double
yy'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
yy'
    CDouble
x0' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
x0
    let x0'' :: Double
x0'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x0'
    CDouble
y0' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
y0
    let y0'' :: Double
y0'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y0'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
xx
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
yx
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
xy
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
yy
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
x0
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
y0
    (Bool, Double, Double, Double, Double, Double, Double)
-> IO (Bool, Double, Double, Double, Double, Double, Double)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Double
xx'', Double
yx'', Double
xy'', Double
yy'', Double
x0'', Double
y0'')

#if defined(ENABLE_OVERLOADING)
data MatrixTo2dMethodInfo
instance (signature ~ (m ((Bool, Double, Double, Double, Double, Double, Double))), MonadIO m) => O.OverloadedMethod MatrixTo2dMethodInfo Matrix signature where
    overloadedMethod = matrixTo2d

instance O.OverloadedMethodInfo MatrixTo2dMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTo2d",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTo2d"
        })


#endif

-- XXX Could not generate method Matrix::to_float
-- Not implemented: Don't know how to allocate "v" of type TCArray False 16 (-1) (TBasicType TFloat)
-- method Matrix::transform_bounds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , 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 = "res"
--           , 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 "graphene_matrix_transform_bounds" graphene_matrix_transform_bounds :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Rect.Rect ->               -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Rect.Rect ->               -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Transforms each corner of a t'GI.Graphene.Structs.Rect.Rect' using the given matrix /@m@/.
-- 
-- The result is the axis aligned bounding rectangle containing the coplanar
-- quadrilateral.
-- 
-- See also: 'GI.Graphene.Structs.Matrix.matrixTransformPoint'
-- 
-- /Since: 1.0/
matrixTransformBounds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Rect.Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Rect.Rect)
matrixTransformBounds :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Rect -> m Rect
matrixTransformBounds Matrix
m Rect
r = IO Rect -> m Rect
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Rect.Rect)
    Ptr Matrix -> Ptr Rect -> Ptr Rect -> IO ()
graphene_matrix_transform_bounds Ptr Matrix
m' Ptr Rect
r' Ptr Rect
res
    Rect
res' <- ((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
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformBoundsMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m (Graphene.Rect.Rect)), MonadIO m) => O.OverloadedMethod MatrixTransformBoundsMethodInfo Matrix signature where
    overloadedMethod = matrixTransformBounds

instance O.OverloadedMethodInfo MatrixTransformBoundsMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformBounds",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformBounds"
        })


#endif

-- method Matrix::transform_box
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the bounds\n  of the transformed box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_box" graphene_matrix_transform_box :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Box.Box ->                 -- b : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Box.Box ->                 -- res : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO ()

-- | Transforms the vertices of a t'GI.Graphene.Structs.Box.Box' using the given matrix /@m@/.
-- 
-- The result is the axis aligned bounding box containing the transformed
-- vertices.
-- 
-- /Since: 1.2/
matrixTransformBox ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Box.Box
    -- ^ /@b@/: a t'GI.Graphene.Structs.Box.Box'
    -> m (Graphene.Box.Box)
matrixTransformBox :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Box -> m Box
matrixTransformBox Matrix
m Box
b = IO Box -> m Box
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Box
b' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
b
    Ptr Box
res <- Int -> IO (Ptr Box)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
32 :: IO (Ptr Graphene.Box.Box)
    Ptr Matrix -> Ptr Box -> Ptr Box -> IO ()
graphene_matrix_transform_box Ptr Matrix
m' Ptr Box
b' Ptr Box
res
    Box
res' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Box -> Box
Graphene.Box.Box) Ptr Box
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
b
    Box -> IO Box
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Box
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformBoxMethodInfo
instance (signature ~ (Graphene.Box.Box -> m (Graphene.Box.Box)), MonadIO m) => O.OverloadedMethod MatrixTransformBoxMethodInfo Matrix signature where
    overloadedMethod = matrixTransformBox

instance O.OverloadedMethodInfo MatrixTransformBoxMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformBox",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformBox"
        })


#endif

-- method Matrix::transform_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  transformed #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_point" graphene_matrix_transform_point :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Graphene.Point.Point ->             -- res : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Transforms the given t'GI.Graphene.Structs.Point.Point' using the matrix /@m@/.
-- 
-- Unlike 'GI.Graphene.Structs.Matrix.matrixTransformVec3', this function will take into
-- account the fourth row vector of the t'GI.Graphene.Structs.Matrix.Matrix' when computing
-- the dot product of each row vector of the matrix.
-- 
-- See also: @/graphene_simd4x4f_point3_mul()/@
-- 
-- /Since: 1.0/
matrixTransformPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Point.Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> m (Graphene.Point.Point)
matrixTransformPoint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Point -> m Point
matrixTransformPoint Matrix
m Point
p = IO Point -> m Point
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Point
res <- Int -> IO (Ptr Point)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
8 :: IO (Ptr Graphene.Point.Point)
    Ptr Matrix -> Ptr Point -> Ptr Point -> IO ()
graphene_matrix_transform_point Ptr Matrix
m' Ptr Point
p' Ptr Point
res
    Point
res' <- ((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
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformPointMethodInfo
instance (signature ~ (Graphene.Point.Point -> m (Graphene.Point.Point)), MonadIO m) => O.OverloadedMethod MatrixTransformPointMethodInfo Matrix signature where
    overloadedMethod = matrixTransformPoint

instance O.OverloadedMethodInfo MatrixTransformPointMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformPoint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformPoint"
        })


#endif

-- method Matrix::transform_point3d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point3d_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the result"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_point3d" graphene_matrix_transform_point3d :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point3D.Point3D ->         -- p : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    Ptr Graphene.Point3D.Point3D ->         -- res : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO ()

-- | Transforms the given t'GI.Graphene.Structs.Point3D.Point3D' using the matrix /@m@/.
-- 
-- Unlike 'GI.Graphene.Structs.Matrix.matrixTransformVec3', this function will take into
-- account the fourth row vector of the t'GI.Graphene.Structs.Matrix.Matrix' when computing
-- the dot product of each row vector of the matrix.
-- 
-- See also: @/graphene_simd4x4f_point3_mul()/@
-- 
-- /Since: 1.2/
matrixTransformPoint3d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Point3D.Point3D
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point3D.Point3D'
    -> m (Graphene.Point3D.Point3D)
matrixTransformPoint3d :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Point3D -> m Point3D
matrixTransformPoint3d Matrix
m Point3D
p = IO Point3D -> m Point3D
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point3D -> m Point3D) -> IO Point3D -> m Point3D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Point3D
p' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
p
    Ptr Point3D
res <- Int -> IO (Ptr Point3D)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
12 :: IO (Ptr Graphene.Point3D.Point3D)
    Ptr Matrix -> Ptr Point3D -> Ptr Point3D -> IO ()
graphene_matrix_transform_point3d Ptr Matrix
m' Ptr Point3D
p' Ptr Point3D
res
    Point3D
res' <- ((ManagedPtr Point3D -> Point3D) -> Ptr Point3D -> IO Point3D
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point3D -> Point3D
Graphene.Point3D.Point3D) Ptr Point3D
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
p
    Point3D -> IO Point3D
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point3D
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformPoint3dMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m (Graphene.Point3D.Point3D)), MonadIO m) => O.OverloadedMethod MatrixTransformPoint3dMethodInfo Matrix signature where
    overloadedMethod = matrixTransformPoint3d

instance O.OverloadedMethodInfo MatrixTransformPoint3dMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformPoint3d",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformPoint3d"
        })


#endif

-- method Matrix::transform_ray
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Ray" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_ray_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Ray" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  transformed ray"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_ray" graphene_matrix_transform_ray :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Ray.Ray ->                 -- r : TInterface (Name {namespace = "Graphene", name = "Ray"})
    Ptr Graphene.Ray.Ray ->                 -- res : TInterface (Name {namespace = "Graphene", name = "Ray"})
    IO ()

-- | Transform a t'GI.Graphene.Structs.Ray.Ray' using the given matrix /@m@/.
-- 
-- /Since: 1.4/
matrixTransformRay ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Ray.Ray
    -- ^ /@r@/: a t'GI.Graphene.Structs.Ray.Ray'
    -> m (Graphene.Ray.Ray)
matrixTransformRay :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Ray -> m Ray
matrixTransformRay Matrix
m Ray
r = IO Ray -> m Ray
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Ray -> m Ray) -> IO Ray -> m Ray
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Ray
r' <- Ray -> IO (Ptr Ray)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Ray
r
    Ptr Ray
res <- Int -> IO (Ptr Ray)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
32 :: IO (Ptr Graphene.Ray.Ray)
    Ptr Matrix -> Ptr Ray -> Ptr Ray -> IO ()
graphene_matrix_transform_ray Ptr Matrix
m' Ptr Ray
r' Ptr Ray
res
    Ray
res' <- ((ManagedPtr Ray -> Ray) -> Ptr Ray -> IO Ray
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Ray -> Ray
Graphene.Ray.Ray) Ptr Ray
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Ray -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Ray
r
    Ray -> IO Ray
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ray
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformRayMethodInfo
instance (signature ~ (Graphene.Ray.Ray -> m (Graphene.Ray.Ray)), MonadIO m) => O.OverloadedMethod MatrixTransformRayMethodInfo Matrix signature where
    overloadedMethod = matrixTransformRay

instance O.OverloadedMethodInfo MatrixTransformRayMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformRay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformRay"
        })


#endif

-- method Matrix::transform_rect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , 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 = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quad" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  transformed quad"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_rect" graphene_matrix_transform_rect :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Rect.Rect ->               -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Quad.Quad ->               -- res : TInterface (Name {namespace = "Graphene", name = "Quad"})
    IO ()

-- | Transforms each corner of a t'GI.Graphene.Structs.Rect.Rect' using the given matrix /@m@/.
-- 
-- The result is a coplanar quadrilateral.
-- 
-- See also: 'GI.Graphene.Structs.Matrix.matrixTransformPoint'
-- 
-- /Since: 1.0/
matrixTransformRect ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Rect.Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Quad.Quad)
matrixTransformRect :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Rect -> m Quad
matrixTransformRect Matrix
m Rect
r = IO Quad -> m Quad
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quad -> m Quad) -> IO Quad -> m Quad
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Quad
res <- Int -> IO (Ptr Quad)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
32 :: IO (Ptr Graphene.Quad.Quad)
    Ptr Matrix -> Ptr Rect -> Ptr Quad -> IO ()
graphene_matrix_transform_rect Ptr Matrix
m' Ptr Rect
r' Ptr Quad
res
    Quad
res' <- ((ManagedPtr Quad -> Quad) -> Ptr Quad -> IO Quad
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quad -> Quad
Graphene.Quad.Quad) Ptr Quad
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Quad -> IO Quad
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Quad
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformRectMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m (Graphene.Quad.Quad)), MonadIO m) => O.OverloadedMethod MatrixTransformRectMethodInfo Matrix signature where
    overloadedMethod = matrixTransformRect

instance O.OverloadedMethodInfo MatrixTransformRectMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformRect",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformRect"
        })


#endif

-- method Matrix::transform_sphere
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "s"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Sphere" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_sphere_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Sphere" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the bounds\n  of the transformed sphere"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_sphere" graphene_matrix_transform_sphere :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Sphere.Sphere ->           -- s : TInterface (Name {namespace = "Graphene", name = "Sphere"})
    Ptr Graphene.Sphere.Sphere ->           -- res : TInterface (Name {namespace = "Graphene", name = "Sphere"})
    IO ()

-- | Transforms a t'GI.Graphene.Structs.Sphere.Sphere' using the given matrix /@m@/. The
-- result is the bounding sphere containing the transformed sphere.
-- 
-- /Since: 1.2/
matrixTransformSphere ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Sphere.Sphere
    -- ^ /@s@/: a t'GI.Graphene.Structs.Sphere.Sphere'
    -> m (Graphene.Sphere.Sphere)
matrixTransformSphere :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Sphere -> m Sphere
matrixTransformSphere Matrix
m Sphere
s = IO Sphere -> m Sphere
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Sphere -> m Sphere) -> IO Sphere -> m Sphere
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Sphere
s' <- Sphere -> IO (Ptr Sphere)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Sphere
s
    Ptr Sphere
res <- Int -> IO (Ptr Sphere)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
20 :: IO (Ptr Graphene.Sphere.Sphere)
    Ptr Matrix -> Ptr Sphere -> Ptr Sphere -> IO ()
graphene_matrix_transform_sphere Ptr Matrix
m' Ptr Sphere
s' Ptr Sphere
res
    Sphere
res' <- ((ManagedPtr Sphere -> Sphere) -> Ptr Sphere -> IO Sphere
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Sphere -> Sphere
Graphene.Sphere.Sphere) Ptr Sphere
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Sphere -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Sphere
s
    Sphere -> IO Sphere
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Sphere
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformSphereMethodInfo
instance (signature ~ (Graphene.Sphere.Sphere -> m (Graphene.Sphere.Sphere)), MonadIO m) => O.OverloadedMethod MatrixTransformSphereMethodInfo Matrix signature where
    overloadedMethod = matrixTransformSphere

instance O.OverloadedMethodInfo MatrixTransformSphereMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformSphere",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformSphere"
        })


#endif

-- method Matrix::transform_vec3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_vec3_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_vec3" graphene_matrix_transform_vec3 :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Vec3.Vec3 ->               -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec3.Vec3 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO ()

-- | Transforms the given t'GI.Graphene.Structs.Vec3.Vec3' using the matrix /@m@/.
-- 
-- This function will multiply the X, Y, and Z row vectors of the matrix /@m@/
-- with the corresponding components of the vector /@v@/. The W row vector will
-- be ignored.
-- 
-- See also: @/graphene_simd4x4f_vec3_mul()/@
-- 
-- /Since: 1.0/
matrixTransformVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Vec3.Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Graphene.Vec3.Vec3)
matrixTransformVec3 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Vec3 -> m Vec3
matrixTransformVec3 Matrix
m Vec3
v = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Matrix -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_matrix_transform_vec3 Ptr Matrix
m' Ptr Vec3
v' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Graphene.Vec3.Vec3) Ptr Vec3
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformVec3MethodInfo
instance (signature ~ (Graphene.Vec3.Vec3 -> m (Graphene.Vec3.Vec3)), MonadIO m) => O.OverloadedMethod MatrixTransformVec3MethodInfo Matrix signature where
    overloadedMethod = matrixTransformVec3

instance O.OverloadedMethodInfo MatrixTransformVec3MethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformVec3",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformVec3"
        })


#endif

-- method Matrix::transform_vec4
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec4_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_vec4_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transform_vec4" graphene_matrix_transform_vec4 :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Vec4.Vec4 ->               -- v : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    Ptr Graphene.Vec4.Vec4 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO ()

-- | Transforms the given t'GI.Graphene.Structs.Vec4.Vec4' using the matrix /@m@/.
-- 
-- See also: @/graphene_simd4x4f_vec4_mul()/@
-- 
-- /Since: 1.0/
matrixTransformVec4 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Vec4.Vec4
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec4.Vec4'
    -> m (Graphene.Vec4.Vec4)
matrixTransformVec4 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Vec4 -> m Vec4
matrixTransformVec4 Matrix
m Vec4
v = IO Vec4 -> m Vec4
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec4 -> m Vec4) -> IO Vec4 -> m Vec4
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Vec4
v' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
v
    Ptr Vec4
res <- Int -> IO (Ptr Vec4)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec4.Vec4)
    Ptr Matrix -> Ptr Vec4 -> Ptr Vec4 -> IO ()
graphene_matrix_transform_vec4 Ptr Matrix
m' Ptr Vec4
v' Ptr Vec4
res
    Vec4
res' <- ((ManagedPtr Vec4 -> Vec4) -> Ptr Vec4 -> IO Vec4
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec4 -> Vec4
Graphene.Vec4.Vec4) Ptr Vec4
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
v
    Vec4 -> IO Vec4
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransformVec4MethodInfo
instance (signature ~ (Graphene.Vec4.Vec4 -> m (Graphene.Vec4.Vec4)), MonadIO m) => O.OverloadedMethod MatrixTransformVec4MethodInfo Matrix signature where
    overloadedMethod = matrixTransformVec4

instance O.OverloadedMethodInfo MatrixTransformVec4MethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTransformVec4",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTransformVec4"
        })


#endif

-- method Matrix::translate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point3d_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_translate" graphene_matrix_translate :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point3D.Point3D ->         -- pos : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO ()

-- | Adds a translation transformation to /@m@/ using the coordinates
-- of the given t'GI.Graphene.Structs.Point3D.Point3D'.
-- 
-- This is the equivalent of calling 'GI.Graphene.Structs.Matrix.matrixInitTranslate' and
-- then multiplying /@m@/ with the translation matrix.
-- 
-- /Since: 1.0/
matrixTranslate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Point3D.Point3D
    -- ^ /@pos@/: a t'GI.Graphene.Structs.Point3D.Point3D'
    -> m ()
matrixTranslate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Point3D -> m ()
matrixTranslate Matrix
m Point3D
pos = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Point3D
pos' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
pos
    Ptr Matrix -> Ptr Point3D -> IO ()
graphene_matrix_translate Ptr Matrix
m' Ptr Point3D
pos'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
pos
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MatrixTranslateMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m ()), MonadIO m) => O.OverloadedMethod MatrixTranslateMethodInfo Matrix signature where
    overloadedMethod = matrixTranslate

instance O.OverloadedMethodInfo MatrixTranslateMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTranslate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTranslate"
        })


#endif

-- method Matrix::transpose
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  transposed matrix"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_transpose" graphene_matrix_transpose :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Transposes the given matrix.
-- 
-- /Since: 1.0/
matrixTranspose ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m (Matrix)
matrixTranspose :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> m Matrix
matrixTranspose Matrix
m = IO Matrix -> m Matrix
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Matrix)
    Ptr Matrix -> Ptr Matrix -> IO ()
graphene_matrix_transpose Ptr Matrix
m' Ptr Matrix
res
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Matrix -> IO Matrix
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
res'

#if defined(ENABLE_OVERLOADING)
data MatrixTransposeMethodInfo
instance (signature ~ (m (Matrix)), MonadIO m) => O.OverloadedMethod MatrixTransposeMethodInfo Matrix signature where
    overloadedMethod = matrixTranspose

instance O.OverloadedMethodInfo MatrixTransposeMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixTranspose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixTranspose"
        })


#endif

-- method Matrix::unproject_point3d
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "projection"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #graphene_matrix_t for the projection matrix"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modelview"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #graphene_matrix_t for the modelview matrix; this is\n  the inverse of the modelview used when projecting the point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #graphene_point3d_t with the coordinates of the point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the unprojected\n  point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_unproject_point3d" graphene_matrix_unproject_point3d :: 
    Ptr Matrix ->                           -- projection : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Matrix ->                           -- modelview : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point3D.Point3D ->         -- point : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    Ptr Graphene.Point3D.Point3D ->         -- res : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO ()

-- | Unprojects the given /@point@/ using the /@projection@/ matrix and
-- a /@modelview@/ matrix.
-- 
-- /Since: 1.2/
matrixUnprojectPoint3d ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@projection@/: a t'GI.Graphene.Structs.Matrix.Matrix' for the projection matrix
    -> Matrix
    -- ^ /@modelview@/: a t'GI.Graphene.Structs.Matrix.Matrix' for the modelview matrix; this is
    --   the inverse of the modelview used when projecting the point
    -> Graphene.Point3D.Point3D
    -- ^ /@point@/: a t'GI.Graphene.Structs.Point3D.Point3D' with the coordinates of the point
    -> m (Graphene.Point3D.Point3D)
matrixUnprojectPoint3d :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Matrix -> Point3D -> m Point3D
matrixUnprojectPoint3d Matrix
projection Matrix
modelview Point3D
point = IO Point3D -> m Point3D
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point3D -> m Point3D) -> IO Point3D -> m Point3D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
projection' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
projection
    Ptr Matrix
modelview' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
modelview
    Ptr Point3D
point' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
point
    Ptr Point3D
res <- Int -> IO (Ptr Point3D)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
12 :: IO (Ptr Graphene.Point3D.Point3D)
    Ptr Matrix -> Ptr Matrix -> Ptr Point3D -> Ptr Point3D -> IO ()
graphene_matrix_unproject_point3d Ptr Matrix
projection' Ptr Matrix
modelview' Ptr Point3D
point' Ptr Point3D
res
    Point3D
res' <- ((ManagedPtr Point3D -> Point3D) -> Ptr Point3D -> IO Point3D
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point3D -> Point3D
Graphene.Point3D.Point3D) Ptr Point3D
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
projection
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
modelview
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
point
    Point3D -> IO Point3D
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point3D
res'

#if defined(ENABLE_OVERLOADING)
data MatrixUnprojectPoint3dMethodInfo
instance (signature ~ (Matrix -> Graphene.Point3D.Point3D -> m (Graphene.Point3D.Point3D)), MonadIO m) => O.OverloadedMethod MatrixUnprojectPoint3dMethodInfo Matrix signature where
    overloadedMethod = matrixUnprojectPoint3d

instance O.OverloadedMethodInfo MatrixUnprojectPoint3dMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixUnprojectPoint3d",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixUnprojectPoint3d"
        })


#endif

-- method Matrix::untransform_bounds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , 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 = "bounds"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the bounds of the transformation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  untransformed rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_untransform_bounds" graphene_matrix_untransform_bounds :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Rect.Rect ->               -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Rect.Rect ->               -- bounds : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Rect.Rect ->               -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Undoes the transformation on the corners of a t'GI.Graphene.Structs.Rect.Rect' using the
-- given matrix, within the given axis aligned rectangular /@bounds@/.
-- 
-- /Since: 1.0/
matrixUntransformBounds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Rect.Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Graphene.Rect.Rect
    -- ^ /@bounds@/: the bounds of the transformation
    -> m (Graphene.Rect.Rect)
matrixUntransformBounds :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Rect -> Rect -> m Rect
matrixUntransformBounds Matrix
m Rect
r Rect
bounds = IO Rect -> m Rect
forall a. IO a -> m a
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 Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Rect.Rect)
    Ptr Matrix -> Ptr Rect -> Ptr Rect -> Ptr Rect -> IO ()
graphene_matrix_untransform_bounds Ptr Matrix
m' Ptr Rect
r' Ptr Rect
bounds' Ptr Rect
res
    Rect
res' <- ((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
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
    Rect -> IO Rect
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data MatrixUntransformBoundsMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Graphene.Rect.Rect -> m (Graphene.Rect.Rect)), MonadIO m) => O.OverloadedMethod MatrixUntransformBoundsMethodInfo Matrix signature where
    overloadedMethod = matrixUntransformBounds

instance O.OverloadedMethodInfo MatrixUntransformBoundsMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixUntransformBounds",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixUntransformBounds"
        })


#endif

-- method Matrix::untransform_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , 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 = "bounds"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the bounds of the transformation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  untransformed point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_matrix_untransform_point" graphene_matrix_untransform_point :: 
    Ptr Matrix ->                           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Graphene.Rect.Rect ->               -- bounds : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- res : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO CInt

-- | Undoes the transformation of a t'GI.Graphene.Structs.Point.Point' using the
-- given matrix, within the given axis aligned rectangular /@bounds@/.
-- 
-- /Since: 1.0/
matrixUntransformPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> Graphene.Point.Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> Graphene.Rect.Rect
    -- ^ /@bounds@/: the bounds of the transformation
    -> m ((Bool, Graphene.Point.Point))
    -- ^ __Returns:__ @true@ if the point was successfully untransformed
matrixUntransformPoint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Matrix -> Point -> Rect -> m (Bool, Point)
matrixUntransformPoint Matrix
m Point
p Rect
bounds = IO (Bool, Point) -> m (Bool, Point)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Point) -> m (Bool, Point))
-> IO (Bool, Point) -> m (Bool, Point)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
    Ptr Point
res <- Int -> IO (Ptr Point)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
8 :: IO (Ptr Graphene.Point.Point)
    CInt
result <- Ptr Matrix -> Ptr Point -> Ptr Rect -> Ptr Point -> IO CInt
graphene_matrix_untransform_point Ptr Matrix
m' Ptr Point
p' Ptr Rect
bounds' Ptr Point
res
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Point
res' <- ((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
res
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
    (Bool, Point) -> IO (Bool, Point)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Point
res')

#if defined(ENABLE_OVERLOADING)
data MatrixUntransformPointMethodInfo
instance (signature ~ (Graphene.Point.Point -> Graphene.Rect.Rect -> m ((Bool, Graphene.Point.Point))), MonadIO m) => O.OverloadedMethod MatrixUntransformPointMethodInfo Matrix signature where
    overloadedMethod = matrixUntransformPoint

instance O.OverloadedMethodInfo MatrixUntransformPointMethodInfo Matrix where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Matrix.matrixUntransformPoint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Matrix.html#v:matrixUntransformPoint"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveMatrixMethod (t :: Symbol) (o :: *) :: * where
    ResolveMatrixMethod "decompose" o = MatrixDecomposeMethodInfo
    ResolveMatrixMethod "determinant" o = MatrixDeterminantMethodInfo
    ResolveMatrixMethod "equal" o = MatrixEqualMethodInfo
    ResolveMatrixMethod "equalFast" o = MatrixEqualFastMethodInfo
    ResolveMatrixMethod "free" o = MatrixFreeMethodInfo
    ResolveMatrixMethod "initFrom2d" o = MatrixInitFrom2dMethodInfo
    ResolveMatrixMethod "initFromFloat" o = MatrixInitFromFloatMethodInfo
    ResolveMatrixMethod "initFromMatrix" o = MatrixInitFromMatrixMethodInfo
    ResolveMatrixMethod "initFromVec4" o = MatrixInitFromVec4MethodInfo
    ResolveMatrixMethod "initFrustum" o = MatrixInitFrustumMethodInfo
    ResolveMatrixMethod "initIdentity" o = MatrixInitIdentityMethodInfo
    ResolveMatrixMethod "initLookAt" o = MatrixInitLookAtMethodInfo
    ResolveMatrixMethod "initOrtho" o = MatrixInitOrthoMethodInfo
    ResolveMatrixMethod "initPerspective" o = MatrixInitPerspectiveMethodInfo
    ResolveMatrixMethod "initRotate" o = MatrixInitRotateMethodInfo
    ResolveMatrixMethod "initScale" o = MatrixInitScaleMethodInfo
    ResolveMatrixMethod "initSkew" o = MatrixInitSkewMethodInfo
    ResolveMatrixMethod "initTranslate" o = MatrixInitTranslateMethodInfo
    ResolveMatrixMethod "interpolate" o = MatrixInterpolateMethodInfo
    ResolveMatrixMethod "inverse" o = MatrixInverseMethodInfo
    ResolveMatrixMethod "is2d" o = MatrixIs2dMethodInfo
    ResolveMatrixMethod "isBackfaceVisible" o = MatrixIsBackfaceVisibleMethodInfo
    ResolveMatrixMethod "isIdentity" o = MatrixIsIdentityMethodInfo
    ResolveMatrixMethod "isSingular" o = MatrixIsSingularMethodInfo
    ResolveMatrixMethod "multiply" o = MatrixMultiplyMethodInfo
    ResolveMatrixMethod "near" o = MatrixNearMethodInfo
    ResolveMatrixMethod "normalize" o = MatrixNormalizeMethodInfo
    ResolveMatrixMethod "perspective" o = MatrixPerspectiveMethodInfo
    ResolveMatrixMethod "print" o = MatrixPrintMethodInfo
    ResolveMatrixMethod "projectPoint" o = MatrixProjectPointMethodInfo
    ResolveMatrixMethod "projectRect" o = MatrixProjectRectMethodInfo
    ResolveMatrixMethod "projectRectBounds" o = MatrixProjectRectBoundsMethodInfo
    ResolveMatrixMethod "rotate" o = MatrixRotateMethodInfo
    ResolveMatrixMethod "rotateEuler" o = MatrixRotateEulerMethodInfo
    ResolveMatrixMethod "rotateQuaternion" o = MatrixRotateQuaternionMethodInfo
    ResolveMatrixMethod "rotateX" o = MatrixRotateXMethodInfo
    ResolveMatrixMethod "rotateY" o = MatrixRotateYMethodInfo
    ResolveMatrixMethod "rotateZ" o = MatrixRotateZMethodInfo
    ResolveMatrixMethod "scale" o = MatrixScaleMethodInfo
    ResolveMatrixMethod "skewXy" o = MatrixSkewXyMethodInfo
    ResolveMatrixMethod "skewXz" o = MatrixSkewXzMethodInfo
    ResolveMatrixMethod "skewYz" o = MatrixSkewYzMethodInfo
    ResolveMatrixMethod "to2d" o = MatrixTo2dMethodInfo
    ResolveMatrixMethod "transformBounds" o = MatrixTransformBoundsMethodInfo
    ResolveMatrixMethod "transformBox" o = MatrixTransformBoxMethodInfo
    ResolveMatrixMethod "transformPoint" o = MatrixTransformPointMethodInfo
    ResolveMatrixMethod "transformPoint3d" o = MatrixTransformPoint3dMethodInfo
    ResolveMatrixMethod "transformRay" o = MatrixTransformRayMethodInfo
    ResolveMatrixMethod "transformRect" o = MatrixTransformRectMethodInfo
    ResolveMatrixMethod "transformSphere" o = MatrixTransformSphereMethodInfo
    ResolveMatrixMethod "transformVec3" o = MatrixTransformVec3MethodInfo
    ResolveMatrixMethod "transformVec4" o = MatrixTransformVec4MethodInfo
    ResolveMatrixMethod "translate" o = MatrixTranslateMethodInfo
    ResolveMatrixMethod "transpose" o = MatrixTransposeMethodInfo
    ResolveMatrixMethod "unprojectPoint3d" o = MatrixUnprojectPoint3dMethodInfo
    ResolveMatrixMethod "untransformBounds" o = MatrixUntransformBoundsMethodInfo
    ResolveMatrixMethod "untransformPoint" o = MatrixUntransformPointMethodInfo
    ResolveMatrixMethod "getRow" o = MatrixGetRowMethodInfo
    ResolveMatrixMethod "getValue" o = MatrixGetValueMethodInfo
    ResolveMatrixMethod "getXScale" o = MatrixGetXScaleMethodInfo
    ResolveMatrixMethod "getXTranslation" o = MatrixGetXTranslationMethodInfo
    ResolveMatrixMethod "getYScale" o = MatrixGetYScaleMethodInfo
    ResolveMatrixMethod "getYTranslation" o = MatrixGetYTranslationMethodInfo
    ResolveMatrixMethod "getZScale" o = MatrixGetZScaleMethodInfo
    ResolveMatrixMethod "getZTranslation" o = MatrixGetZTranslationMethodInfo
    ResolveMatrixMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveMatrixMethod t Matrix, O.OverloadedMethod info Matrix p, R.HasField t Matrix p) => R.HasField t Matrix p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveMatrixMethod t Matrix, O.OverloadedMethodInfo info Matrix) => OL.IsLabel t (O.MethodProxy info Matrix) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif