{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A structure capable of holding a vector with three dimensions: x, y, and z.
-- 
-- The contents of the t'GI.Graphene.Structs.Vec3.Vec3' structure are private and should
-- never be accessed directly.

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

module GI.Graphene.Structs.Vec3
    ( 

-- * Exported types
    Vec3(..)                                ,
    newZeroVec3                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [add]("GI.Graphene.Structs.Vec3#g:method:add"), [cross]("GI.Graphene.Structs.Vec3#g:method:cross"), [divide]("GI.Graphene.Structs.Vec3#g:method:divide"), [dot]("GI.Graphene.Structs.Vec3#g:method:dot"), [equal]("GI.Graphene.Structs.Vec3#g:method:equal"), [free]("GI.Graphene.Structs.Vec3#g:method:free"), [init]("GI.Graphene.Structs.Vec3#g:method:init"), [initFromFloat]("GI.Graphene.Structs.Vec3#g:method:initFromFloat"), [initFromVec3]("GI.Graphene.Structs.Vec3#g:method:initFromVec3"), [interpolate]("GI.Graphene.Structs.Vec3#g:method:interpolate"), [length]("GI.Graphene.Structs.Vec3#g:method:length"), [max]("GI.Graphene.Structs.Vec3#g:method:max"), [min]("GI.Graphene.Structs.Vec3#g:method:min"), [multiply]("GI.Graphene.Structs.Vec3#g:method:multiply"), [near]("GI.Graphene.Structs.Vec3#g:method:near"), [negate]("GI.Graphene.Structs.Vec3#g:method:negate"), [normalize]("GI.Graphene.Structs.Vec3#g:method:normalize"), [scale]("GI.Graphene.Structs.Vec3#g:method:scale"), [subtract]("GI.Graphene.Structs.Vec3#g:method:subtract").
-- 
-- ==== Getters
-- [getX]("GI.Graphene.Structs.Vec3#g:method:getX"), [getXy]("GI.Graphene.Structs.Vec3#g:method:getXy"), [getXy0]("GI.Graphene.Structs.Vec3#g:method:getXy0"), [getXyz0]("GI.Graphene.Structs.Vec3#g:method:getXyz0"), [getXyz1]("GI.Graphene.Structs.Vec3#g:method:getXyz1"), [getXyzw]("GI.Graphene.Structs.Vec3#g:method:getXyzw"), [getY]("GI.Graphene.Structs.Vec3#g:method:getY"), [getZ]("GI.Graphene.Structs.Vec3#g:method:getZ").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveVec3Method                       ,
#endif

-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    Vec3AddMethodInfo                       ,
#endif
    vec3Add                                 ,


-- ** alloc #method:alloc#

    vec3Alloc                               ,


-- ** cross #method:cross#

#if defined(ENABLE_OVERLOADING)
    Vec3CrossMethodInfo                     ,
#endif
    vec3Cross                               ,


-- ** divide #method:divide#

#if defined(ENABLE_OVERLOADING)
    Vec3DivideMethodInfo                    ,
#endif
    vec3Divide                              ,


-- ** dot #method:dot#

#if defined(ENABLE_OVERLOADING)
    Vec3DotMethodInfo                       ,
#endif
    vec3Dot                                 ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    Vec3EqualMethodInfo                     ,
#endif
    vec3Equal                               ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    Vec3FreeMethodInfo                      ,
#endif
    vec3Free                                ,


-- ** getX #method:getX#

#if defined(ENABLE_OVERLOADING)
    Vec3GetXMethodInfo                      ,
#endif
    vec3GetX                                ,


-- ** getXy #method:getXy#

#if defined(ENABLE_OVERLOADING)
    Vec3GetXyMethodInfo                     ,
#endif
    vec3GetXy                               ,


-- ** getXy0 #method:getXy0#

#if defined(ENABLE_OVERLOADING)
    Vec3GetXy0MethodInfo                    ,
#endif
    vec3GetXy0                              ,


-- ** getXyz0 #method:getXyz0#

#if defined(ENABLE_OVERLOADING)
    Vec3GetXyz0MethodInfo                   ,
#endif
    vec3GetXyz0                             ,


-- ** getXyz1 #method:getXyz1#

#if defined(ENABLE_OVERLOADING)
    Vec3GetXyz1MethodInfo                   ,
#endif
    vec3GetXyz1                             ,


-- ** getXyzw #method:getXyzw#

#if defined(ENABLE_OVERLOADING)
    Vec3GetXyzwMethodInfo                   ,
#endif
    vec3GetXyzw                             ,


-- ** getY #method:getY#

#if defined(ENABLE_OVERLOADING)
    Vec3GetYMethodInfo                      ,
#endif
    vec3GetY                                ,


-- ** getZ #method:getZ#

#if defined(ENABLE_OVERLOADING)
    Vec3GetZMethodInfo                      ,
#endif
    vec3GetZ                                ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    Vec3InitMethodInfo                      ,
#endif
    vec3Init                                ,


-- ** initFromFloat #method:initFromFloat#

#if defined(ENABLE_OVERLOADING)
    Vec3InitFromFloatMethodInfo             ,
#endif
    vec3InitFromFloat                       ,


-- ** initFromVec3 #method:initFromVec3#

#if defined(ENABLE_OVERLOADING)
    Vec3InitFromVec3MethodInfo              ,
#endif
    vec3InitFromVec3                        ,


-- ** interpolate #method:interpolate#

#if defined(ENABLE_OVERLOADING)
    Vec3InterpolateMethodInfo               ,
#endif
    vec3Interpolate                         ,


-- ** length #method:length#

#if defined(ENABLE_OVERLOADING)
    Vec3LengthMethodInfo                    ,
#endif
    vec3Length                              ,


-- ** max #method:max#

#if defined(ENABLE_OVERLOADING)
    Vec3MaxMethodInfo                       ,
#endif
    vec3Max                                 ,


-- ** min #method:min#

#if defined(ENABLE_OVERLOADING)
    Vec3MinMethodInfo                       ,
#endif
    vec3Min                                 ,


-- ** multiply #method:multiply#

#if defined(ENABLE_OVERLOADING)
    Vec3MultiplyMethodInfo                  ,
#endif
    vec3Multiply                            ,


-- ** near #method:near#

#if defined(ENABLE_OVERLOADING)
    Vec3NearMethodInfo                      ,
#endif
    vec3Near                                ,


-- ** negate #method:negate#

#if defined(ENABLE_OVERLOADING)
    Vec3NegateMethodInfo                    ,
#endif
    vec3Negate                              ,


-- ** normalize #method:normalize#

#if defined(ENABLE_OVERLOADING)
    Vec3NormalizeMethodInfo                 ,
#endif
    vec3Normalize                           ,


-- ** one #method:one#

    vec3One                                 ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    Vec3ScaleMethodInfo                     ,
#endif
    vec3Scale                               ,


-- ** subtract #method:subtract#

#if defined(ENABLE_OVERLOADING)
    Vec3SubtractMethodInfo                  ,
#endif
    vec3Subtract                            ,


-- ** xAxis #method:xAxis#

    vec3XAxis                               ,


-- ** yAxis #method:yAxis#

    vec3YAxis                               ,


-- ** zAxis #method:zAxis#

    vec3ZAxis                               ,


-- ** zero #method:zero#

    vec3Zero                                ,




    ) where

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

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

import {-# SOURCE #-} qualified GI.Graphene.Structs.Vec2 as Graphene.Vec2
import {-# SOURCE #-} qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4

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

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

foreign import ccall "graphene_vec3_get_type" c_graphene_vec3_get_type :: 
    IO GType

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

instance B.Types.TypedObject Vec3 where
    glibType :: IO GType
glibType = IO GType
c_graphene_vec3_get_type

instance B.Types.GBoxed Vec3

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

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

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



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

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

foreign import ccall "graphene_vec3_alloc" graphene_vec3_alloc :: 
    IO (Ptr Vec3)

-- | Allocates a new t'GI.Graphene.Structs.Vec3.Vec3' structure.
-- 
-- The contents of the returned structure are undefined.
-- 
-- Use 'GI.Graphene.Structs.Vec3.vec3Init' to initialize the vector.
-- 
-- /Since: 1.0/
vec3Alloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec3
    -- ^ __Returns:__ the newly allocated t'GI.Graphene.Structs.Vec3.Vec3'
    --   structure. Use 'GI.Graphene.Structs.Vec3.vec3Free' to free the resources allocated
    --   by this function.
vec3Alloc :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec3
vec3Alloc  = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
result <- IO (Ptr Vec3)
graphene_vec3_alloc
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3Alloc" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Adds each component of the two given vectors.
-- 
-- /Since: 1.0/
vec3Add ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Add :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Add Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_add Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3AddMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3AddMethodInfo Vec3 signature where
    overloadedMethod = vec3Add

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


#endif

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

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

-- | Computes the cross product of the two given vectors.
-- 
-- /Since: 1.0/
vec3Cross ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Cross :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Cross Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_cross Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3CrossMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3CrossMethodInfo Vec3 signature where
    overloadedMethod = vec3Cross

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


#endif

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

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

-- | Divides each component of the first operand /@a@/ by the corresponding
-- component of the second operand /@b@/, and places the results into the
-- vector /@res@/.
-- 
-- /Since: 1.0/
vec3Divide ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Divide :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Divide Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_divide Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3DivideMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3DivideMethodInfo Vec3 signature where
    overloadedMethod = vec3Divide

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


#endif

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

foreign import ccall "graphene_vec3_dot" graphene_vec3_dot :: 
    Ptr Vec3 ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Vec3 ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO CFloat

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

#if defined(ENABLE_OVERLOADING)
data Vec3DotMethodInfo
instance (signature ~ (Vec3 -> m Float), MonadIO m) => O.OverloadedMethod Vec3DotMethodInfo Vec3 signature where
    overloadedMethod = vec3Dot

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


#endif

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

foreign import ccall "graphene_vec3_equal" graphene_vec3_equal :: 
    Ptr Vec3 ->                             -- v1 : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Vec3 ->                             -- v2 : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO CInt

-- | Checks whether the two given t'GI.Graphene.Structs.Vec3.Vec3' are equal.
-- 
-- /Since: 1.2/
vec3Equal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v1@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@v2@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m Bool
    -- ^ __Returns:__ @true@ if the two vectors are equal, and false otherwise
vec3Equal :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Bool
vec3Equal Vec3
v1 Vec3
v2 = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v1' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v1
    Ptr Vec3
v2' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v2
    CInt
result <- Ptr Vec3 -> Ptr Vec3 -> IO CInt
graphene_vec3_equal Ptr Vec3
v1' Ptr Vec3
v2'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v1
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v2
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data Vec3EqualMethodInfo
instance (signature ~ (Vec3 -> m Bool), MonadIO m) => O.OverloadedMethod Vec3EqualMethodInfo Vec3 signature where
    overloadedMethod = vec3Equal

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


#endif

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

foreign import ccall "graphene_vec3_free" graphene_vec3_free :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data Vec3FreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod Vec3FreeMethodInfo Vec3 signature where
    overloadedMethod = vec3Free

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


#endif

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

foreign import ccall "graphene_vec3_get_x" graphene_vec3_get_x :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO CFloat

-- | Retrieves the first component of the given vector /@v@/.
-- 
-- /Since: 1.0/
vec3GetX ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m Float
    -- ^ __Returns:__ the value of the first component of the vector
vec3GetX :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Float
vec3GetX Vec3
v = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    CFloat
result <- Ptr Vec3 -> IO CFloat
graphene_vec3_get_x Ptr Vec3
v'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data Vec3GetXMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec3GetXMethodInfo Vec3 signature where
    overloadedMethod = vec3GetX

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


#endif

-- method Vec3::get_xy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_vec2_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_vec3_get_xy" graphene_vec3_get_xy :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec2.Vec2 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

-- | Creates a t'GI.Graphene.Structs.Vec2.Vec2' that contains the first and second
-- components of the given t'GI.Graphene.Structs.Vec3.Vec3'.
-- 
-- /Since: 1.0/
vec3GetXy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Graphene.Vec2.Vec2)
vec3GetXy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Vec2
vec3GetXy Vec3
v = IO Vec2 -> m Vec2
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec2 -> m Vec2) -> IO Vec2 -> m Vec2
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec2.Vec2)
    Ptr Vec3 -> Ptr Vec2 -> IO ()
