{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A quaternion.
-- 
-- The contents of the t'GI.Graphene.Structs.Quaternion.Quaternion' structure are private
-- and should never be accessed directly.
-- 
-- /Since: 1.0/

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

module GI.Graphene.Structs.Quaternion
    ( 

-- * Exported types
    Quaternion(..)                          ,
    newZeroQuaternion                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [add]("GI.Graphene.Structs.Quaternion#g:method:add"), [dot]("GI.Graphene.Structs.Quaternion#g:method:dot"), [equal]("GI.Graphene.Structs.Quaternion#g:method:equal"), [free]("GI.Graphene.Structs.Quaternion#g:method:free"), [init]("GI.Graphene.Structs.Quaternion#g:method:init"), [initFromAngleVec3]("GI.Graphene.Structs.Quaternion#g:method:initFromAngleVec3"), [initFromAngles]("GI.Graphene.Structs.Quaternion#g:method:initFromAngles"), [initFromEuler]("GI.Graphene.Structs.Quaternion#g:method:initFromEuler"), [initFromMatrix]("GI.Graphene.Structs.Quaternion#g:method:initFromMatrix"), [initFromQuaternion]("GI.Graphene.Structs.Quaternion#g:method:initFromQuaternion"), [initFromRadians]("GI.Graphene.Structs.Quaternion#g:method:initFromRadians"), [initFromVec4]("GI.Graphene.Structs.Quaternion#g:method:initFromVec4"), [initIdentity]("GI.Graphene.Structs.Quaternion#g:method:initIdentity"), [invert]("GI.Graphene.Structs.Quaternion#g:method:invert"), [multiply]("GI.Graphene.Structs.Quaternion#g:method:multiply"), [normalize]("GI.Graphene.Structs.Quaternion#g:method:normalize"), [scale]("GI.Graphene.Structs.Quaternion#g:method:scale"), [slerp]("GI.Graphene.Structs.Quaternion#g:method:slerp"), [toAngleVec3]("GI.Graphene.Structs.Quaternion#g:method:toAngleVec3"), [toAngles]("GI.Graphene.Structs.Quaternion#g:method:toAngles"), [toMatrix]("GI.Graphene.Structs.Quaternion#g:method:toMatrix"), [toRadians]("GI.Graphene.Structs.Quaternion#g:method:toRadians"), [toVec4]("GI.Graphene.Structs.Quaternion#g:method:toVec4").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveQuaternionMethod                 ,
#endif

-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    QuaternionAddMethodInfo                 ,
#endif
    quaternionAdd                           ,


-- ** alloc #method:alloc#

    quaternionAlloc                         ,


-- ** dot #method:dot#

#if defined(ENABLE_OVERLOADING)
    QuaternionDotMethodInfo                 ,
#endif
    quaternionDot                           ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    QuaternionEqualMethodInfo               ,
#endif
    quaternionEqual                         ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    QuaternionFreeMethodInfo                ,
#endif
    quaternionFree                          ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitMethodInfo                ,
#endif
    quaternionInit                          ,


-- ** initFromAngleVec3 #method:initFromAngleVec3#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromAngleVec3MethodInfo   ,
#endif
    quaternionInitFromAngleVec3             ,


-- ** initFromAngles #method:initFromAngles#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromAnglesMethodInfo      ,
#endif
    quaternionInitFromAngles                ,


-- ** initFromEuler #method:initFromEuler#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromEulerMethodInfo       ,
#endif
    quaternionInitFromEuler                 ,


-- ** initFromMatrix #method:initFromMatrix#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromMatrixMethodInfo      ,
#endif
    quaternionInitFromMatrix                ,


-- ** initFromQuaternion #method:initFromQuaternion#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromQuaternionMethodInfo  ,
#endif
    quaternionInitFromQuaternion            ,


-- ** initFromRadians #method:initFromRadians#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromRadiansMethodInfo     ,
#endif
    quaternionInitFromRadians               ,


-- ** initFromVec4 #method:initFromVec4#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitFromVec4MethodInfo        ,
#endif
    quaternionInitFromVec4                  ,


-- ** initIdentity #method:initIdentity#

#if defined(ENABLE_OVERLOADING)
    QuaternionInitIdentityMethodInfo        ,
#endif
    quaternionInitIdentity                  ,


-- ** invert #method:invert#

#if defined(ENABLE_OVERLOADING)
    QuaternionInvertMethodInfo              ,
#endif
    quaternionInvert                        ,


-- ** multiply #method:multiply#

#if defined(ENABLE_OVERLOADING)
    QuaternionMultiplyMethodInfo            ,
#endif
    quaternionMultiply                      ,


-- ** normalize #method:normalize#

#if defined(ENABLE_OVERLOADING)
    QuaternionNormalizeMethodInfo           ,
#endif
    quaternionNormalize                     ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    QuaternionScaleMethodInfo               ,
#endif
    quaternionScale                         ,


-- ** slerp #method:slerp#

#if defined(ENABLE_OVERLOADING)
    QuaternionSlerpMethodInfo               ,
#endif
    quaternionSlerp                         ,


-- ** toAngleVec3 #method:toAngleVec3#

#if defined(ENABLE_OVERLOADING)
    QuaternionToAngleVec3MethodInfo         ,
#endif
    quaternionToAngleVec3                   ,


-- ** toAngles #method:toAngles#

#if defined(ENABLE_OVERLOADING)
    QuaternionToAnglesMethodInfo            ,
#endif
    quaternionToAngles                      ,


-- ** toMatrix #method:toMatrix#

#if defined(ENABLE_OVERLOADING)
    QuaternionToMatrixMethodInfo            ,
#endif
    quaternionToMatrix                      ,


-- ** toRadians #method:toRadians#

#if defined(ENABLE_OVERLOADING)
    QuaternionToRadiansMethodInfo           ,
#endif
    quaternionToRadians                     ,


-- ** toVec4 #method:toVec4#

#if defined(ENABLE_OVERLOADING)
    QuaternionToVec4MethodInfo              ,
#endif
    quaternionToVec4                        ,




    ) 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.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.Euler as Graphene.Euler
import {-# SOURCE #-} qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
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 Quaternion = Quaternion (SP.ManagedPtr Quaternion)
    deriving (Quaternion -> Quaternion -> Bool
(Quaternion -> Quaternion -> Bool)
-> (Quaternion -> Quaternion -> Bool) -> Eq Quaternion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Quaternion -> Quaternion -> Bool
$c/= :: Quaternion -> Quaternion -> Bool
== :: Quaternion -> Quaternion -> Bool
$c== :: Quaternion -> Quaternion -> Bool
Eq)

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

foreign import ccall "graphene_quaternion_get_type" c_graphene_quaternion_get_type :: 
    IO GType

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

instance B.Types.TypedObject Quaternion where
    glibType :: IO GType
glibType = IO GType
c_graphene_quaternion_get_type

instance B.Types.GBoxed Quaternion

-- | Convert 'Quaternion' 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 Quaternion) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_graphene_quaternion_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Quaternion -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Quaternion
P.Nothing = Ptr GValue -> Ptr Quaternion -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Quaternion
forall a. Ptr a
FP.nullPtr :: FP.Ptr Quaternion)
    gvalueSet_ Ptr GValue
