{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Describe a rotation using Euler angles.
-- 
-- The contents of the t'GI.Graphene.Structs.Euler.Euler' structure are private
-- and should never be accessed directly.
-- 
-- /Since: 1.2/

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

module GI.Graphene.Structs.Euler
    ( 

-- * Exported types
    Euler(..)                               ,
    newZeroEuler                            ,
    noEuler                                 ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveEulerMethod                      ,
#endif


-- ** alloc #method:alloc#

    eulerAlloc                              ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    EulerEqualMethodInfo                    ,
#endif
    eulerEqual                              ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    EulerFreeMethodInfo                     ,
#endif
    eulerFree                               ,


-- ** getAlpha #method:getAlpha#

#if defined(ENABLE_OVERLOADING)
    EulerGetAlphaMethodInfo                 ,
#endif
    eulerGetAlpha                           ,


-- ** getBeta #method:getBeta#

#if defined(ENABLE_OVERLOADING)
    EulerGetBetaMethodInfo                  ,
#endif
    eulerGetBeta                            ,


-- ** getGamma #method:getGamma#

#if defined(ENABLE_OVERLOADING)
    EulerGetGammaMethodInfo                 ,
#endif
    eulerGetGamma                           ,


-- ** getOrder #method:getOrder#

#if defined(ENABLE_OVERLOADING)
    EulerGetOrderMethodInfo                 ,
#endif
    eulerGetOrder                           ,


-- ** getX #method:getX#

#if defined(ENABLE_OVERLOADING)
    EulerGetXMethodInfo                     ,
#endif
    eulerGetX                               ,


-- ** getY #method:getY#

#if defined(ENABLE_OVERLOADING)
    EulerGetYMethodInfo                     ,
#endif
    eulerGetY                               ,


-- ** getZ #method:getZ#

#if defined(ENABLE_OVERLOADING)
    EulerGetZMethodInfo                     ,
#endif
    eulerGetZ                               ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    EulerInitMethodInfo                     ,
#endif
    eulerInit                               ,


-- ** initFromEuler #method:initFromEuler#

#if defined(ENABLE_OVERLOADING)
    EulerInitFromEulerMethodInfo            ,
#endif
    eulerInitFromEuler                      ,


-- ** initFromMatrix #method:initFromMatrix#

#if defined(ENABLE_OVERLOADING)
    EulerInitFromMatrixMethodInfo           ,
#endif
    eulerInitFromMatrix                     ,


-- ** initFromQuaternion #method:initFromQuaternion#

#if defined(ENABLE_OVERLOADING)
    EulerInitFromQuaternionMethodInfo       ,
#endif
    eulerInitFromQuaternion                 ,


-- ** initFromVec3 #method:initFromVec3#

#if defined(ENABLE_OVERLOADING)
    EulerInitFromVec3MethodInfo             ,
#endif
    eulerInitFromVec3                       ,


-- ** initWithOrder #method:initWithOrder#

#if defined(ENABLE_OVERLOADING)
    EulerInitWithOrderMethodInfo            ,
#endif
    eulerInitWithOrder                      ,


-- ** reorder #method:reorder#

#if defined(ENABLE_OVERLOADING)
    EulerReorderMethodInfo                  ,
#endif
    eulerReorder                            ,


-- ** toMatrix #method:toMatrix#

#if defined(ENABLE_OVERLOADING)
    EulerToMatrixMethodInfo                 ,
#endif
    eulerToMatrix                           ,


-- ** toQuaternion #method:toQuaternion#

#if defined(ENABLE_OVERLOADING)
    EulerToQuaternionMethodInfo             ,
#endif
    eulerToQuaternion                       ,


-- ** toVec3 #method:toVec3#

#if defined(ENABLE_OVERLOADING)
    EulerToVec3MethodInfo                   ,
#endif
    eulerToVec3                             ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 {-# SOURCE #-} qualified GI.Graphene.Enums as Graphene.Enums
import {-# SOURCE #-} qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import {-# SOURCE #-} qualified GI.Graphene.Structs.Quaternion as Graphene.Quaternion
import {-# SOURCE #-} qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3

-- | Memory-managed wrapper type.
newtype Euler = Euler (ManagedPtr Euler)
    deriving (Euler -> Euler -> Bool
(Euler -> Euler -> Bool) -> (Euler -> Euler -> Bool) -> Eq Euler
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Euler -> Euler -> Bool
$c/= :: Euler -> Euler -> Bool
== :: Euler -> Euler -> Bool
$c== :: Euler -> Euler -> Bool
Eq)
foreign import ccall "graphene_euler_get_type" c_graphene_euler_get_type :: 
    IO GType

instance BoxedObject Euler where
    boxedType :: Euler -> IO GType
boxedType _ = IO GType
c_graphene_euler_get_type

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

-- | Construct a `Euler` struct initialized to zero.
newZeroEuler :: MonadIO m => m Euler
newZeroEuler :: m Euler
newZeroEuler = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Euler)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 20 IO (Ptr Euler) -> (Ptr Euler -> IO Euler) -> IO Euler
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Euler -> Euler
Euler

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


-- | A convenience alias for `Nothing` :: `Maybe` `Euler`.
noEuler :: Maybe Euler
noEuler :: Maybe Euler
noEuler = Maybe Euler
forall a. Maybe a
Nothing


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

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

foreign import ccall "graphene_euler_alloc" graphene_euler_alloc :: 
    IO (Ptr Euler)

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method Euler::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , 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
--           }
--       , Arg
--           { argCName = "b"
--           , 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 (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_equal" graphene_euler_equal :: 
    Ptr Euler ->                            -- a : TInterface (Name {namespace = "Graphene", name = "Euler"})
    Ptr Euler ->                            -- b : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CInt

-- | Checks if two t'GI.Graphene.Structs.Euler.Euler' are equal.
-- 
-- /Since: 1.2/
eulerEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@a@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> Euler
    -- ^ /@b@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Bool
    -- ^ __Returns:__ @true@ if the two t'GI.Graphene.Structs.Euler.Euler' are equal
eulerEqual :: Euler -> Euler -> m Bool
eulerEqual a :: Euler
a b :: Euler
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 Euler
a' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
a
    Ptr Euler
b' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
b
    CInt
result <- Ptr Euler -> Ptr Euler -> IO CInt
graphene_euler_equal Ptr Euler
a' Ptr Euler
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
a
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
b
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EulerEqualMethodInfo
instance (signature ~ (Euler -> m Bool), MonadIO m) => O.MethodInfo EulerEqualMethodInfo Euler signature where
    overloadedMethod = eulerEqual

#endif

-- method Euler::free
-- method type : OrdinaryMethod
-- Args: [ 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: Nothing
-- throws : False
-- Skip return : False

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

-- | Frees the resources allocated by 'GI.Graphene.Structs.Euler.eulerAlloc'.
-- 
-- /Since: 1.2/
eulerFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m ()
eulerFree :: Euler -> m ()
eulerFree e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Euler -> IO ()
graphene_euler_free Ptr Euler
e'
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EulerFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo EulerFreeMethodInfo Euler signature where
    overloadedMethod = eulerFree

#endif

-- method Euler::get_alpha
-- method type : OrdinaryMethod
-- Args: [ 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 (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_alpha" graphene_euler_get_alpha :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CFloat

-- | Retrieves the first component of the Euler angle vector,
-- depending on the order of rotation.
-- 
-- See also: 'GI.Graphene.Structs.Euler.eulerGetX'
-- 
-- /Since: 1.10/
eulerGetAlpha ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Float
    -- ^ __Returns:__ the first component of the Euler angle vector, in radians
eulerGetAlpha :: Euler -> m Float
eulerGetAlpha e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CFloat
result <- Ptr Euler -> IO CFloat
graphene_euler_get_alpha Ptr Euler
e'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetAlphaMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo EulerGetAlphaMethodInfo Euler signature where
    overloadedMethod = eulerGetAlpha

#endif

-- method Euler::get_beta
-- method type : OrdinaryMethod
-- Args: [ 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 (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_beta" graphene_euler_get_beta :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CFloat

-- | Retrieves the second component of the Euler angle vector,
-- depending on the order of rotation.
-- 
-- See also: 'GI.Graphene.Structs.Euler.eulerGetY'
-- 
-- /Since: 1.10/
eulerGetBeta ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Float
    -- ^ __Returns:__ the second component of the Euler angle vector, in radians
eulerGetBeta :: Euler -> m Float
eulerGetBeta e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CFloat
result <- Ptr Euler -> IO CFloat
graphene_euler_get_beta Ptr Euler
e'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetBetaMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo EulerGetBetaMethodInfo Euler signature where
    overloadedMethod = eulerGetBeta

#endif

-- method Euler::get_gamma
-- method type : OrdinaryMethod
-- Args: [ 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 (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_gamma" graphene_euler_get_gamma :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CFloat

-- | Retrieves the third component of the Euler angle vector,
-- depending on the order of rotation.
-- 
-- See also: 'GI.Graphene.Structs.Euler.eulerGetZ'
-- 
-- /Since: 1.10/
eulerGetGamma ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Float
    -- ^ __Returns:__ the third component of the Euler angle vector, in radians
eulerGetGamma :: Euler -> m Float
eulerGetGamma e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CFloat
result <- Ptr Euler -> IO CFloat
graphene_euler_get_gamma Ptr Euler
e'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetGammaMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo EulerGetGammaMethodInfo Euler signature where
    overloadedMethod = eulerGetGamma

#endif

-- method Euler::get_order
-- method type : OrdinaryMethod
-- Args: [ 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 = "EulerOrder" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_order" graphene_euler_get_order :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CInt

-- | Retrieves the order used to apply the rotations described in the
-- t'GI.Graphene.Structs.Euler.Euler' structure, when converting to and from other
-- structures, like t'GI.Graphene.Structs.Quaternion.Quaternion' and t'GI.Graphene.Structs.Matrix.Matrix'.
-- 
-- This function does not return the 'GI.Graphene.Enums.EulerOrderDefault'
-- enumeration value; it will return the effective order of rotation
-- instead.
-- 
-- /Since: 1.2/
eulerGetOrder ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Graphene.Enums.EulerOrder
    -- ^ __Returns:__ the order used to apply the rotations
eulerGetOrder :: Euler -> m EulerOrder
eulerGetOrder e :: Euler
e = IO EulerOrder -> m EulerOrder
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EulerOrder -> m EulerOrder) -> IO EulerOrder -> m EulerOrder
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CInt
result <- Ptr Euler -> IO CInt
graphene_euler_get_order Ptr Euler
e'
    let result' :: EulerOrder
result' = (Int -> EulerOrder
forall a. Enum a => Int -> a
toEnum (Int -> EulerOrder) -> (CInt -> Int) -> CInt -> EulerOrder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    EulerOrder -> IO EulerOrder
forall (m :: * -> *) a. Monad m => a -> m a
return EulerOrder
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetOrderMethodInfo
instance (signature ~ (m Graphene.Enums.EulerOrder), MonadIO m) => O.MethodInfo EulerGetOrderMethodInfo Euler signature where
    overloadedMethod = eulerGetOrder

#endif

-- method Euler::get_x
-- method type : OrdinaryMethod
-- Args: [ 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 (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_x" graphene_euler_get_x :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CFloat

-- | Retrieves the rotation angle on the X axis, in degrees.
-- 
-- /Since: 1.2/
eulerGetX ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Float
    -- ^ __Returns:__ the rotation angle
eulerGetX :: Euler -> m Float
eulerGetX e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CFloat
result <- Ptr Euler -> IO CFloat
graphene_euler_get_x Ptr Euler
e'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetXMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo EulerGetXMethodInfo Euler signature where
    overloadedMethod = eulerGetX

#endif

-- method Euler::get_y
-- method type : OrdinaryMethod
-- Args: [ 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 (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_y" graphene_euler_get_y :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CFloat

-- | Retrieves the rotation angle on the Y axis, in degrees.
-- 
-- /Since: 1.2/
eulerGetY ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Float
    -- ^ __Returns:__ the rotation angle
eulerGetY :: Euler -> m Float
eulerGetY e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CFloat
result <- Ptr Euler -> IO CFloat
graphene_euler_get_y Ptr Euler
e'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetYMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo EulerGetYMethodInfo Euler signature where
    overloadedMethod = eulerGetY

#endif

-- method Euler::get_z
-- method type : OrdinaryMethod
-- Args: [ 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 (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_get_z" graphene_euler_get_z :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO CFloat

-- | Retrieves the rotation angle on the Z axis, in degrees.
-- 
-- /Since: 1.2/
eulerGetZ ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Float
    -- ^ __Returns:__ the rotation angle
eulerGetZ :: Euler -> m Float
eulerGetZ e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    CFloat
result <- Ptr Euler -> IO CFloat
graphene_euler_get_z Ptr Euler
e'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data EulerGetZMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo EulerGetZMethodInfo Euler signature where
    overloadedMethod = eulerGetZ

#endif

-- method Euler::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "e"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Euler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_euler_t to initialize"
--                 , 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 "rotation angle on the X axis, in degrees"
--                 , 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 "rotation angle on the Y axis, in degrees"
--                 , 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 "rotation angle on the Z axis, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Euler" })
-- throws : False
-- Skip return : False

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

-- | Initializes a t'GI.Graphene.Structs.Euler.Euler' using the given angles.
-- 
-- The order of the rotations is 'GI.Graphene.Enums.EulerOrderDefault'.
-- 
-- /Since: 1.2/
eulerInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: the t'GI.Graphene.Structs.Euler.Euler' to initialize
    -> Float
    -- ^ /@x@/: rotation angle on the X axis, in degrees
    -> Float
    -- ^ /@y@/: rotation angle on the Y axis, in degrees
    -> Float
    -- ^ /@z@/: rotation angle on the Z axis, in degrees
    -> m Euler
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Euler.Euler'
eulerInit :: Euler -> Float -> Float -> Float -> m Euler
eulerInit e :: Euler
e x :: Float
x y :: Float
y z :: Float
z = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    let x' :: CFloat
x' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x
    let y' :: CFloat
y' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y
    let z' :: CFloat
z' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
z
    Ptr Euler
result <- Ptr Euler -> CFloat -> CFloat -> CFloat -> IO (Ptr Euler)
graphene_euler_init Ptr Euler
e' CFloat
x' CFloat
y' CFloat
z'
    Text -> Ptr Euler -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eulerInit" Ptr Euler
result
    Euler
result' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
result'

#if defined(ENABLE_OVERLOADING)
data EulerInitMethodInfo
instance (signature ~ (Float -> Float -> Float -> m Euler), MonadIO m) => O.MethodInfo EulerInitMethodInfo Euler signature where
    overloadedMethod = eulerInit

#endif

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

foreign import ccall "graphene_euler_init_from_euler" graphene_euler_init_from_euler :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    Ptr Euler ->                            -- src : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO (Ptr Euler)

-- | Initializes a t'GI.Graphene.Structs.Euler.Euler' using the angles and order of
-- another t'GI.Graphene.Structs.Euler.Euler'.
-- 
-- If the t'GI.Graphene.Structs.Euler.Euler' /@src@/ is 'P.Nothing', this function is equivalent
-- to calling 'GI.Graphene.Structs.Euler.eulerInit' with all angles set to 0.
-- 
-- /Since: 1.2/
eulerInitFromEuler ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: the t'GI.Graphene.Structs.Euler.Euler' to initialize
    -> Maybe (Euler)
    -- ^ /@src@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m Euler
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Euler.Euler'
eulerInitFromEuler :: Euler -> Maybe Euler -> m Euler
eulerInitFromEuler e :: Euler
e src :: Maybe Euler
src = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Euler
maybeSrc <- case Maybe Euler
src of
        Nothing -> Ptr Euler -> IO (Ptr Euler)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Euler
forall a. Ptr a
nullPtr
        Just jSrc :: Euler
jSrc -> do
            Ptr Euler
jSrc' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
jSrc
            Ptr Euler -> IO (Ptr Euler)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Euler
jSrc'
    Ptr Euler
result <- Ptr Euler -> Ptr Euler -> IO (Ptr Euler)
graphene_euler_init_from_euler Ptr Euler
e' Ptr Euler
maybeSrc
    Text -> Ptr Euler -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eulerInitFromEuler" Ptr Euler
result
    Euler
result' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Maybe Euler -> (Euler -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Euler
src Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
result'

#if defined(ENABLE_OVERLOADING)
data EulerInitFromEulerMethodInfo
instance (signature ~ (Maybe (Euler) -> m Euler), MonadIO m) => O.MethodInfo EulerInitFromEulerMethodInfo Euler signature where
    overloadedMethod = eulerInitFromEuler

#endif

-- method Euler::init_from_matrix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "e"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Euler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_euler_t to initialize"
--                 , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a rotation matrix" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "order"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "EulerOrder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the order used to apply the rotations"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Euler" })
-- throws : False
-- Skip return : False

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

-- | Initializes a t'GI.Graphene.Structs.Euler.Euler' using the given rotation matrix.
-- 
-- If the t'GI.Graphene.Structs.Matrix.Matrix' /@m@/ is 'P.Nothing', the t'GI.Graphene.Structs.Euler.Euler' will
-- be initialized with all angles set to 0.
-- 
-- /Since: 1.2/
eulerInitFromMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: the t'GI.Graphene.Structs.Euler.Euler' to initialize
    -> Maybe (Graphene.Matrix.Matrix)
    -- ^ /@m@/: a rotation matrix
    -> Graphene.Enums.EulerOrder
    -- ^ /@order@/: the order used to apply the rotations
    -> m Euler
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Euler.Euler'
eulerInitFromMatrix :: Euler -> Maybe Matrix -> EulerOrder -> m Euler
eulerInitFromMatrix e :: Euler
e m :: Maybe Matrix
m order :: EulerOrder
order = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Matrix
maybeM <- case Maybe Matrix
m of
        Nothing -> Ptr Matrix -> IO (Ptr Matrix)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Matrix
forall a. Ptr a
nullPtr
        Just jM :: Matrix
jM -> do
            Ptr Matrix
jM' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
jM
            Ptr Matrix -> IO (Ptr Matrix)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Matrix
jM'
    let order' :: CInt
order' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EulerOrder -> Int) -> EulerOrder -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EulerOrder -> Int
forall a. Enum a => a -> Int
fromEnum) EulerOrder
order
    Ptr Euler
result <- Ptr Euler -> Ptr Matrix -> CInt -> IO (Ptr Euler)
graphene_euler_init_from_matrix Ptr Euler
e' Ptr Matrix
maybeM CInt
order'
    Text -> Ptr Euler -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eulerInitFromMatrix" Ptr Euler
result
    Euler
result' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Maybe Matrix -> (Matrix -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Matrix
m Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
result'

#if defined(ENABLE_OVERLOADING)
data EulerInitFromMatrixMethodInfo
instance (signature ~ (Maybe (Graphene.Matrix.Matrix) -> Graphene.Enums.EulerOrder -> m Euler), MonadIO m) => O.MethodInfo EulerInitFromMatrixMethodInfo Euler signature where
    overloadedMethod = eulerInitFromMatrix

#endif

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

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

-- | Initializes a t'GI.Graphene.Structs.Euler.Euler' using the given normalized quaternion.
-- 
-- If the t'GI.Graphene.Structs.Quaternion.Quaternion' /@q@/ is 'P.Nothing', the t'GI.Graphene.Structs.Euler.Euler' will
-- be initialized with all angles set to 0.
-- 
-- /Since: 1.2/
eulerInitFromQuaternion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> Maybe (Graphene.Quaternion.Quaternion)
    -- ^ /@q@/: a normalized t'GI.Graphene.Structs.Quaternion.Quaternion'
    -> Graphene.Enums.EulerOrder
    -- ^ /@order@/: the order used to apply the rotations
    -> m Euler
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Euler.Euler'
eulerInitFromQuaternion :: Euler -> Maybe Quaternion -> EulerOrder -> m Euler
eulerInitFromQuaternion e :: Euler
e q :: Maybe Quaternion
q order :: EulerOrder
order = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Quaternion
maybeQ <- case Maybe Quaternion
q of
        Nothing -> Ptr Quaternion -> IO (Ptr Quaternion)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Quaternion
forall a. Ptr a
nullPtr
        Just jQ :: Quaternion
jQ -> do
            Ptr Quaternion
jQ' <- Quaternion -> IO (Ptr Quaternion)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Quaternion
jQ
            Ptr Quaternion -> IO (Ptr Quaternion)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Quaternion
jQ'
    let order' :: CInt
order' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EulerOrder -> Int) -> EulerOrder -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EulerOrder -> Int
forall a. Enum a => a -> Int
fromEnum) EulerOrder
order
    Ptr Euler
result <- Ptr Euler -> Ptr Quaternion -> CInt -> IO (Ptr Euler)
graphene_euler_init_from_quaternion Ptr Euler
e' Ptr Quaternion
maybeQ CInt
order'
    Text -> Ptr Euler -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eulerInitFromQuaternion" Ptr Euler
result
    Euler
result' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Maybe Quaternion -> (Quaternion -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Quaternion
q Quaternion -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
result'

#if defined(ENABLE_OVERLOADING)
data EulerInitFromQuaternionMethodInfo
instance (signature ~ (Maybe (Graphene.Quaternion.Quaternion) -> Graphene.Enums.EulerOrder -> m Euler), MonadIO m) => O.MethodInfo EulerInitFromQuaternionMethodInfo Euler signature where
    overloadedMethod = eulerInitFromQuaternion

#endif

-- method Euler::init_from_vec3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "e"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Euler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_euler_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #graphene_vec3_t containing the rotation\n  angles in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "order"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "EulerOrder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the order used to apply the rotations"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Euler" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_init_from_vec3" graphene_euler_init_from_vec3 :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    Ptr Graphene.Vec3.Vec3 ->               -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    CInt ->                                 -- order : TInterface (Name {namespace = "Graphene", name = "EulerOrder"})
    IO (Ptr Euler)

-- | Initializes a t'GI.Graphene.Structs.Euler.Euler' using the angles contained in a
-- t'GI.Graphene.Structs.Vec3.Vec3'.
-- 
-- If the t'GI.Graphene.Structs.Vec3.Vec3' /@v@/ is 'P.Nothing', the t'GI.Graphene.Structs.Euler.Euler' will be
-- initialized with all angles set to 0.
-- 
-- /Since: 1.2/
eulerInitFromVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: the t'GI.Graphene.Structs.Euler.Euler' to initialize
    -> Maybe (Graphene.Vec3.Vec3)
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3' containing the rotation
    --   angles in degrees
    -> Graphene.Enums.EulerOrder
    -- ^ /@order@/: the order used to apply the rotations
    -> m Euler
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Euler.Euler'
eulerInitFromVec3 :: Euler -> Maybe Vec3 -> EulerOrder -> m Euler
eulerInitFromVec3 e :: Euler
e v :: Maybe Vec3
v order :: EulerOrder
order = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Vec3
maybeV <- case Maybe Vec3
v of
        Nothing -> Ptr Vec3 -> IO (Ptr Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Vec3
forall a. Ptr a
nullPtr
        Just jV :: Vec3
jV -> do
            Ptr Vec3
jV' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
jV
            Ptr Vec3 -> IO (Ptr Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Vec3
jV'
    let order' :: CInt
order' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EulerOrder -> Int) -> EulerOrder -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EulerOrder -> Int
forall a. Enum a => a -> Int
fromEnum) EulerOrder
order
    Ptr Euler
result <- Ptr Euler -> Ptr Vec3 -> CInt -> IO (Ptr Euler)
graphene_euler_init_from_vec3 Ptr Euler
e' Ptr Vec3
maybeV CInt
order'
    Text -> Ptr Euler -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eulerInitFromVec3" Ptr Euler
result
    Euler
result' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Maybe Vec3 -> (Vec3 -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Vec3
v Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
result'

#if defined(ENABLE_OVERLOADING)
data EulerInitFromVec3MethodInfo
instance (signature ~ (Maybe (Graphene.Vec3.Vec3) -> Graphene.Enums.EulerOrder -> m Euler), MonadIO m) => O.MethodInfo EulerInitFromVec3MethodInfo Euler signature where
    overloadedMethod = eulerInitFromVec3

#endif

-- method Euler::init_with_order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "e"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Euler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_euler_t to initialize"
--                 , 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 "rotation angle on the X axis, in degrees"
--                 , 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 "rotation angle on the Y axis, in degrees"
--                 , 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 "rotation angle on the Z axis, in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "order"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "EulerOrder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the order used to apply the rotations"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Euler" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_init_with_order" graphene_euler_init_with_order :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    CFloat ->                               -- x : TBasicType TFloat
    CFloat ->                               -- y : TBasicType TFloat
    CFloat ->                               -- z : TBasicType TFloat
    CInt ->                                 -- order : TInterface (Name {namespace = "Graphene", name = "EulerOrder"})
    IO (Ptr Euler)

-- | Initializes a t'GI.Graphene.Structs.Euler.Euler' with the given angles and /@order@/.
-- 
-- /Since: 1.2/
eulerInitWithOrder ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: the t'GI.Graphene.Structs.Euler.Euler' to initialize
    -> Float
    -- ^ /@x@/: rotation angle on the X axis, in degrees
    -> Float
    -- ^ /@y@/: rotation angle on the Y axis, in degrees
    -> Float
    -- ^ /@z@/: rotation angle on the Z axis, in degrees
    -> Graphene.Enums.EulerOrder
    -- ^ /@order@/: the order used to apply the rotations
    -> m Euler
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Euler.Euler'
eulerInitWithOrder :: Euler -> Float -> Float -> Float -> EulerOrder -> m Euler
eulerInitWithOrder e :: Euler
e x :: Float
x y :: Float
y z :: Float
z order :: EulerOrder
order = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    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 order' :: CInt
order' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EulerOrder -> Int) -> EulerOrder -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EulerOrder -> Int
forall a. Enum a => a -> Int
fromEnum) EulerOrder
order
    Ptr Euler
result <- Ptr Euler -> CFloat -> CFloat -> CFloat -> CInt -> IO (Ptr Euler)
graphene_euler_init_with_order Ptr Euler
e' CFloat
x' CFloat
y' CFloat
z' CInt
order'
    Text -> Ptr Euler -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eulerInitWithOrder" Ptr Euler
result
    Euler
result' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
result
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
result'

#if defined(ENABLE_OVERLOADING)
data EulerInitWithOrderMethodInfo
instance (signature ~ (Float -> Float -> Float -> Graphene.Enums.EulerOrder -> m Euler), MonadIO m) => O.MethodInfo EulerInitWithOrderMethodInfo Euler signature where
    overloadedMethod = eulerInitWithOrder

#endif

-- method Euler::reorder
-- method type : OrdinaryMethod
-- Args: [ 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
--           }
--       , Arg
--           { argCName = "order"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "EulerOrder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new order" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Euler" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the reordered\n  #graphene_euler_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_euler_reorder" graphene_euler_reorder :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    CInt ->                                 -- order : TInterface (Name {namespace = "Graphene", name = "EulerOrder"})
    Ptr Euler ->                            -- res : TInterface (Name {namespace = "Graphene", name = "Euler"})
    IO ()

-- | Reorders a t'GI.Graphene.Structs.Euler.Euler' using /@order@/.
-- 
-- This function is equivalent to creating a t'GI.Graphene.Structs.Quaternion.Quaternion' from the
-- given t'GI.Graphene.Structs.Euler.Euler', and then converting the quaternion into another
-- t'GI.Graphene.Structs.Euler.Euler'.
-- 
-- /Since: 1.2/
eulerReorder ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> Graphene.Enums.EulerOrder
    -- ^ /@order@/: the new order
    -> m (Euler)
eulerReorder :: Euler -> EulerOrder -> m Euler
eulerReorder e :: Euler
e order :: EulerOrder
order = IO Euler -> m Euler
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Euler -> m Euler) -> IO Euler -> m Euler
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    let order' :: CInt
order' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EulerOrder -> Int) -> EulerOrder -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EulerOrder -> Int
forall a. Enum a => a -> Int
fromEnum) EulerOrder
order
    Ptr Euler
res <- Int -> IO (Ptr Euler)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 20 :: IO (Ptr Euler)
    Ptr Euler -> CInt -> Ptr Euler -> IO ()
graphene_euler_reorder Ptr Euler
e' CInt
order' Ptr Euler
res
    Euler
res' <- ((ManagedPtr Euler -> Euler) -> Ptr Euler -> IO Euler
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Euler -> Euler
Euler) Ptr Euler
res
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Euler -> IO Euler
forall (m :: * -> *) a. Monad m => a -> m a
return Euler
res'

#if defined(ENABLE_OVERLOADING)
data EulerReorderMethodInfo
instance (signature ~ (Graphene.Enums.EulerOrder -> m (Euler)), MonadIO m) => O.MethodInfo EulerReorderMethodInfo Euler signature where
    overloadedMethod = eulerReorder

#endif

-- method Euler::to_matrix
-- method type : OrdinaryMethod
-- Args: [ 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
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for 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_euler_to_matrix" graphene_euler_to_matrix :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    Ptr Graphene.Matrix.Matrix ->           -- res : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO ()

-- | Converts a t'GI.Graphene.Structs.Euler.Euler' into a transformation matrix expressing
-- the extrinsic composition of rotations described by the Euler angles.
-- 
-- The rotations are applied over the reference frame axes in the order
-- associated with the t'GI.Graphene.Structs.Euler.Euler'; for instance, if the order
-- used to initialize /@e@/ is 'GI.Graphene.Enums.EulerOrderXyz':
-- 
--  * the first rotation moves the body around the X axis with
--    an angle φ
--  * the second rotation moves the body around the Y axis with
--    an angle of ϑ
--  * the third rotation moves the body around the Z axis with
--    an angle of ψ
-- 
-- The rotation sign convention is right-handed, to preserve compatibility
-- between Euler-based, quaternion-based, and angle-axis-based rotations.
-- 
-- /Since: 1.2/
eulerToMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m (Graphene.Matrix.Matrix)
eulerToMatrix :: Euler -> m Matrix
eulerToMatrix e :: Euler
e = 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Matrix
res <- Int -> IO (Ptr Matrix)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 64 :: IO (Ptr Graphene.Matrix.Matrix)
    Ptr Euler -> Ptr Matrix -> IO ()
graphene_euler_to_matrix Ptr Euler
e' Ptr Matrix
res
    Matrix
res' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Graphene.Matrix.Matrix) Ptr Matrix
res
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Matrix -> IO Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
res'

#if defined(ENABLE_OVERLOADING)
data EulerToMatrixMethodInfo
instance (signature ~ (m (Graphene.Matrix.Matrix)), MonadIO m) => O.MethodInfo EulerToMatrixMethodInfo Euler signature where
    overloadedMethod = eulerToMatrix

#endif

-- method Euler::to_quaternion
-- method type : OrdinaryMethod
-- Args: [ 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
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Quaternion" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_quaternion_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_euler_to_quaternion" graphene_euler_to_quaternion :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    Ptr Graphene.Quaternion.Quaternion ->   -- res : TInterface (Name {namespace = "Graphene", name = "Quaternion"})
    IO ()

-- | Converts a t'GI.Graphene.Structs.Euler.Euler' into a t'GI.Graphene.Structs.Quaternion.Quaternion'.
-- 
-- /Since: 1.10/
eulerToQuaternion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m (Graphene.Quaternion.Quaternion)
eulerToQuaternion :: Euler -> m Quaternion
eulerToQuaternion e :: 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 Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Quaternion
res <- Int -> IO (Ptr Quaternion)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Graphene.Quaternion.Quaternion)
    Ptr Euler -> Ptr Quaternion -> IO ()
graphene_euler_to_quaternion Ptr Euler
e' Ptr Quaternion
res
    Quaternion
res' <- ((ManagedPtr Quaternion -> Quaternion)
-> Ptr Quaternion -> IO Quaternion
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Quaternion -> Quaternion
Graphene.Quaternion.Quaternion) Ptr Quaternion
res
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Quaternion -> IO Quaternion
forall (m :: * -> *) a. Monad m => a -> m a
return Quaternion
res'

#if defined(ENABLE_OVERLOADING)
data EulerToQuaternionMethodInfo
instance (signature ~ (m (Graphene.Quaternion.Quaternion)), MonadIO m) => O.MethodInfo EulerToQuaternionMethodInfo Euler signature where
    overloadedMethod = eulerToQuaternion

#endif

-- method Euler::to_vec3
-- method type : OrdinaryMethod
-- Args: [ 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
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_vec3_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_euler_to_vec3" graphene_euler_to_vec3 :: 
    Ptr Euler ->                            -- e : TInterface (Name {namespace = "Graphene", name = "Euler"})
    Ptr Graphene.Vec3.Vec3 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO ()

-- | Retrieves the angles of a t'GI.Graphene.Structs.Euler.Euler' and initializes a
-- t'GI.Graphene.Structs.Vec3.Vec3' with them.
-- 
-- /Since: 1.2/
eulerToVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Euler
    -- ^ /@e@/: a t'GI.Graphene.Structs.Euler.Euler'
    -> m (Graphene.Vec3.Vec3)
eulerToVec3 :: Euler -> m Vec3
eulerToVec3 e :: Euler
e = IO Vec3 -> m Vec3
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Euler
e' <- Euler -> IO (Ptr Euler)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Euler
e
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Euler -> Ptr Vec3 -> IO ()
graphene_euler_to_vec3 Ptr Euler
e' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Graphene.Vec3.Vec3) Ptr Vec3
res
    Euler -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Euler
e
    Vec3 -> IO Vec3
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data EulerToVec3MethodInfo
instance (signature ~ (m (Graphene.Vec3.Vec3)), MonadIO m) => O.MethodInfo EulerToVec3MethodInfo Euler signature where
    overloadedMethod = eulerToVec3

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveEulerMethod (t :: Symbol) (o :: *) :: * where
    ResolveEulerMethod "equal" o = EulerEqualMethodInfo
    ResolveEulerMethod "free" o = EulerFreeMethodInfo
    ResolveEulerMethod "init" o = EulerInitMethodInfo
    ResolveEulerMethod "initFromEuler" o = EulerInitFromEulerMethodInfo
    ResolveEulerMethod "initFromMatrix" o = EulerInitFromMatrixMethodInfo
    ResolveEulerMethod "initFromQuaternion" o = EulerInitFromQuaternionMethodInfo
    ResolveEulerMethod "initFromVec3" o = EulerInitFromVec3MethodInfo
    ResolveEulerMethod "initWithOrder" o = EulerInitWithOrderMethodInfo
    ResolveEulerMethod "reorder" o = EulerReorderMethodInfo
    ResolveEulerMethod "toMatrix" o = EulerToMatrixMethodInfo
    ResolveEulerMethod "toQuaternion" o = EulerToQuaternionMethodInfo
    ResolveEulerMethod "toVec3" o = EulerToVec3MethodInfo
    ResolveEulerMethod "getAlpha" o = EulerGetAlphaMethodInfo
    ResolveEulerMethod "getBeta" o = EulerGetBetaMethodInfo
    ResolveEulerMethod "getGamma" o = EulerGetGammaMethodInfo
    ResolveEulerMethod "getOrder" o = EulerGetOrderMethodInfo
    ResolveEulerMethod "getX" o = EulerGetXMethodInfo
    ResolveEulerMethod "getY" o = EulerGetYMethodInfo
    ResolveEulerMethod "getZ" o = EulerGetZMethodInfo
    ResolveEulerMethod l o = O.MethodResolutionFailed l o

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

#endif