graphene_vec3_get_xy Ptr Vec3
v' Ptr Vec2
res
    Vec2
res' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec2 -> Vec2
Graphene.Vec2.Vec2) Ptr Vec2
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec2 -> IO Vec2
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec3GetXyMethodInfo
instance (signature ~ (m (Graphene.Vec2.Vec2)), MonadIO m) => O.OverloadedMethod Vec3GetXyMethodInfo Vec3 signature where
    overloadedMethod = vec3GetXy

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


#endif

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

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

-- | Creates a t'GI.Graphene.Structs.Vec3.Vec3' that contains the first two components of
-- the given t'GI.Graphene.Structs.Vec3.Vec3', and the third component set to 0.
-- 
-- /Since: 1.0/
vec3GetXy0 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3GetXy0 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Vec3
vec3GetXy0 Vec3
v = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_get_xy0 Ptr Vec3
v' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3GetXy0MethodInfo
instance (signature ~ (m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3GetXy0MethodInfo Vec3 signature where
    overloadedMethod = vec3GetXy0

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


#endif

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

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

-- | Converts a t'GI.Graphene.Structs.Vec3.Vec3' in a t'GI.Graphene.Structs.Vec4.Vec4' using 0.0
-- as the value for the fourth component of the resulting vector.
-- 
-- /Since: 1.0/
vec3GetXyz0 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Graphene.Vec4.Vec4)
vec3GetXyz0 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Vec4
vec3GetXyz0 Vec3
v = IO Vec4 -> m Vec4
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec4 -> m Vec4) -> IO Vec4 -> m Vec4
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr Vec4
res <- Int -> IO (Ptr Vec4)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec4.Vec4)
    Ptr Vec3 -> Ptr Vec4 -> IO ()