gv (P.Just Quaternion
obj) = Quaternion -> (Ptr Quaternion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Quaternion
obj (Ptr GValue -> Ptr Quaternion -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Quaternion)
gvalueGet_ Ptr GValue
gv = do
        Ptr Quaternion
ptr <- Ptr GValue -> IO (Ptr Quaternion)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Quaternion)
        if Ptr Quaternion
ptr Ptr Quaternion -> Ptr Quaternion -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Quaternion
forall a. Ptr a
FP.nullPtr
        then Quaternion -> Maybe Quaternion
forall a. a -> Maybe a
P.Just (Quaternion -> Maybe Quaternion)
-> IO Quaternion -> IO (Maybe Quaternion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion Ptr Quaternion
ptr
        else Maybe Quaternion -> IO (Maybe Quaternion)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Quaternion
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `Quaternion` struct initialized to zero.
newZeroQuaternion :: MonadIO m => m Quaternion
newZeroQuaternion :: forall (m :: * -> *). MonadIO m => m Quaternion
newZeroQuaternion = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
16 IO (Ptr Quaternion)
-> (Ptr Quaternion -> IO Quaternion) -> IO Quaternion
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion

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



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

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

foreign import ccall "graphene_quaternion_alloc" graphene_quaternion_alloc :: 
    IO (Ptr Quaternion)

-- | Allocates a new t'GI.Graphene.Structs.Quaternion.Quaternion'.
-- 
-- The contents of the returned value are undefined.
-- 
-- /Since: 1.0/
quaternionAlloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Quaternion
    -- ^ __Returns:__ the newly allocated t'GI.Graphene.Structs.Quaternion.Quaternion'
quaternionAlloc :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Quaternion
quaternionAlloc  = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
result <- IO (Ptr Quaternion)
graphene_quaternion_alloc
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionAlloc" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Adds two t'GI.Graphene.Structs.Quaternion.Quaternion' /@a@/ and /@b@/.
-- 
-- /Since: 1.10/
quaternionAdd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@a@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Quaternion
    -- ^ /@b@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m (Quaternion)
quaternionAdd :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Quaternion -> m Quaternion
quaternionAdd Quaternion
a Quaternion
b = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
a' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
a
    Ptr Quaternion
b' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
b
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Quaternion)
    Ptr Quaternion -> Ptr Quaternion -> Ptr Quaternion -> IO ()
graphene_quaternion_add Ptr Quaternion
a' Ptr Quaternion
b' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
res
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
a
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
b
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionAddMethodInfo
instance (signature ~ (Quaternion -> m (Quaternion)), MonadIO m) => O.OverloadedMethod QuaternionAddMethodInfo Quaternion signature where
    overloadedMethod = quaternionAdd

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


