{-# 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 two dimensions, x and y.
-- 
-- The contents of the t'GI.Graphene.Structs.Vec2.Vec2' 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.Vec2
    ( 

-- * Exported types
    Vec2(..)                                ,
    newZeroVec2                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveVec2Method                       ,
#endif

-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    Vec2AddMethodInfo                       ,
#endif
    vec2Add                                 ,


-- ** alloc #method:alloc#

    vec2Alloc                               ,


-- ** divide #method:divide#

#if defined(ENABLE_OVERLOADING)
    Vec2DivideMethodInfo                    ,
#endif
    vec2Divide                              ,


-- ** dot #method:dot#

#if defined(ENABLE_OVERLOADING)
    Vec2DotMethodInfo                       ,
#endif
    vec2Dot                                 ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    Vec2EqualMethodInfo                     ,
#endif
    vec2Equal                               ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    Vec2FreeMethodInfo                      ,
#endif
    vec2Free                                ,


-- ** getX #method:getX#

#if defined(ENABLE_OVERLOADING)
    Vec2GetXMethodInfo                      ,
#endif
    vec2GetX                                ,


-- ** getY #method:getY#

#if defined(ENABLE_OVERLOADING)
    Vec2GetYMethodInfo                      ,
#endif
    vec2GetY                                ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    Vec2InitMethodInfo                      ,
#endif
    vec2Init                                ,


-- ** initFromFloat #method:initFromFloat#

#if defined(ENABLE_OVERLOADING)
    Vec2InitFromFloatMethodInfo             ,
#endif
    vec2InitFromFloat                       ,


-- ** initFromVec2 #method:initFromVec2#

#if defined(ENABLE_OVERLOADING)
    Vec2InitFromVec2MethodInfo              ,
#endif
    vec2InitFromVec2                        ,


-- ** interpolate #method:interpolate#

#if defined(ENABLE_OVERLOADING)
    Vec2InterpolateMethodInfo               ,
#endif
    vec2Interpolate                         ,


-- ** length #method:length#

#if defined(ENABLE_OVERLOADING)
    Vec2LengthMethodInfo                    ,
#endif
    vec2Length                              ,


-- ** max #method:max#

#if defined(ENABLE_OVERLOADING)
    Vec2MaxMethodInfo                       ,
#endif
    vec2Max                                 ,


-- ** min #method:min#

#if defined(ENABLE_OVERLOADING)
    Vec2MinMethodInfo                       ,
#endif
    vec2Min                                 ,


-- ** multiply #method:multiply#

#if defined(ENABLE_OVERLOADING)
    Vec2MultiplyMethodInfo                  ,
#endif
    vec2Multiply                            ,


-- ** near #method:near#

#if defined(ENABLE_OVERLOADING)
    Vec2NearMethodInfo                      ,
#endif
    vec2Near                                ,


-- ** negate #method:negate#

#if defined(ENABLE_OVERLOADING)
    Vec2NegateMethodInfo                    ,
#endif
    vec2Negate                              ,


-- ** normalize #method:normalize#

#if defined(ENABLE_OVERLOADING)
    Vec2NormalizeMethodInfo                 ,
#endif
    vec2Normalize                           ,


-- ** one #method:one#

    vec2One                                 ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    Vec2ScaleMethodInfo                     ,
#endif
    vec2Scale                               ,


-- ** subtract #method:subtract#

#if defined(ENABLE_OVERLOADING)
    Vec2SubtractMethodInfo                  ,
#endif
    vec2Subtract                            ,


-- ** xAxis #method:xAxis#

    vec2XAxis                               ,


-- ** yAxis #method:yAxis#

    vec2YAxis                               ,


-- ** zero #method:zero#

    vec2Zero                                ,




    ) where

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

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


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

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

foreign import ccall "graphene_vec2_get_type" c_graphene_vec2_get_type :: 
    IO GType

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

instance B.Types.TypedObject Vec2 where
    glibType :: IO GType
glibType = IO GType
c_graphene_vec2_get_type

instance B.Types.GBoxed Vec2

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

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

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



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

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

foreign import ccall "graphene_vec2_alloc" graphene_vec2_alloc :: 
    IO (Ptr Vec2)

-- | Allocates a new t'GI.Graphene.Structs.Vec2.Vec2' structure.
-- 
-- The contents of the returned structure are undefined.
-- 
-- Use 'GI.Graphene.Structs.Vec2.vec2Init' to initialize the vector.
-- 
-- /Since: 1.0/
vec2Alloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec2
    -- ^ __Returns:__ the newly allocated t'GI.Graphene.Structs.Vec2.Vec2'
    --   structure. Use 'GI.Graphene.Structs.Vec2.vec2Free' to free the resources allocated
    --   by this function.
vec2Alloc :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec2
vec2Alloc  = IO Vec2 -> m Vec2
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 Vec2
result <- IO (Ptr Vec2)
graphene_vec2_alloc
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2Alloc" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Adds each component of the two passed vectors and places
-- each result into the components of /@res@/.
-- 
-- /Since: 1.0/
vec2Add ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Add :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2Add Vec2
a Vec2
b = IO Vec2 -> m Vec2
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 Vec2
a' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
a
    Ptr Vec2
b' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
b
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_add Ptr Vec2
a' Ptr Vec2
b' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
a
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
b
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2AddMethodInfo
instance (signature ~ (Vec2 -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2AddMethodInfo Vec2 signature where
    overloadedMethod = vec2Add

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


#endif

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

foreign import ccall "graphene_vec2_divide" graphene_vec2_divide :: 
    Ptr Vec2 ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    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/
vec2Divide ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Divide :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2Divide Vec2
a Vec2
b = IO Vec2 -> m Vec2
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 Vec2
a' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
a
    Ptr Vec2
b' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
b
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_divide Ptr Vec2
a' Ptr Vec2
b' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
a
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
b
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2DivideMethodInfo
instance (signature ~ (Vec2 -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2DivideMethodInfo Vec2 signature where
    overloadedMethod = vec2Divide

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data Vec2DotMethodInfo
instance (signature ~ (Vec2 -> m Float), MonadIO m) => O.OverloadedMethod Vec2DotMethodInfo Vec2 signature where
    overloadedMethod = vec2Dot

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data Vec2EqualMethodInfo
instance (signature ~ (Vec2 -> m Bool), MonadIO m) => O.OverloadedMethod Vec2EqualMethodInfo Vec2 signature where
    overloadedMethod = vec2Equal

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


#endif

-- method Vec2::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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_vec2_free" graphene_vec2_free :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data Vec2FreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod Vec2FreeMethodInfo Vec2 signature where
    overloadedMethod = vec2Free

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


#endif

-- method Vec2::get_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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_vec2_get_x" graphene_vec2_get_x :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO CFloat

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

#if defined(ENABLE_OVERLOADING)
data Vec2GetXMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec2GetXMethodInfo Vec2 signature where
    overloadedMethod = vec2GetX

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


#endif

-- method Vec2::get_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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_vec2_get_y" graphene_vec2_get_y :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO CFloat

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

#if defined(ENABLE_OVERLOADING)
data Vec2GetYMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec2GetYMethodInfo Vec2 signature where
    overloadedMethod = vec2GetY

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


#endif

-- method Vec2::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Vec2" })
-- throws : False
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
data Vec2InitMethodInfo
instance (signature ~ (Float -> Float -> m Vec2), MonadIO m) => O.OverloadedMethod Vec2InitMethodInfo Vec2 signature where
    overloadedMethod = vec2Init

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


#endif

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

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

-- | Initializes /@v@/ with the contents of the given array.
-- 
-- /Since: 1.0/
vec2InitFromFloat ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> [Float]
    -- ^ /@src@/: an array of floating point values
    --   with at least two elements
    -> m Vec2
    -- ^ __Returns:__ the initialized vector
vec2InitFromFloat :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> [Float] -> m Vec2
vec2InitFromFloat Vec2
v [Float]
src = IO Vec2 -> m Vec2
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 Vec2
v' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
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 Vec2
result <- Ptr Vec2 -> Ptr CFloat -> IO (Ptr Vec2)
graphene_vec2_init_from_float Ptr Vec2
v' Ptr CFloat
src'
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2InitFromFloat" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
src'
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

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

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


#endif

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

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

-- | Copies the contents of /@src@/ into /@v@/.
-- 
-- /Since: 1.0/
vec2InitFromVec2 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@src@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m Vec2
    -- ^ __Returns:__ the initialized vector
vec2InitFromVec2 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2InitFromVec2 Vec2
v Vec2
src = IO Vec2 -> m Vec2
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 Vec2
v' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
v
    Ptr Vec2
src' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
src
    Ptr Vec2
result <- Ptr Vec2 -> Ptr Vec2 -> IO (Ptr Vec2)
graphene_vec2_init_from_vec2 Ptr Vec2
v' Ptr Vec2
src'
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2InitFromVec2" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
src
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

#if defined(ENABLE_OVERLOADING)
data Vec2InitFromVec2MethodInfo
instance (signature ~ (Vec2 -> m Vec2), MonadIO m) => O.OverloadedMethod Vec2InitFromVec2MethodInfo Vec2 signature where
    overloadedMethod = vec2InitFromVec2

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


#endif

-- method Vec2::interpolate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v1"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v2"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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 = "Vec2" }
--           , 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_vec2_interpolate" graphene_vec2_interpolate :: 
    Ptr Vec2 ->                             -- v1 : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- v2 : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    CDouble ->                              -- factor : TBasicType TDouble
    Ptr Vec2 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

-- | Linearly interpolates /@v1@/ and /@v2@/ using the given /@factor@/.
-- 
-- /Since: 1.10/
vec2Interpolate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@v1@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@v2@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Double
    -- ^ /@factor@/: the interpolation factor
    -> m (Vec2)
vec2Interpolate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> Double -> m Vec2
vec2Interpolate Vec2
v1 Vec2
v2 Double
factor = IO Vec2 -> m Vec2
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 Vec2
v1' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
v1
    Ptr Vec2
v2' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
v2
    let factor' :: CDouble
factor' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
factor
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> CDouble -> Ptr Vec2 -> IO ()
graphene_vec2_interpolate Ptr Vec2
v1' Ptr Vec2
v2' CDouble
factor' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v1
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v2
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2InterpolateMethodInfo
instance (signature ~ (Vec2 -> Double -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2InterpolateMethodInfo Vec2 signature where
    overloadedMethod = vec2Interpolate

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


#endif

-- method Vec2::length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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_vec2_length" graphene_vec2_length :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO CFloat

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

#if defined(ENABLE_OVERLOADING)
data Vec2LengthMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod Vec2LengthMethodInfo Vec2 signature where
    overloadedMethod = vec2Length

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


#endif

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

-- | Compares the two given vectors and places the maximum
-- values of each component into /@res@/.
-- 
-- /Since: 1.0/
vec2Max ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Max :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2Max Vec2
a Vec2
b = IO Vec2 -> m Vec2
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 Vec2
a' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
a
    Ptr Vec2
b' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
b
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_max Ptr Vec2
a' Ptr Vec2
b' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
a
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
b
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2MaxMethodInfo
instance (signature ~ (Vec2 -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2MaxMethodInfo Vec2 signature where
    overloadedMethod = vec2Max

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


#endif

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

-- | Compares the two given vectors and places the minimum
-- values of each component into /@res@/.
-- 
-- /Since: 1.0/
vec2Min ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Min :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2Min Vec2
a Vec2
b = IO Vec2 -> m Vec2
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 Vec2
a' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
a
    Ptr Vec2
b' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
b
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_min Ptr Vec2
a' Ptr Vec2
b' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
a
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
b
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2MinMethodInfo
instance (signature ~ (Vec2 -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2MinMethodInfo Vec2 signature where
    overloadedMethod = vec2Min

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


#endif

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

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

-- | Multiplies each component of the two passed vectors and places
-- each result into the components of /@res@/.
-- 
-- /Since: 1.0/
vec2Multiply ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Multiply :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2Multiply Vec2
a Vec2
b = IO Vec2 -> m Vec2
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 Vec2
a' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
a
    Ptr Vec2
b' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
b
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_multiply Ptr Vec2
a' Ptr Vec2
b' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
a
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
b
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2MultiplyMethodInfo
instance (signature ~ (Vec2 -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2MultiplyMethodInfo Vec2 signature where
    overloadedMethod = vec2Multiply

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data Vec2NearMethodInfo
instance (signature ~ (Vec2 -> Float -> m Bool), MonadIO m) => O.OverloadedMethod Vec2NearMethodInfo Vec2 signature where
    overloadedMethod = vec2Near

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


#endif

-- method Vec2::negate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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 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_vec2_negate" graphene_vec2_negate :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

-- | Negates the given t'GI.Graphene.Structs.Vec2.Vec2'.
-- 
-- /Since: 1.2/
vec2Negate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Negate :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec2 -> m Vec2
vec2Negate Vec2
v = IO Vec2 -> m Vec2
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 Vec2
v' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
v
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_negate Ptr Vec2
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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2NegateMethodInfo
instance (signature ~ (m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2NegateMethodInfo Vec2 signature where
    overloadedMethod = vec2Negate

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


#endif

-- method Vec2::normalize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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 the\n  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_vec2_normalize" graphene_vec2_normalize :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

-- | Computes the normalized vector for the given vector /@v@/.
-- 
-- /Since: 1.0/
vec2Normalize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Normalize :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Vec2 -> m Vec2
vec2Normalize Vec2
v = IO Vec2 -> m Vec2
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 Vec2
v' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
v
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_normalize Ptr Vec2
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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2NormalizeMethodInfo
instance (signature ~ (m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2NormalizeMethodInfo Vec2 signature where
    overloadedMethod = vec2Normalize

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


#endif

-- method Vec2::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_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 = "Vec2" }
--           , 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_vec2_scale" graphene_vec2_scale :: 
    Ptr Vec2 ->                             -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    CFloat ->                               -- factor : TBasicType TFloat
    Ptr Vec2 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

-- | Multiplies all components of the given vector with the given scalar /@factor@/.
-- 
-- /Since: 1.2/
vec2Scale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@v@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Float
    -- ^ /@factor@/: the scalar factor
    -> m (Vec2)
vec2Scale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Float -> m Vec2
vec2Scale Vec2
v Float
factor = IO Vec2 -> m Vec2
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 Vec2
v' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
v
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> CFloat -> Ptr Vec2 -> IO ()
graphene_vec2_scale Ptr Vec2
v' CFloat
factor' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
v
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2ScaleMethodInfo
instance (signature ~ (Float -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2ScaleMethodInfo Vec2 signature where
    overloadedMethod = vec2Scale

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


#endif

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

foreign import ccall "graphene_vec2_subtract" graphene_vec2_subtract :: 
    Ptr Vec2 ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    Ptr Vec2 ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    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/
vec2Subtract ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Vec2
    -- ^ /@a@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> Vec2
    -- ^ /@b@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m (Vec2)
vec2Subtract :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Vec2 -> Vec2 -> m Vec2
vec2Subtract Vec2
a Vec2
b = IO Vec2 -> m Vec2
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 Vec2
a' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
a
    Ptr Vec2
b' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
b
    Ptr Vec2
res <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Vec2)
    Ptr Vec2 -> Ptr Vec2 -> Ptr Vec2 -> IO ()
graphene_vec2_subtract Ptr Vec2
a' Ptr Vec2
b' 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
Vec2) Ptr Vec2
res
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
a
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
b
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
res'

#if defined(ENABLE_OVERLOADING)
data Vec2SubtractMethodInfo
instance (signature ~ (Vec2 -> m (Vec2)), MonadIO m) => O.OverloadedMethod Vec2SubtractMethodInfo Vec2 signature where
    overloadedMethod = vec2Subtract

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


#endif

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

foreign import ccall "graphene_vec2_one" graphene_vec2_one :: 
    IO (Ptr Vec2)

-- | Retrieves a constant vector with (1, 1) components.
-- 
-- /Since: 1.0/
vec2One ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec2
    -- ^ __Returns:__ the one vector
vec2One :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec2
vec2One  = IO Vec2 -> m Vec2
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 Vec2
result <- IO (Ptr Vec2)
graphene_vec2_one
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2One" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec2_x_axis" graphene_vec2_x_axis :: 
    IO (Ptr Vec2)

-- | Retrieves a constant vector with (1, 0) components.
-- 
-- /Since: 1.0/
vec2XAxis ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec2
    -- ^ __Returns:__ the X axis vector
vec2XAxis :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec2
vec2XAxis  = IO Vec2 -> m Vec2
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 Vec2
result <- IO (Ptr Vec2)
graphene_vec2_x_axis
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2XAxis" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec2_y_axis" graphene_vec2_y_axis :: 
    IO (Ptr Vec2)

-- | Retrieves a constant vector with (0, 1) components.
-- 
-- /Since: 1.0/
vec2YAxis ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec2
    -- ^ __Returns:__ the Y axis vector
vec2YAxis :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec2
vec2YAxis  = IO Vec2 -> m Vec2
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 Vec2
result <- IO (Ptr Vec2)
graphene_vec2_y_axis
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2YAxis" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_vec2_zero" graphene_vec2_zero :: 
    IO (Ptr Vec2)

-- | Retrieves a constant vector with (0, 0) components.
-- 
-- /Since: 1.0/
vec2Zero ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vec2
    -- ^ __Returns:__ the zero vector
vec2Zero :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vec2
vec2Zero  = IO Vec2 -> m Vec2
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 Vec2
result <- IO (Ptr Vec2)
graphene_vec2_zero
    Text -> Ptr Vec2 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vec2Zero" Ptr Vec2
result
    Vec2
result' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec2 -> Vec2
Vec2) Ptr Vec2
result
    Vec2 -> IO Vec2
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveVec2Method (t :: Symbol) (o :: *) :: * where
    ResolveVec2Method "add" o = Vec2AddMethodInfo
    ResolveVec2Method "divide" o = Vec2DivideMethodInfo
    ResolveVec2Method "dot" o = Vec2DotMethodInfo
    ResolveVec2Method "equal" o = Vec2EqualMethodInfo
    ResolveVec2Method "free" o = Vec2FreeMethodInfo
    ResolveVec2Method "init" o = Vec2InitMethodInfo
    ResolveVec2Method "initFromFloat" o = Vec2InitFromFloatMethodInfo
    ResolveVec2Method "initFromVec2" o = Vec2InitFromVec2MethodInfo
    ResolveVec2Method "interpolate" o = Vec2InterpolateMethodInfo
    ResolveVec2Method "length" o = Vec2LengthMethodInfo
    ResolveVec2Method "max" o = Vec2MaxMethodInfo
    ResolveVec2Method "min" o = Vec2MinMethodInfo
    ResolveVec2Method "multiply" o = Vec2MultiplyMethodInfo
    ResolveVec2Method "near" o = Vec2NearMethodInfo
    ResolveVec2Method "negate" o = Vec2NegateMethodInfo
    ResolveVec2Method "normalize" o = Vec2NormalizeMethodInfo
    ResolveVec2Method "scale" o = Vec2ScaleMethodInfo
    ResolveVec2Method "subtract" o = Vec2SubtractMethodInfo
    ResolveVec2Method "getX" o = Vec2GetXMethodInfo
    ResolveVec2Method "getY" o = Vec2GetYMethodInfo
    ResolveVec2Method l o = O.MethodResolutionFailed l o

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

#endif

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

#endif