graphene_vec3_get_xyz0 Ptr Vec3
v' Ptr Vec4
res
    Vec4
res' <- ((ManagedPtr Vec4 -> Vec4) -> Ptr Vec4 -> IO Vec4
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec4 -> Vec4
Graphene.Vec4.Vec4) Ptr Vec4
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec4 -> IO Vec4
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
res'

#if defined(ENABLE_OVERLOADING)
data Vec3GetXyz0MethodInfo
instance (signature ~ (m (Graphene.Vec4.Vec4)), MonadIO m) => O.OverloadedMethod Vec3GetXyz0MethodInfo Vec3 signature where
    overloadedMethod = vec3GetXyz0

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


#endif

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

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

-- | Converts a t'GI.Graphene.Structs.Vec3.Vec3' in a t'GI.Graphene.Structs.Vec4.Vec4' using 1.0
-- as the value for the fourth component of the resulting vector.
-- 
-- /Since: 1.0/
vec3GetXyz1 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Graphene.Vec4.Vec4)
vec3GetXyz1 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Vec4
vec3GetXyz1 Vec3
v = IO Vec4 -> m Vec4
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec4 -> m Vec4) -> IO Vec4 -> m Vec4
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr Vec4
res <- Int -> IO (Ptr Vec4)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec4.Vec4)
    Ptr Vec3 -> Ptr Vec4 -> IO ()