#endif

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

-- | Computes the dot product of two t'GI.Graphene.Structs.Quaternion.Quaternion'.
-- 
-- /Since: 1.0/
quaternionDot ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@a@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Quaternion
    -- ^ /@b@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m Float
    -- ^ __Returns:__ the value of the dot products
quaternionDot :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Quaternion -> m Float
quaternionDot Quaternion
a Quaternion
b = IO Float -> m Float
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 Quaternion
a' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
a
    Ptr Quaternion
b' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
b
    CFloat
result <- Ptr Quaternion -> Ptr Quaternion -> IO CFloat
graphene_quaternion_dot Ptr Quaternion
a' Ptr Quaternion
b'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
a
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
b
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionDotMethodInfo
instance (signature ~ (Quaternion -> m Float), MonadIO m) => O.OverloadedMethod QuaternionDotMethodInfo Quaternion signature where
    overloadedMethod = quaternionDot

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


#endif

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

-- | Checks whether the given quaternions are equal.
-- 
-- /Since: 1.0/
quaternionEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@a@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Quaternion
    -- ^ /@b@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m Bool
    -- ^ __Returns:__ @true@ if the quaternions are equal
quaternionEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Quaternion -> m Bool
quaternionEqual Quaternion
a Quaternion
b = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
a' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
a
    Ptr Quaternion
b' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
b
    CInt
result <- Ptr Quaternion -> Ptr Quaternion -> IO CInt
graphene_quaternion_equal Ptr Quaternion
a' Ptr Quaternion
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
a
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
b
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionEqualMethodInfo
instance (signature ~ (Quaternion -> m Bool), MonadIO m) => O.OverloadedMethod QuaternionEqualMethodInfo Quaternion signature where
    overloadedMethod = quaternionEqual

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


#endif

-- method Quaternion::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "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_quaternion_free" graphene_quaternion_free :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Releases the resources allocated by 'GI.Graphene.Structs.Quaternion.quaternionAlloc'.
-- 
-- /Since: 1.0/
quaternionFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m ()
quaternionFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m ()
quaternionFree Quaternion
q = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Quaternion -> IO ()
graphene_quaternion_free Ptr Quaternion
q'
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data QuaternionFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod QuaternionFreeMethodInfo Quaternion signature where
    overloadedMethod = quaternionFree

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


#endif

-- method Quaternion::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_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 first component of the quaternion"
--                 , 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 second component of the quaternion"
--                 , 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 third component of the quaternion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "w"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the fourth component of the quaternion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Quaternion" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_init" graphene_quaternion_init :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    CFloat ->                               -- x : TBasicType TFloat
    CFloat ->                               -- y : TBasicType TFloat
    CFloat ->                               -- z : TBasicType TFloat
    CFloat ->                               -- w : TBasicType TFloat
    IO (Ptr Quaternion)

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using the given four values.
-- 
-- /Since: 1.0/
quaternionInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Float
    -- ^ /@x@/: the first component of the quaternion
    -> Float
    -- ^ /@y@/: the second component of the quaternion
    -> Float
    -- ^ /@z@/: the third component of the quaternion
    -> Float
    -- ^ /@w@/: the fourth component of the quaternion
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Float -> Float -> Float -> Float -> m Quaternion
quaternionInit Quaternion
q Float
x Float
y Float
z Float
w = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    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
    let w' :: CFloat
w' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
w
    Ptr Quaternion