graphene_vec3_get_xyz1 Ptr Vec3
v' Ptr Vec4
res
    Vec4
res' <- ((ManagedPtr Vec4 -> Vec4) -> Ptr Vec4 -> IO Vec4
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec4 -> Vec4
Graphene.Vec4.Vec4) Ptr Vec4
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec4 -> IO Vec4
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
res'

#if defined(ENABLE_OVERLOADING)
data Vec3GetXyz1MethodInfo
instance (signature ~ (m (Graphene.Vec4.Vec4)), MonadIO m) => O.OverloadedMethod Vec3GetXyz1MethodInfo Vec3 signature where
    overloadedMethod = vec3GetXyz1

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


#endif

-- method Vec3::get_xyzw
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "w"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value of the W component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_vec3_get_xyzw" graphene_vec3_get_xyzw :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    CFloat ->                               -- w : TBasicType TFloat
    Ptr Graphene.Vec4.Vec4 ->               -- res : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO ()

-- | Converts a t'GI.Graphene.Structs.Vec3.Vec3' in a t'GI.Graphene.Structs.Vec4.Vec4' using /@w@/ as
-- the value of the fourth component of the resulting vector.
-- 
-- /Since: 1.0/
vec3GetXyzw ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Float
    -- ^ /@w@/: the value of the W component
    -> m (Graphene.Vec4.Vec4)
vec3GetXyzw :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Float -> m Vec4
vec3GetXyzw Vec3
v Float
w = IO Vec4 -> m Vec4
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec4 -> m Vec4) -> IO Vec4 -> m Vec4
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    let w' :: CFloat
w' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
w
    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 Vec3 -> CFloat -> Ptr Vec4 -> IO ()
graphene_vec3_get_xyzw Ptr Vec3
v' CFloat
w' 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
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec4 -> IO Vec4
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
res'

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

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


#endif

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

foreign import ccall "graphene_vec3_get_y" graphene_vec3_get_y :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO CFloat

-- | Retrieves the second component of the given vector /@v@/.
-- 
-- /Since: 1.0/
vec3GetY ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m Float
    -- ^ __Returns:__ the value of the second component of the vector
vec3GetY :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Float
vec3GetY Vec3
v = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    CFloat
result <- Ptr Vec3 -> IO CFloat
graphene_vec3_get_y Ptr Vec3
v'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data Vec3GetYMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec3GetYMethodInfo Vec3 signature where
    overloadedMethod = vec3GetY

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


#endif

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

foreign import ccall "graphene_vec3_get_z" graphene_vec3_get_z :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO CFloat

-- | Retrieves the third component of the given vector /@v@/.
-- 
-- /Since: 1.0/
vec3GetZ ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m Float
    -- ^ __Returns:__ the value of the third component of the vector
vec3GetZ :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Float
vec3GetZ Vec3
v = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    CFloat
result <- Ptr Vec3 -> IO CFloat
graphene_vec3_get_z Ptr Vec3
v'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data Vec3GetZMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec3GetZMethodInfo Vec3 signature where
    overloadedMethod = vec3GetZ

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


#endif

-- method Vec3::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the X field of the vector"
--                 , 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 Y field of the vector"
--                 , 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 Z field of the vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Vec3" })
-- throws : False
-- Skip return : False

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

-- | Initializes a t'GI.Graphene.Structs.Vec3.Vec3' using the given values.
-- 
-- This function can be called multiple times.
-- 
-- /Since: 1.0/
vec3Init ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Float
    -- ^ /@x@/: the X field of the vector
    -> Float
    -- ^ /@y@/: the Y field of the vector
    -> Float
    -- ^ /@z@/: the Z field of the vector
    -> m Vec3
    -- ^ __Returns:__ a pointer to the initialized
    --   vector
vec3Init :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Float -> Float -> Float -> m Vec3
vec3Init Vec3
v Float
x Float
y Float
z = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    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 Vec3
result <- Ptr Vec3 -> CFloat -> CFloat -> CFloat -> IO (Ptr Vec3)
graphene_vec3_init Ptr Vec3
v' CFloat
x' CFloat
y' CFloat
z'
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3Init" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
data Vec3InitMethodInfo
instance (signature ~ (Float -> Float -> Float -> m Vec3), MonadIO m) => O.OverloadedMethod Vec3InitMethodInfo Vec3 signature where
    overloadedMethod = vec3Init

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


#endif

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

foreign import ccall "graphene_vec3_init_from_float" graphene_vec3_init_from_float :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr CFloat ->                           -- src : TCArray False 3 (-1) (TBasicType TFloat)
    IO (Ptr Vec3)