result <- Ptr Quaternion
-> CFloat -> CFloat -> CFloat -> CFloat -> IO (Ptr Quaternion)
graphene_quaternion_init Ptr Quaternion
q' CFloat
x' CFloat
y' CFloat
z' CFloat
w'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInit" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitMethodInfo
instance (signature ~ (Float -> Float -> Float -> Float -> m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitMethodInfo Quaternion signature where
    overloadedMethod = quaternionInit

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


#endif

-- method Quaternion::init_from_angle_vec3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_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 on a given axis, 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 of rotation, expressed as a vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Quaternion" })
-- throws : False
-- Skip return : False

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

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using an /@angle@/ on a
-- specific /@axis@/.
-- 
-- /Since: 1.0/
quaternionInitFromAngleVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Float
    -- ^ /@angle@/: the rotation on a given axis, in degrees
    -> Graphene.Vec3.Vec3
    -- ^ /@axis@/: the axis of rotation, expressed as a vector
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitFromAngleVec3 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Float -> Vec3 -> m Quaternion
quaternionInitFromAngleVec3 Quaternion
q Float
angle Vec3
axis = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    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 Quaternion
result <- Ptr Quaternion -> CFloat -> Ptr Vec3 -> IO (Ptr Quaternion)
graphene_quaternion_init_from_angle_vec3 Ptr Quaternion
q' CFloat
angle' Ptr Vec3
axis'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromAngleVec3" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
axis
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

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

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


#endif

-- method Quaternion::init_from_angles
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "deg_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rotation angle on the X axis (yaw), in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "deg_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rotation angle on the Y axis (pitch), in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "deg_z"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rotation angle on the Z axis (roll), in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Quaternion" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_init_from_angles" graphene_quaternion_init_from_angles :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    CFloat ->                               -- deg_x : TBasicType TFloat
    CFloat ->                               -- deg_y : TBasicType TFloat
    CFloat ->                               -- deg_z : TBasicType TFloat
    IO (Ptr Quaternion)

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using the values of
-- the <http://en.wikipedia.org/wiki/Euler_angles Euler angles>
-- on each axis.
-- 
-- See also: 'GI.Graphene.Structs.Quaternion.quaternionInitFromEuler'
-- 
-- /Since: 1.0/
quaternionInitFromAngles ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Float
    -- ^ /@degX@/: rotation angle on the X axis (yaw), in degrees
    -> Float
    -- ^ /@degY@/: rotation angle on the Y axis (pitch), in degrees
    -> Float
    -- ^ /@degZ@/: rotation angle on the Z axis (roll), in degrees
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitFromAngles :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Float -> Float -> Float -> m Quaternion
quaternionInitFromAngles Quaternion
q Float
degX Float
degY Float
degZ = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    let degX' :: CFloat
degX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
degX
    let degY' :: CFloat
degY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
degY
    let degZ' :: CFloat
degZ' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
degZ
    Ptr Quaternion
result <- Ptr Quaternion -> CFloat -> CFloat -> CFloat -> IO (Ptr Quaternion)
graphene_quaternion_init_from_angles Ptr Quaternion
q' CFloat
degX' CFloat
degY' CFloat
degZ'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromAngles" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitFromAnglesMethodInfo
instance (signature ~ (Float -> Float -> Float -> m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitFromAnglesMethodInfo Quaternion signature where
    overloadedMethod = quaternionInitFromAngles

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


#endif

-- method Quaternion::init_from_euler
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_quaternion_t to initialize"
--                 , 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 #graphene_euler_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Quaternion" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_init_from_euler" graphene_quaternion_init_from_euler :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Graphene.Euler.Euler ->             -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO (Ptr Quaternion)

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using the given t'GI.Graphene.Structs.Euler.Euler'.
-- 
-- /Since: 1.2/
quaternionInitFromEuler ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: the t'GI.Graphene.Structs.Quaternion.Quaternion' to initialize
    -> Graphene.Euler.Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Quaternion
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Quaternion.Quaternion'
quaternionInitFromEuler :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Euler -> m Quaternion
quaternionInitFromEuler Quaternion
q Euler
e = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Quaternion
result <- Ptr Quaternion -> Ptr Euler -> IO (Ptr Quaternion)
graphene_quaternion_init_from_euler Ptr Quaternion
q' Ptr Euler
e'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromEuler" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitFromEulerMethodInfo
instance (signature ~ (Graphene.Euler.Euler -> m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitFromEulerMethodInfo Quaternion signature where
    overloadedMethod = quaternionInitFromEuler

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


#endif

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

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

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using the rotation components
-- of a transformation matrix.
-- 
-- /Since: 1.0/
quaternionInitFromMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Graphene.Matrix.Matrix
    -- ^ /@m@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitFromMatrix :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Matrix -> m Quaternion
quaternionInitFromMatrix Quaternion
q Matrix
m = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Matrix
m' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
m
    Ptr Quaternion
result <- Ptr Quaternion -> Ptr Matrix -> IO (Ptr Quaternion)
graphene_quaternion_init_from_matrix Ptr Quaternion
q' Ptr Matrix
m'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromMatrix" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
m
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

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

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


#endif

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

foreign import ccall "graphene_quaternion_init_from_quaternion" graphene_quaternion_init_from_quaternion :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Quaternion ->                       -- src : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO (Ptr Quaternion)

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' with the values from /@src@/.
-- 
-- /Since: 1.0/
quaternionInitFromQuaternion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Quaternion
    -- ^ /@src@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitFromQuaternion :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Quaternion -> m Quaternion
quaternionInitFromQuaternion Quaternion
q Quaternion
src = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Quaternion
src' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
src
    Ptr Quaternion
result <- Ptr Quaternion -> Ptr Quaternion -> IO (Ptr Quaternion)
graphene_quaternion_init_from_quaternion Ptr Quaternion
q' Ptr Quaternion
src'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromQuaternion" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
src
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitFromQuaternionMethodInfo
instance (signature ~ (Quaternion -> m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitFromQuaternionMethodInfo Quaternion signature where
    overloadedMethod = quaternionInitFromQuaternion

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


#endif

-- method Quaternion::init_from_radians
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rad_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rotation angle on the X axis (yaw), in radians"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rad_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rotation angle on the Y axis (pitch), in radians"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rad_z"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rotation angle on the Z axis (roll), in radians"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Quaternion" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_init_from_radians" graphene_quaternion_init_from_radians :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    CFloat ->                               -- rad_x : TBasicType TFloat
    CFloat ->                               -- rad_y : TBasicType TFloat
    CFloat ->                               -- rad_z : TBasicType TFloat
    IO (Ptr Quaternion)

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using the values of
-- the <http://en.wikipedia.org/wiki/Euler_angles Euler angles>
-- on each axis.
-- 
-- See also: 'GI.Graphene.Structs.Quaternion.quaternionInitFromEuler'
-- 
-- /Since: 1.0/
quaternionInitFromRadians ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Float
    -- ^ /@radX@/: rotation angle on the X axis (yaw), in radians
    -> Float
    -- ^ /@radY@/: rotation angle on the Y axis (pitch), in radians
    -> Float
    -- ^ /@radZ@/: rotation angle on the Z axis (roll), in radians
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitFromRadians :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Float -> Float -> Float -> m Quaternion
quaternionInitFromRadians Quaternion
q Float
radX Float
radY Float
radZ = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    let radX' :: CFloat
radX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
radX
    let radY' :: CFloat
radY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
radY
    let radZ' :: CFloat
radZ' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
radZ
    Ptr Quaternion
result <- Ptr Quaternion -> CFloat -> CFloat -> CFloat -> IO (Ptr Quaternion)
graphene_quaternion_init_from_radians Ptr Quaternion
q' CFloat
radX' CFloat
radY' CFloat
radZ'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromRadians" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitFromRadiansMethodInfo
instance (signature ~ (Float -> Float -> Float -> m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitFromRadiansMethodInfo Quaternion signature where
    overloadedMethod = quaternionInitFromRadians

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


#endif

-- method Quaternion::init_from_vec4
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Quaternion" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_init_from_vec4" graphene_quaternion_init_from_vec4 :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Graphene.Vec4.Vec4 ->               -- src : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO (Ptr Quaternion)

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' with the values from /@src@/.
-- 
-- /Since: 1.0/
quaternionInitFromVec4 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Graphene.Vec4.Vec4
    -- ^ /@src@/: a t'GI.Graphene.Structs.Vec4.Vec4'
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitFromVec4 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Vec4 -> m Quaternion
quaternionInitFromVec4 Quaternion
q Vec4
src = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Vec4
src' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
src
    Ptr Quaternion
result <- Ptr Quaternion -> Ptr Vec4 -> IO (Ptr Quaternion)
graphene_quaternion_init_from_vec4 Ptr Quaternion
q' Ptr Vec4
src'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitFromVec4" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
src
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitFromVec4MethodInfo
instance (signature ~ (Graphene.Vec4.Vec4 -> m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitFromVec4MethodInfo Quaternion signature where
    overloadedMethod = quaternionInitFromVec4

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


#endif

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

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

-- | Initializes a t'GI.Graphene.Structs.Quaternion.Quaternion' using the identity
-- transformation.
-- 
-- /Since: 1.0/
quaternionInitIdentity ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m Quaternion
    -- ^ __Returns:__ the initialized quaternion
quaternionInitIdentity :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m Quaternion
quaternionInitIdentity Quaternion
q = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Quaternion
result <- Ptr Quaternion -> IO (Ptr Quaternion)
graphene_quaternion_init_identity Ptr Quaternion
q'
    Text -> Ptr Quaternion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"quaternionInitIdentity" Ptr Quaternion
result
    Quaternion
result' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
result
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
result'

#if defined(ENABLE_OVERLOADING)
data QuaternionInitIdentityMethodInfo
instance (signature ~ (m Quaternion), MonadIO m) => O.OverloadedMethod QuaternionInitIdentityMethodInfo Quaternion signature where
    overloadedMethod = quaternionInitIdentity

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


#endif

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

foreign import ccall "graphene_quaternion_invert" graphene_quaternion_invert :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Quaternion ->                       -- res : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Inverts a t'GI.Graphene.Structs.Quaternion.Quaternion', and returns the conjugate
-- quaternion of /@q@/.
-- 
-- /Since: 1.0/
quaternionInvert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m (Quaternion)
quaternionInvert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m Quaternion
quaternionInvert Quaternion
q = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Quaternion)
    Ptr Quaternion -> Ptr Quaternion -> IO ()
graphene_quaternion_invert Ptr Quaternion
q' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
res
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionInvertMethodInfo
instance (signature ~ (m (Quaternion)), MonadIO m) => O.OverloadedMethod QuaternionInvertMethodInfo Quaternion signature where
    overloadedMethod = quaternionInvert

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


#endif

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

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

-- | Multiplies two t'GI.Graphene.Structs.Quaternion.Quaternion' /@a@/ and /@b@/.
-- 
-- /Since: 1.10/
quaternionMultiply ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@a@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Quaternion
    -- ^ /@b@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m (Quaternion)
quaternionMultiply :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Quaternion -> m Quaternion
quaternionMultiply Quaternion
a Quaternion
b = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
a' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
a
    Ptr Quaternion
b' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
b
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Quaternion)
    Ptr Quaternion -> Ptr Quaternion -> Ptr Quaternion -> IO ()
graphene_quaternion_multiply Ptr Quaternion
a' Ptr Quaternion
b' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
res
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
a
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
b
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionMultiplyMethodInfo
instance (signature ~ (Quaternion -> m (Quaternion)), MonadIO m) => O.OverloadedMethod QuaternionMultiplyMethodInfo Quaternion signature where
    overloadedMethod = quaternionMultiply

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


#endif

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

foreign import ccall "graphene_quaternion_normalize" graphene_quaternion_normalize :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Quaternion ->                       -- res : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Normalizes a t'GI.Graphene.Structs.Quaternion.Quaternion'.
-- 
-- /Since: 1.0/
quaternionNormalize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m (Quaternion)
quaternionNormalize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m Quaternion
quaternionNormalize Quaternion
q = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Quaternion)
    Ptr Quaternion -> Ptr Quaternion -> IO ()
graphene_quaternion_normalize Ptr Quaternion
q' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
res
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionNormalizeMethodInfo
instance (signature ~ (m (Quaternion)), MonadIO m) => O.OverloadedMethod QuaternionNormalizeMethodInfo Quaternion signature where
    overloadedMethod = quaternionNormalize

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


#endif

-- method Quaternion::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_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 "a scaling factor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the result of the operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_scale" graphene_quaternion_scale :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    CFloat ->                               -- factor : TBasicType TFloat
    Ptr Quaternion ->                       -- res : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Scales all the elements of a t'GI.Graphene.Structs.Quaternion.Quaternion' /@q@/ using
-- the given scalar factor.
-- 
-- /Since: 1.10/
quaternionScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Float
    -- ^ /@factor@/: a scaling factor
    -> m (Quaternion)
quaternionScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Float -> m Quaternion
quaternionScale Quaternion
q Float
factor = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Quaternion)
    Ptr Quaternion -> CFloat -> Ptr Quaternion -> IO ()
graphene_quaternion_scale Ptr Quaternion
q' CFloat
factor' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
res
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionScaleMethodInfo
instance (signature ~ (Float -> m (Quaternion)), MonadIO m) => O.OverloadedMethod QuaternionScaleMethodInfo Quaternion signature where
    overloadedMethod = quaternionScale

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


#endif

-- method Quaternion::slerp
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_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 "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 = "Quaternion" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the interpolated\n  quaternion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_slerp" graphene_quaternion_slerp :: 
    Ptr Quaternion ->                       -- a : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Quaternion ->                       -- b : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    CFloat ->                               -- factor : TBasicType TFloat
    Ptr Quaternion ->                       -- res : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Interpolates between the two given quaternions using a spherical
-- linear interpolation, or <http://en.wikipedia.org/wiki/Slerp SLERP>,
-- using the given interpolation /@factor@/.
-- 
-- /Since: 1.0/
quaternionSlerp ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@a@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Quaternion
    -- ^ /@b@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Float
    -- ^ /@factor@/: the linear interpolation factor
    -> m (Quaternion)
quaternionSlerp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> Quaternion -> Float -> m Quaternion
quaternionSlerp Quaternion
a Quaternion
b Float
factor = IO Quaternion -> m Quaternion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Quaternion -> m Quaternion) -> IO Quaternion -> m Quaternion
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
a' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
a
    Ptr Quaternion
b' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
b
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Quaternion)
    Ptr Quaternion
-> Ptr Quaternion -> CFloat -> Ptr Quaternion -> IO ()
graphene_quaternion_slerp Ptr Quaternion
a' Ptr Quaternion
b' CFloat
factor' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Quaternion) Ptr Quaternion
res
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
a
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
b
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionSlerpMethodInfo
instance (signature ~ (Quaternion -> Float -> m (Quaternion)), MonadIO m) => O.OverloadedMethod QuaternionSlerpMethodInfo Quaternion signature where
    overloadedMethod = quaternionSlerp

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


#endif

-- method Quaternion::to_angle_vec3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the angle, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "axis"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the rotation axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Converts a quaternion into an /@angle@/, /@axis@/ pair.
-- 
-- /Since: 1.0/
quaternionToAngleVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m ((Float, Graphene.Vec3.Vec3))
quaternionToAngleVec3 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m (Float, Vec3)
quaternionToAngleVec3 Quaternion
q = IO (Float, Vec3) -> m (Float, Vec3)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Vec3) -> m (Float, Vec3))
-> IO (Float, Vec3) -> m (Float, Vec3)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr CFloat
angle <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Vec3
axis <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Quaternion -> Ptr CFloat -> Ptr Vec3 -> IO ()
graphene_quaternion_to_angle_vec3 Ptr Quaternion
q' Ptr CFloat
angle Ptr Vec3
axis
    CFloat
angle' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
angle
    let angle'' :: Float
angle'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
angle'
    Vec3
axis' <- ((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
axis
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
angle
    (Float, Vec3) -> IO (Float, Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
angle'', Vec3
axis')

#if defined(ENABLE_OVERLOADING)
data QuaternionToAngleVec3MethodInfo
instance (signature ~ (m ((Float, Graphene.Vec3.Vec3))), MonadIO m) => O.OverloadedMethod QuaternionToAngleVec3MethodInfo Quaternion signature where
    overloadedMethod = quaternionToAngleVec3

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


#endif

-- method Quaternion::to_angles
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "deg_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the rotation angle on\n  the X axis (yaw), in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "deg_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the rotation angle on\n  the Y axis (pitch), in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "deg_z"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the rotation angle on\n  the Z axis (roll), in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_to_angles" graphene_quaternion_to_angles :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr CFloat ->                           -- deg_x : TBasicType TFloat
    Ptr CFloat ->                           -- deg_y : TBasicType TFloat
    Ptr CFloat ->                           -- deg_z : TBasicType TFloat
    IO ()

-- | Converts a t'GI.Graphene.Structs.Quaternion.Quaternion' to its corresponding rotations
-- on the <http://en.wikipedia.org/wiki/Euler_angles Euler angles>
-- on each axis.
-- 
-- /Since: 1.2/
quaternionToAngles ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m ((Float, Float, Float))
quaternionToAngles :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m (Float, Float, Float)
quaternionToAngles Quaternion
q = IO (Float, Float, Float) -> m (Float, Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float, Float) -> m (Float, Float, Float))
-> IO (Float, Float, Float) -> m (Float, Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr CFloat
degX <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
degY <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
degZ <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Quaternion -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> IO ()
graphene_quaternion_to_angles Ptr Quaternion
q' Ptr CFloat
degX Ptr CFloat
degY Ptr CFloat
degZ
    CFloat
degX' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
degX
    let degX'' :: Float
degX'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
degX'
    CFloat
degY' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
degY
    let degY'' :: Float
degY'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
degY'
    CFloat
degZ' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
degZ
    let degZ'' :: Float
degZ'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
degZ'
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
degX
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
degY
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
degZ
    (Float, Float, Float) -> IO (Float, Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
degX'', Float
degY'', Float
degZ'')

#if defined(ENABLE_OVERLOADING)
data QuaternionToAnglesMethodInfo
instance (signature ~ (m ((Float, Float, Float))), MonadIO m) => O.OverloadedMethod QuaternionToAnglesMethodInfo Quaternion signature where
    overloadedMethod = quaternionToAngles

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


#endif

-- method Quaternion::to_matrix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "m"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_matrix_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_quaternion_to_matrix" graphene_quaternion_to_matrix :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Graphene.Matrix.Matrix ->           -- m : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Converts a quaternion into a transformation matrix expressing
-- the rotation defined by the t'GI.Graphene.Structs.Quaternion.Quaternion'.
-- 
-- /Since: 1.0/
quaternionToMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m (Graphene.Matrix.Matrix)
quaternionToMatrix :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m Matrix
quaternionToMatrix Quaternion
q = IO Matrix -> m Matrix
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Matrix -> m Matrix) -> IO Matrix -> m Matrix
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr Matrix
m <- Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
64 :: IO (Ptr Graphene.Matrix.Matrix)
    Ptr Quaternion -> Ptr Matrix -> IO ()
graphene_quaternion_to_matrix Ptr Quaternion
q' Ptr Matrix
m
    Matrix
m' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Graphene.Matrix.Matrix) Ptr Matrix
m
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Matrix -> IO Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
m'

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

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


#endif

-- method Quaternion::to_radians
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rad_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the rotation angle on\n  the X axis (yaw), in radians"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "rad_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the rotation angle on\n  the Y axis (pitch), in radians"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "rad_z"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the rotation angle on\n  the Z axis (roll), in radians"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_quaternion_to_radians" graphene_quaternion_to_radians :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr CFloat ->                           -- rad_x : TBasicType TFloat
    Ptr CFloat ->                           -- rad_y : TBasicType TFloat
    Ptr CFloat ->                           -- rad_z : TBasicType TFloat
    IO ()

-- | Converts a t'GI.Graphene.Structs.Quaternion.Quaternion' to its corresponding rotations
-- on the <http://en.wikipedia.org/wiki/Euler_angles Euler angles>
-- on each axis.
-- 
-- /Since: 1.2/
quaternionToRadians ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m ((Float, Float, Float))
quaternionToRadians :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m (Float, Float, Float)
quaternionToRadians Quaternion
q = IO (Float, Float, Float) -> m (Float, Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float, Float) -> m (Float, Float, Float))
-> IO (Float, Float, Float) -> m (Float, Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    Ptr CFloat
radX <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
radY <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
radZ <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Quaternion -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> IO ()
graphene_quaternion_to_radians Ptr Quaternion
q' Ptr CFloat
radX Ptr CFloat
radY Ptr CFloat
radZ
    CFloat
radX' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
radX
    let radX'' :: Float
radX'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
radX'
    CFloat
radY' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
radY
    let radY'' :: Float
radY'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
radY'
    CFloat
radZ' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
radZ
    let radZ'' :: Float
radZ'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
radZ'
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
radX
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
radY
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
radZ
    (Float, Float, Float) -> IO (Float, Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
radX'', Float
radY'', Float
radZ'')

#if defined(ENABLE_OVERLOADING)
data QuaternionToRadiansMethodInfo
instance (signature ~ (m ((Float, Float, Float))), MonadIO m) => O.OverloadedMethod QuaternionToRadiansMethodInfo Quaternion signature where
    overloadedMethod = quaternionToRadians

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


#endif

-- method Quaternion::to_vec4
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "q"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_quaternion_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\n  #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_quaternion_to_vec4" graphene_quaternion_to_vec4 :: 
    Ptr Quaternion ->                       -- q : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    Ptr Graphene.Vec4.Vec4 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO ()

-- | Copies the components of a t'GI.Graphene.Structs.Quaternion.Quaternion' into a
-- t'GI.Graphene.Structs.Vec4.Vec4'.
-- 
-- /Since: 1.0/
quaternionToVec4 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Quaternion
    -- ^ /@q@/: a t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> m (Graphene.Vec4.Vec4)
quaternionToVec4 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Quaternion -> m Vec4
quaternionToVec4 Quaternion
q = IO Vec4 -> m Vec4
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 Quaternion
q' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
q
    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 Quaternion -> Ptr Vec4 -> IO ()
graphene_quaternion_to_vec4 Ptr Quaternion
q' 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
    Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Quaternion
q
    Vec4 -> IO Vec4
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
res'

#if defined(ENABLE_OVERLOADING)
data QuaternionToVec4MethodInfo
instance (signature ~ (m (Graphene.Vec4.Vec4)), MonadIO m) => O.OverloadedMethod QuaternionToVec4MethodInfo Quaternion signature where
    overloadedMethod = quaternionToVec4

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


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveQuaternionMethod (t :: Symbol) (o :: *) :: * where
    ResolveQuaternionMethod "add" o = QuaternionAddMethodInfo
    ResolveQuaternionMethod "dot" o = QuaternionDotMethodInfo
    ResolveQuaternionMethod "equal" o = QuaternionEqualMethodInfo
    ResolveQuaternionMethod "free" o = QuaternionFreeMethodInfo
    ResolveQuaternionMethod "init" o = QuaternionInitMethodInfo
    ResolveQuaternionMethod "initFromAngleVec3" o = QuaternionInitFromAngleVec3MethodInfo
    ResolveQuaternionMethod "initFromAngles" o = QuaternionInitFromAnglesMethodInfo
    ResolveQuaternionMethod "initFromEuler" o = QuaternionInitFromEulerMethodInfo
    ResolveQuaternionMethod "initFromMatrix" o = QuaternionInitFromMatrixMethodInfo
    ResolveQuaternionMethod "initFromQuaternion" o = QuaternionInitFromQuaternionMethodInfo
    ResolveQuaternionMethod "initFromRadians" o = QuaternionInitFromRadiansMethodInfo
    ResolveQuaternionMethod "initFromVec4" o = QuaternionInitFromVec4MethodInfo
    ResolveQuaternionMethod "initIdentity" o = QuaternionInitIdentityMethodInfo
    ResolveQuaternionMethod "invert" o = QuaternionInvertMethodInfo
    ResolveQuaternionMethod "multiply" o = QuaternionMultiplyMethodInfo
    ResolveQuaternionMethod "normalize" o = QuaternionNormalizeMethodInfo
    ResolveQuaternionMethod "scale" o = QuaternionScaleMethodInfo
    ResolveQuaternionMethod "slerp" o = QuaternionSlerpMethodInfo
    ResolveQuaternionMethod "toAngleVec3" o = QuaternionToAngleVec3MethodInfo
    ResolveQuaternionMethod "toAngles" o = QuaternionToAnglesMethodInfo
    ResolveQuaternionMethod "toMatrix" o = QuaternionToMatrixMethodInfo
    ResolveQuaternionMethod "toRadians" o = QuaternionToRadiansMethodInfo
    ResolveQuaternionMethod "toVec4" o = QuaternionToVec4MethodInfo
    ResolveQuaternionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveQuaternionMethod t Quaternion, O.OverloadedMethod info Quaternion p) => OL.IsLabel t (Quaternion -> 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 ~ ResolveQuaternionMethod t Quaternion, O.OverloadedMethod info Quaternion p, R.HasField t Quaternion p) => R.HasField t Quaternion p where
    getField = O.overloadedMethod @info

#endif

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

#endif