-- | Initializes a t'GI.Graphene.Structs.Vec3.Vec3' with the values from an array.
-- 
-- /Since: 1.0/
vec3InitFromFloat ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> [Float]
    -- ^ /@src@/: an array of 3 floating point values
    -> m Vec3
    -- ^ __Returns:__ the initialized vector
vec3InitFromFloat :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> [Float] -> m Vec3
vec3InitFromFloat Vec3
v [Float]
src = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr CFloat
src' <- ((Float -> CFloat) -> [Float] -> IO (Ptr CFloat)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac) [Float]
src
    Ptr Vec3
result <- Ptr Vec3 -> Ptr CFloat -> IO (Ptr Vec3)
graphene_vec3_init_from_float Ptr Vec3
v' Ptr CFloat
src'
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3InitFromFloat" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
src'
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

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

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


#endif

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

foreign import ccall "graphene_vec3_init_from_vec3" graphene_vec3_init_from_vec3 :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Vec3 ->                             -- src : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO (Ptr Vec3)

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

#if defined(ENABLE_OVERLOADING)
data Vec3InitFromVec3MethodInfo
instance (signature ~ (Vec3 -> m Vec3), MonadIO m) => O.OverloadedMethod Vec3InitFromVec3MethodInfo Vec3 signature where
    overloadedMethod = vec3InitFromVec3

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


#endif

-- method Vec3::interpolate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v1"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v2"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the interpolation factor"
--                 , 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 "the interpolated vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_vec3_interpolate" graphene_vec3_interpolate :: 
    Ptr Vec3 ->                             -- v1 : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Vec3 ->                             -- v2 : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    CDouble ->                              -- factor : TBasicType TDouble
    Ptr Vec3 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO ()

-- | Linearly interpolates /@v1@/ and /@v2@/ using the given /@factor@/.
-- 
-- /Since: 1.10/
vec3Interpolate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v1@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@v2@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Double
    -- ^ /@factor@/: the interpolation factor
    -> m (Vec3)
vec3Interpolate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> Double -> m Vec3
vec3Interpolate Vec3
v1 Vec3
v2 Double
factor = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v1' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v1
    Ptr Vec3
v2' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v2
    let factor' :: CDouble
factor' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
factor
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> CDouble -> Ptr Vec3 -> IO ()
graphene_vec3_interpolate Ptr Vec3
v1' Ptr Vec3
v2' CDouble
factor' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v1
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v2
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3InterpolateMethodInfo
instance (signature ~ (Vec3 -> Double -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3InterpolateMethodInfo Vec3 signature where
    overloadedMethod = vec3Interpolate

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


#endif

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

foreign import ccall "graphene_vec3_length" graphene_vec3_length :: 
    Ptr Vec3 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO CFloat

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

#if defined(ENABLE_OVERLOADING)
data Vec3LengthMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec3LengthMethodInfo Vec3 signature where
    overloadedMethod = vec3Length

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


#endif

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

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

-- | Compares each component of the two given vectors and creates a
-- vector that contains the maximum values.
-- 
-- /Since: 1.0/
vec3Max ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Max :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Max Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_max Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3MaxMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3MaxMethodInfo Vec3 signature where
    overloadedMethod = vec3Max

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


#endif

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

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

-- | Compares each component of the two given vectors and creates a
-- vector that contains the minimum values.
-- 
-- /Since: 1.0/
vec3Min ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Min :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Min Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_min Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3MinMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3MinMethodInfo Vec3 signature where
    overloadedMethod = vec3Min

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


#endif

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

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

-- | Multiplies each component of the two given vectors.
-- 
-- /Since: 1.0/
vec3Multiply ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Multiply :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Multiply Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_multiply Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3MultiplyMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3MultiplyMethodInfo Vec3 signature where
    overloadedMethod = vec3Multiply

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


#endif

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

-- | Compares the two given t'GI.Graphene.Structs.Vec3.Vec3' vectors and checks
-- whether their values are within the given /@epsilon@/.
-- 
-- /Since: 1.2/
vec3Near ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v1@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@v2@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Float
    -- ^ /@epsilon@/: the threshold between the two vectors
    -> m Bool
    -- ^ __Returns:__ @true@ if the two vectors are near each other
vec3Near :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> Float -> m Bool
vec3Near Vec3
v1 Vec3
v2 Float
epsilon = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v1' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v1
    Ptr Vec3
v2' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v2
    let epsilon' :: CFloat
epsilon' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
epsilon
    CInt
result <- Ptr Vec3 -> Ptr Vec3 -> CFloat -> IO CInt
graphene_vec3_near Ptr Vec3
v1' Ptr Vec3
v2' CFloat
epsilon'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v1
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v2
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data Vec3NearMethodInfo
instance (signature ~ (Vec3 -> Float -> m Bool), MonadIO m) => O.OverloadedMethod Vec3NearMethodInfo Vec3 signature where
    overloadedMethod = vec3Near

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


#endif

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

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

-- | Negates the given t'GI.Graphene.Structs.Vec3.Vec3'.
-- 
-- /Since: 1.2/
vec3Negate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Negate :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec3 -> m Vec3
vec3Negate Vec3
v = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_negate Ptr Vec3
v' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3NegateMethodInfo
instance (signature ~ (m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3NegateMethodInfo Vec3 signature where
    overloadedMethod = vec3Negate

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data Vec3NormalizeMethodInfo
instance (signature ~ (m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3NormalizeMethodInfo Vec3 signature where
    overloadedMethod = vec3Normalize

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


#endif

-- method Vec3::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec3_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scalar factor" , 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 the result vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Multiplies all components of the given vector with the given scalar /@factor@/.
-- 
-- /Since: 1.2/
vec3Scale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Float
    -- ^ /@factor@/: the scalar factor
    -> m (Vec3)
vec3Scale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Float -> m Vec3
vec3Scale Vec3
v Float
factor = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
v' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
v
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> CFloat -> Ptr Vec3 -> IO ()
graphene_vec3_scale Ptr Vec3
v' CFloat
factor' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
v
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3ScaleMethodInfo
instance (signature ~ (Float -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3ScaleMethodInfo Vec3 signature where
    overloadedMethod = vec3Scale

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


#endif

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

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

-- | Subtracts from each component of the first operand /@a@/ the
-- corresponding component of the second operand /@b@/ and places
-- each result into the components of /@res@/.
-- 
-- /Since: 1.0/
vec3Subtract ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec3
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> Vec3
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Vec3)
vec3Subtract :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec3 -> Vec3 -> m Vec3
vec3Subtract Vec3
a Vec3
b = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
a' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
a
    Ptr Vec3
b' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
b
    Ptr Vec3
res <- Int -> IO (Ptr Vec3)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec3)
    Ptr Vec3 -> Ptr Vec3 -> Ptr Vec3 -> IO ()
graphene_vec3_subtract Ptr Vec3
a' Ptr Vec3
b' Ptr Vec3
res
    Vec3
res' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
res
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
a
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
b
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
res'

#if defined(ENABLE_OVERLOADING)
data Vec3SubtractMethodInfo
instance (signature ~ (Vec3 -> m (Vec3)), MonadIO m) => O.OverloadedMethod Vec3SubtractMethodInfo Vec3 signature where
    overloadedMethod = vec3Subtract

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


#endif

-- XXX Could not generate method Vec3::to_float
-- Not implemented: Don't know how to allocate "dest" of type TCArray False 3 (-1) (TBasicType TFloat)
-- method Vec3::one
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Vec3" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_vec3_one" graphene_vec3_one :: 
    IO (Ptr Vec3)

-- | Provides a constant pointer to a vector with three components,
-- all sets to 1.
-- 
-- /Since: 1.0/
vec3One ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec3
    -- ^ __Returns:__ a constant vector
vec3One :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec3
vec3One  = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
result <- IO (Ptr Vec3)
graphene_vec3_one
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3One" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec3_x_axis" graphene_vec3_x_axis :: 
    IO (Ptr Vec3)

-- | Provides a constant pointer to a vector with three components
-- with values set to (1, 0, 0).
-- 
-- /Since: 1.0/
vec3XAxis ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec3
    -- ^ __Returns:__ a constant vector
vec3XAxis :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec3
vec3XAxis  = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
result <- IO (Ptr Vec3)
graphene_vec3_x_axis
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3XAxis" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec3_y_axis" graphene_vec3_y_axis :: 
    IO (Ptr Vec3)

-- | Provides a constant pointer to a vector with three components
-- with values set to (0, 1, 0).
-- 
-- /Since: 1.0/
vec3YAxis ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec3
    -- ^ __Returns:__ a constant vector
vec3YAxis :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec3
vec3YAxis  = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
result <- IO (Ptr Vec3)
graphene_vec3_y_axis
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3YAxis" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec3_z_axis" graphene_vec3_z_axis :: 
    IO (Ptr Vec3)

-- | Provides a constant pointer to a vector with three components
-- with values set to (0, 0, 1).
-- 
-- /Since: 1.0/
vec3ZAxis ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec3
    -- ^ __Returns:__ a constant vector
vec3ZAxis :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec3
vec3ZAxis  = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
result <- IO (Ptr Vec3)
graphene_vec3_z_axis
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3ZAxis" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec3_zero" graphene_vec3_zero :: 
    IO (Ptr Vec3)

-- | Provides a constant pointer to a vector with three components,
-- all sets to 0.
-- 
-- /Since: 1.0/
vec3Zero ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec3
    -- ^ __Returns:__ a constant vector
vec3Zero :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec3
vec3Zero  = IO Vec3 -> m Vec3
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vec3
result <- IO (Ptr Vec3)
graphene_vec3_zero
    Text -> Ptr Vec3 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec3Zero" Ptr Vec3
result
    Vec3
result' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec3 -> Vec3
Vec3) Ptr Vec3
result
    Vec3 -> IO Vec3
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveVec3Method (t :: Symbol) (o :: *) :: * where
    ResolveVec3Method "add" o = Vec3AddMethodInfo
    ResolveVec3Method "cross" o = Vec3CrossMethodInfo
    ResolveVec3Method "divide" o = Vec3DivideMethodInfo
    ResolveVec3Method "dot" o = Vec3DotMethodInfo
    ResolveVec3Method "equal" o = Vec3EqualMethodInfo
    ResolveVec3Method "free" o = Vec3FreeMethodInfo
    ResolveVec3Method "init" o = Vec3InitMethodInfo
    ResolveVec3Method "initFromFloat" o = Vec3InitFromFloatMethodInfo
    ResolveVec3Method "initFromVec3" o = Vec3InitFromVec3MethodInfo
    ResolveVec3Method "interpolate" o = Vec3InterpolateMethodInfo
    ResolveVec3Method "length" o = Vec3LengthMethodInfo
    ResolveVec3Method "max" o = Vec3MaxMethodInfo
    ResolveVec3Method "min" o = Vec3MinMethodInfo
    ResolveVec3Method "multiply" o = Vec3MultiplyMethodInfo
    ResolveVec3Method "near" o = Vec3NearMethodInfo
    ResolveVec3Method "negate" o = Vec3NegateMethodInfo
    ResolveVec3Method "normalize" o = Vec3NormalizeMethodInfo
    ResolveVec3Method "scale" o = Vec3ScaleMethodInfo
    ResolveVec3Method "subtract" o = Vec3SubtractMethodInfo
    ResolveVec3Method "getX" o = Vec3GetXMethodInfo
    ResolveVec3Method "getXy" o = Vec3GetXyMethodInfo
    ResolveVec3Method "getXy0" o = Vec3GetXy0MethodInfo
    ResolveVec3Method "getXyz0" o = Vec3GetXyz0MethodInfo
    ResolveVec3Method "getXyz1" o = Vec3GetXyz1MethodInfo
    ResolveVec3Method "getXyzw" o = Vec3GetXyzwMethodInfo
    ResolveVec3Method "getY" o = Vec3GetYMethodInfo
    ResolveVec3Method "getZ" o = Vec3GetZMethodInfo
    ResolveVec3Method l o = O.MethodResolutionFailed l o

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

#endif

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

#endif