{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A 3D box, described as the volume between a minimum and
-- a maximum vertices.
-- 
-- /Since: 1.2/

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

module GI.Graphene.Structs.Box
    ( 

-- * Exported types
    Box(..)                                 ,
    newZeroBox                              ,
    noBox                                   ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveBoxMethod                        ,
#endif


-- ** alloc #method:alloc#

    boxAlloc                                ,


-- ** containsBox #method:containsBox#

#if defined(ENABLE_OVERLOADING)
    BoxContainsBoxMethodInfo                ,
#endif
    boxContainsBox                          ,


-- ** containsPoint #method:containsPoint#

#if defined(ENABLE_OVERLOADING)
    BoxContainsPointMethodInfo              ,
#endif
    boxContainsPoint                        ,


-- ** empty #method:empty#

    boxEmpty                                ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    BoxEqualMethodInfo                      ,
#endif
    boxEqual                                ,


-- ** expand #method:expand#

#if defined(ENABLE_OVERLOADING)
    BoxExpandMethodInfo                     ,
#endif
    boxExpand                               ,


-- ** expandScalar #method:expandScalar#

#if defined(ENABLE_OVERLOADING)
    BoxExpandScalarMethodInfo               ,
#endif
    boxExpandScalar                         ,


-- ** expandVec3 #method:expandVec3#

#if defined(ENABLE_OVERLOADING)
    BoxExpandVec3MethodInfo                 ,
#endif
    boxExpandVec3                           ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    BoxFreeMethodInfo                       ,
#endif
    boxFree                                 ,


-- ** getBoundingSphere #method:getBoundingSphere#

#if defined(ENABLE_OVERLOADING)
    BoxGetBoundingSphereMethodInfo          ,
#endif
    boxGetBoundingSphere                    ,


-- ** getCenter #method:getCenter#

#if defined(ENABLE_OVERLOADING)
    BoxGetCenterMethodInfo                  ,
#endif
    boxGetCenter                            ,


-- ** getDepth #method:getDepth#

#if defined(ENABLE_OVERLOADING)
    BoxGetDepthMethodInfo                   ,
#endif
    boxGetDepth                             ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    BoxGetHeightMethodInfo                  ,
#endif
    boxGetHeight                            ,


-- ** getMax #method:getMax#

#if defined(ENABLE_OVERLOADING)
    BoxGetMaxMethodInfo                     ,
#endif
    boxGetMax                               ,


-- ** getMin #method:getMin#

#if defined(ENABLE_OVERLOADING)
    BoxGetMinMethodInfo                     ,
#endif
    boxGetMin                               ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    BoxGetSizeMethodInfo                    ,
#endif
    boxGetSize                              ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    BoxGetWidthMethodInfo                   ,
#endif
    boxGetWidth                             ,


-- ** infinite #method:infinite#

    boxInfinite                             ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    BoxInitMethodInfo                       ,
#endif
    boxInit                                 ,


-- ** initFromBox #method:initFromBox#

#if defined(ENABLE_OVERLOADING)
    BoxInitFromBoxMethodInfo                ,
#endif
    boxInitFromBox                          ,


-- ** initFromPoints #method:initFromPoints#

#if defined(ENABLE_OVERLOADING)
    BoxInitFromPointsMethodInfo             ,
#endif
    boxInitFromPoints                       ,


-- ** initFromVec3 #method:initFromVec3#

#if defined(ENABLE_OVERLOADING)
    BoxInitFromVec3MethodInfo               ,
#endif
    boxInitFromVec3                         ,


-- ** initFromVectors #method:initFromVectors#

#if defined(ENABLE_OVERLOADING)
    BoxInitFromVectorsMethodInfo            ,
#endif
    boxInitFromVectors                      ,


-- ** intersection #method:intersection#

#if defined(ENABLE_OVERLOADING)
    BoxIntersectionMethodInfo               ,
#endif
    boxIntersection                         ,


-- ** minusOne #method:minusOne#

    boxMinusOne                             ,


-- ** one #method:one#

    boxOne                                  ,


-- ** oneMinusOne #method:oneMinusOne#

    boxOneMinusOne                          ,


-- ** union #method:union#

#if defined(ENABLE_OVERLOADING)
    BoxUnionMethodInfo                      ,
#endif
    boxUnion                                ,


-- ** zero #method:zero#

    boxZero                                 ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import {-# SOURCE #-} qualified GI.Graphene.Structs.Sphere as Graphene.Sphere
import {-# SOURCE #-} qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3

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

instance BoxedObject Box where
    boxedType :: Box -> IO GType
boxedType _ = IO GType
c_graphene_box_get_type

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `Box`.
noBox :: Maybe Box
noBox :: Maybe Box
noBox = Maybe Box
forall a. Maybe a
Nothing


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

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

foreign import ccall "graphene_box_alloc" graphene_box_alloc :: 
    IO (Ptr Box)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Checks whether the t'GI.Graphene.Structs.Box.Box' /@a@/ contains the given
-- t'GI.Graphene.Structs.Box.Box' /@b@/.
-- 
-- /Since: 1.2/
boxContainsBox ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@a@/: a t'GI.Graphene.Structs.Box.Box'
    -> Box
    -- ^ /@b@/: a t'GI.Graphene.Structs.Box.Box'
    -> m Bool
    -- ^ __Returns:__ @true@ if the box is contained in the given box
boxContainsBox :: Box -> Box -> m Bool
boxContainsBox a :: Box
a b :: Box
b = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
a' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
a
    Ptr Box
b' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
b
    CInt
result <- Ptr Box -> Ptr Box -> IO CInt
graphene_box_contains_box Ptr Box
a' Ptr Box
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
a
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
b
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BoxContainsBoxMethodInfo
instance (signature ~ (Box -> m Bool), MonadIO m) => O.MethodInfo BoxContainsBoxMethodInfo Box signature where
    overloadedMethod = boxContainsBox

#endif

-- method Box::contains_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the coordinates to check"
--                 , 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_box_contains_point" graphene_box_contains_point :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Point3D.Point3D ->         -- point : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO CInt

-- | Checks whether /@box@/ contains the given /@point@/.
-- 
-- /Since: 1.2/
boxContainsPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> Graphene.Point3D.Point3D
    -- ^ /@point@/: the coordinates to check
    -> m Bool
    -- ^ __Returns:__ @true@ if the point is contained in the given box
boxContainsPoint :: Box -> Point3D -> m Bool
boxContainsPoint box :: Box
box point :: Point3D
point = 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 Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Point3D
point' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
point
    CInt
result <- Ptr Box -> Ptr Point3D -> IO CInt
graphene_box_contains_point Ptr Box
box' Ptr Point3D
point'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
point
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BoxContainsPointMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m Bool), MonadIO m) => O.MethodInfo BoxContainsPointMethodInfo Box signature where
    overloadedMethod = boxContainsPoint

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data BoxEqualMethodInfo
instance (signature ~ (Box -> m Bool), MonadIO m) => O.MethodInfo BoxEqualMethodInfo Box signature where
    overloadedMethod = boxEqual

#endif

-- method Box::expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "point"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the coordinates of the point to include"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the expanded box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_expand" graphene_box_expand :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Point3D.Point3D ->         -- point : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    Ptr Box ->                              -- res : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO ()

-- | Expands the dimensions of /@box@/ to include the coordinates at /@point@/.
-- 
-- /Since: 1.2/
boxExpand ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> Graphene.Point3D.Point3D
    -- ^ /@point@/: the coordinates of the point to include
    -> m (Box)
boxExpand :: Box -> Point3D -> m Box
boxExpand box :: Box
box point :: Point3D
point = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Point3D
point' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
point
    Ptr Box
res <- Int -> IO (Ptr Box)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Box)
    Ptr Box -> Ptr Point3D -> Ptr Box -> IO ()
graphene_box_expand Ptr Box
box' Ptr Point3D
point' Ptr Box
res
    Box
res' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Box -> Box
Box) Ptr Box
res
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
point
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
res'

#if defined(ENABLE_OVERLOADING)
data BoxExpandMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m (Box)), MonadIO m) => O.MethodInfo BoxExpandMethodInfo Box signature where
    overloadedMethod = boxExpand

#endif

-- method Box::expand_scalar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scalar"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a scalar value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the expanded box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_expand_scalar" graphene_box_expand_scalar :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    CFloat ->                               -- scalar : TBasicType TFloat
    Ptr Box ->                              -- res : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO ()

-- | Expands the dimensions of /@box@/ by the given /@scalar@/ value.
-- 
-- If /@scalar@/ is positive, the t'GI.Graphene.Structs.Box.Box' will grow; if /@scalar@/ is
-- negative, the t'GI.Graphene.Structs.Box.Box' will shrink.
-- 
-- /Since: 1.2/
boxExpandScalar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> Float
    -- ^ /@scalar@/: a scalar value
    -> m (Box)
boxExpandScalar :: Box -> Float -> m Box
boxExpandScalar box :: Box
box scalar :: Float
scalar = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    let scalar' :: CFloat
scalar' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
scalar
    Ptr Box
res <- Int -> IO (Ptr Box)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Box)
    Ptr Box -> CFloat -> Ptr Box -> IO ()
graphene_box_expand_scalar Ptr Box
box' CFloat
scalar' Ptr Box
res
    Box
res' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Box -> Box
Box) Ptr Box
res
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
res'

#if defined(ENABLE_OVERLOADING)
data BoxExpandScalarMethodInfo
instance (signature ~ (Float -> m (Box)), MonadIO m) => O.MethodInfo BoxExpandScalarMethodInfo Box signature where
    overloadedMethod = boxExpandScalar

#endif

-- method Box::expand_vec3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vec"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the coordinates of the point to include, as a #graphene_vec3_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the expanded box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_expand_vec3" graphene_box_expand_vec3 :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Vec3.Vec3 ->               -- vec : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Box ->                              -- res : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO ()

-- | Expands the dimensions of /@box@/ to include the coordinates of the
-- given vector.
-- 
-- /Since: 1.2/
boxExpandVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> Graphene.Vec3.Vec3
    -- ^ /@vec@/: the coordinates of the point to include, as a t'GI.Graphene.Structs.Vec3.Vec3'
    -> m (Box)
boxExpandVec3 :: Box -> Vec3 -> m Box
boxExpandVec3 box :: Box
box vec :: Vec3
vec = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Vec3
vec' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
vec
    Ptr Box
res <- Int -> IO (Ptr Box)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Box)
    Ptr Box -> Ptr Vec3 -> Ptr Box -> IO ()
graphene_box_expand_vec3 Ptr Box
box' Ptr Vec3
vec' Ptr Box
res
    Box
res' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Box -> Box
Box) Ptr Box
res
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
vec
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
res'

#if defined(ENABLE_OVERLOADING)
data BoxExpandVec3MethodInfo
instance (signature ~ (Graphene.Vec3.Vec3 -> m (Box)), MonadIO m) => O.MethodInfo BoxExpandVec3MethodInfo Box signature where
    overloadedMethod = boxExpandVec3

#endif

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

foreign import ccall "graphene_box_free" graphene_box_free :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO ()

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

#if defined(ENABLE_OVERLOADING)
data BoxFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo BoxFreeMethodInfo Box signature where
    overloadedMethod = boxFree

#endif

-- method Box::get_bounding_sphere
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sphere"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Sphere" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the bounding sphere"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_get_bounding_sphere" graphene_box_get_bounding_sphere :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Sphere.Sphere ->           -- sphere : TInterface (Name {namespace = "Graphene", name = "Sphere"})
    IO ()

-- | Computes the bounding t'GI.Graphene.Structs.Sphere.Sphere' capable of containing the given
-- t'GI.Graphene.Structs.Box.Box'.
-- 
-- /Since: 1.2/
boxGetBoundingSphere ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m (Graphene.Sphere.Sphere)
boxGetBoundingSphere :: Box -> m Sphere
boxGetBoundingSphere box :: Box
box = IO Sphere -> m Sphere
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Sphere -> m Sphere) -> IO Sphere -> m Sphere
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Sphere
sphere <- Int -> IO (Ptr Sphere)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 20 :: IO (Ptr Graphene.Sphere.Sphere)
    Ptr Box -> Ptr Sphere -> IO ()
graphene_box_get_bounding_sphere Ptr Box
box' Ptr Sphere
sphere
    Sphere
sphere' <- ((ManagedPtr Sphere -> Sphere) -> Ptr Sphere -> IO Sphere
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Sphere -> Sphere
Graphene.Sphere.Sphere) Ptr Sphere
sphere
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Sphere -> IO Sphere
forall (m :: * -> *) a. Monad m => a -> m a
return Sphere
sphere'

#if defined(ENABLE_OVERLOADING)
data BoxGetBoundingSphereMethodInfo
instance (signature ~ (m (Graphene.Sphere.Sphere)), MonadIO m) => O.MethodInfo BoxGetBoundingSphereMethodInfo Box signature where
    overloadedMethod = boxGetBoundingSphere

#endif

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

foreign import ccall "graphene_box_get_center" graphene_box_get_center :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Point3D.Point3D ->         -- center : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO ()

-- | Retrieves the coordinates of the center of a t'GI.Graphene.Structs.Box.Box'.
-- 
-- /Since: 1.2/
boxGetCenter ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m (Graphene.Point3D.Point3D)
boxGetCenter :: Box -> m Point3D
boxGetCenter box :: Box
box = IO Point3D -> m Point3D
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point3D -> m Point3D) -> IO Point3D -> m Point3D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Point3D
center <- Int -> IO (Ptr Point3D)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 12 :: IO (Ptr Graphene.Point3D.Point3D)
    Ptr Box -> Ptr Point3D -> IO ()
graphene_box_get_center Ptr Box
box' Ptr Point3D
center
    Point3D
center' <- ((ManagedPtr Point3D -> Point3D) -> Ptr Point3D -> IO Point3D
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point3D -> Point3D
Graphene.Point3D.Point3D) Ptr Point3D
center
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Point3D -> IO Point3D
forall (m :: * -> *) a. Monad m => a -> m a
return Point3D
center'

#if defined(ENABLE_OVERLOADING)
data BoxGetCenterMethodInfo
instance (signature ~ (m (Graphene.Point3D.Point3D)), MonadIO m) => O.MethodInfo BoxGetCenterMethodInfo Box signature where
    overloadedMethod = boxGetCenter

#endif

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

foreign import ccall "graphene_box_get_depth" graphene_box_get_depth :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO CFloat

-- | Retrieves the size of the /@box@/ on the Z axis.
-- 
-- /Since: 1.2/
boxGetDepth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m Float
    -- ^ __Returns:__ the depth of the box
boxGetDepth :: Box -> m Float
boxGetDepth box :: Box
box = 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 Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    CFloat
result <- Ptr Box -> IO CFloat
graphene_box_get_depth Ptr Box
box'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data BoxGetDepthMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo BoxGetDepthMethodInfo Box signature where
    overloadedMethod = boxGetDepth

#endif

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

foreign import ccall "graphene_box_get_height" graphene_box_get_height :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO CFloat

-- | Retrieves the size of the /@box@/ on the Y axis.
-- 
-- /Since: 1.2/
boxGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m Float
    -- ^ __Returns:__ the height of the box
boxGetHeight :: Box -> m Float
boxGetHeight box :: Box
box = 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 Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    CFloat
result <- Ptr Box -> IO CFloat
graphene_box_get_height Ptr Box
box'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data BoxGetHeightMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo BoxGetHeightMethodInfo Box signature where
    overloadedMethod = boxGetHeight

#endif

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

foreign import ccall "graphene_box_get_max" graphene_box_get_max :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Point3D.Point3D ->         -- max : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO ()

-- | Retrieves the coordinates of the maximum point of the given
-- t'GI.Graphene.Structs.Box.Box'.
-- 
-- /Since: 1.2/
boxGetMax ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m (Graphene.Point3D.Point3D)
boxGetMax :: Box -> m Point3D
boxGetMax box :: Box
box = IO Point3D -> m Point3D
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point3D -> m Point3D) -> IO Point3D -> m Point3D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Point3D
max <- Int -> IO (Ptr Point3D)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 12 :: IO (Ptr Graphene.Point3D.Point3D)
    Ptr Box -> Ptr Point3D -> IO ()
graphene_box_get_max Ptr Box
box' Ptr Point3D
max
    Point3D
max' <- ((ManagedPtr Point3D -> Point3D) -> Ptr Point3D -> IO Point3D
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point3D -> Point3D
Graphene.Point3D.Point3D) Ptr Point3D
max
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Point3D -> IO Point3D
forall (m :: * -> *) a. Monad m => a -> m a
return Point3D
max'

#if defined(ENABLE_OVERLOADING)
data BoxGetMaxMethodInfo
instance (signature ~ (m (Graphene.Point3D.Point3D)), MonadIO m) => O.MethodInfo BoxGetMaxMethodInfo Box signature where
    overloadedMethod = boxGetMax

#endif

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

foreign import ccall "graphene_box_get_min" graphene_box_get_min :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Point3D.Point3D ->         -- min : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO ()

-- | Retrieves the coordinates of the minimum point of the given
-- t'GI.Graphene.Structs.Box.Box'.
-- 
-- /Since: 1.2/
boxGetMin ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m (Graphene.Point3D.Point3D)
boxGetMin :: Box -> m Point3D
boxGetMin box :: Box
box = IO Point3D -> m Point3D
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point3D -> m Point3D) -> IO Point3D -> m Point3D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Point3D
min <- Int -> IO (Ptr Point3D)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 12 :: IO (Ptr Graphene.Point3D.Point3D)
    Ptr Box -> Ptr Point3D -> IO ()
graphene_box_get_min Ptr Box
box' Ptr Point3D
min
    Point3D
min' <- ((ManagedPtr Point3D -> Point3D) -> Ptr Point3D -> IO Point3D
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point3D -> Point3D
Graphene.Point3D.Point3D) Ptr Point3D
min
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Point3D -> IO Point3D
forall (m :: * -> *) a. Monad m => a -> m a
return Point3D
min'

#if defined(ENABLE_OVERLOADING)
data BoxGetMinMethodInfo
instance (signature ~ (m (Graphene.Point3D.Point3D)), MonadIO m) => O.MethodInfo BoxGetMinMethodInfo Box signature where
    overloadedMethod = boxGetMin

#endif

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

foreign import ccall "graphene_box_get_size" graphene_box_get_size :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Vec3.Vec3 ->               -- size : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO ()

-- | Retrieves the size of the box on all three axes, and stores
-- it into the given /@size@/ vector.
-- 
-- /Since: 1.2/
boxGetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m (Graphene.Vec3.Vec3)
boxGetSize :: Box -> m Vec3
boxGetSize box :: Box
box = IO Vec3 -> m Vec3
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec3 -> m Vec3) -> IO Vec3 -> m Vec3
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Vec3
size <- Int -> IO (Ptr Vec3)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Graphene.Vec3.Vec3)
    Ptr Box -> Ptr Vec3 -> IO ()
graphene_box_get_size Ptr Box
box' Ptr Vec3
size
    Vec3
size' <- ((ManagedPtr Vec3 -> Vec3) -> Ptr Vec3 -> IO Vec3
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec3 -> Vec3
Graphene.Vec3.Vec3) Ptr Vec3
size
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Vec3 -> IO Vec3
forall (m :: * -> *) a. Monad m => a -> m a
return Vec3
size'

#if defined(ENABLE_OVERLOADING)
data BoxGetSizeMethodInfo
instance (signature ~ (m (Graphene.Vec3.Vec3)), MonadIO m) => O.MethodInfo BoxGetSizeMethodInfo Box signature where
    overloadedMethod = boxGetSize

#endif

-- XXX Could not generate method Box::get_vertices
-- Error was : Not implemented: "Don't know how to allocate \"vertices\" of type TCArray False 8 (-1) (TInterface (Name {namespace = \"Graphene\", name = \"Vec3\"}))"
-- method Box::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_get_width" graphene_box_get_width :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO CFloat

-- | Retrieves the size of the /@box@/ on the X axis.
-- 
-- /Since: 1.2/
boxGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m Float
    -- ^ __Returns:__ the width of the box
boxGetWidth :: Box -> m Float
boxGetWidth box :: Box
box = 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 Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    CFloat
result <- Ptr Box -> IO CFloat
graphene_box_get_width Ptr Box
box'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data BoxGetWidthMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo BoxGetWidthMethodInfo Box signature where
    overloadedMethod = boxGetWidth

#endif

-- method Box::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_box_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the coordinates of the minimum vertex"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point3D" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the coordinates of the maximum vertex"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Box" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_init" graphene_box_init :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Point3D.Point3D ->         -- min : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    Ptr Graphene.Point3D.Point3D ->         -- max : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO (Ptr Box)

-- | Initializes the given t'GI.Graphene.Structs.Box.Box' with two vertices.
-- 
-- /Since: 1.2/
boxInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: the t'GI.Graphene.Structs.Box.Box' to initialize
    -> Maybe (Graphene.Point3D.Point3D)
    -- ^ /@min@/: the coordinates of the minimum vertex
    -> Maybe (Graphene.Point3D.Point3D)
    -- ^ /@max@/: the coordinates of the maximum vertex
    -> m Box
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Box.Box'
boxInit :: Box -> Maybe Point3D -> Maybe Point3D -> m Box
boxInit box :: Box
box min :: Maybe Point3D
min max :: Maybe Point3D
max = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Point3D
maybeMin <- case Maybe Point3D
min of
        Nothing -> Ptr Point3D -> IO (Ptr Point3D)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Point3D
forall a. Ptr a
nullPtr
        Just jMin :: Point3D
jMin -> do
            Ptr Point3D
jMin' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
jMin
            Ptr Point3D -> IO (Ptr Point3D)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Point3D
jMin'
    Ptr Point3D
maybeMax <- case Maybe Point3D
max of
        Nothing -> Ptr Point3D -> IO (Ptr Point3D)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Point3D
forall a. Ptr a
nullPtr
        Just jMax :: Point3D
jMax -> do
            Ptr Point3D
jMax' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
jMax
            Ptr Point3D -> IO (Ptr Point3D)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Point3D
jMax'
    Ptr Box
result <- Ptr Box -> Ptr Point3D -> Ptr Point3D -> IO (Ptr Box)
graphene_box_init Ptr Box
box' Ptr Point3D
maybeMin Ptr Point3D
maybeMax
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxInit" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Maybe Point3D -> (Point3D -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Point3D
min Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe Point3D -> (Point3D -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Point3D
max Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
data BoxInitMethodInfo
instance (signature ~ (Maybe (Graphene.Point3D.Point3D) -> Maybe (Graphene.Point3D.Point3D) -> m Box), MonadIO m) => O.MethodInfo BoxInitMethodInfo Box signature where
    overloadedMethod = boxInit

#endif

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

foreign import ccall "graphene_box_init_from_box" graphene_box_init_from_box :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Box ->                              -- src : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO (Ptr Box)

-- | Initializes the given t'GI.Graphene.Structs.Box.Box' with the vertices of
-- another t'GI.Graphene.Structs.Box.Box'.
-- 
-- /Since: 1.2/
boxInitFromBox ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: the t'GI.Graphene.Structs.Box.Box' to initialize
    -> Box
    -- ^ /@src@/: a t'GI.Graphene.Structs.Box.Box'
    -> m Box
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Box.Box'
boxInitFromBox :: Box -> Box -> m Box
boxInitFromBox box :: Box
box src :: Box
src = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Box
src' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
src
    Ptr Box
result <- Ptr Box -> Ptr Box -> IO (Ptr Box)
graphene_box_init_from_box Ptr Box
box' Ptr Box
src'
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxInitFromBox" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
src
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
data BoxInitFromBoxMethodInfo
instance (signature ~ (Box -> m Box), MonadIO m) => O.MethodInfo BoxInitFromBoxMethodInfo Box signature where
    overloadedMethod = boxInitFromBox

#endif

-- method Box::init_from_points
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_box_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_points"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number #graphene_point3d_t in the @points array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "points"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 1
--                 (TInterface Name { namespace = "Graphene" , name = "Point3D" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #graphene_point3d_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_points"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number #graphene_point3d_t in the @points array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Box" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_init_from_points" graphene_box_init_from_points :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Word32 ->                               -- n_points : TBasicType TUInt
    Ptr Graphene.Point3D.Point3D ->         -- points : TCArray False (-1) 1 (TInterface (Name {namespace = "Graphene", name = "Point3D"}))
    IO (Ptr Box)

-- | Initializes the given t'GI.Graphene.Structs.Box.Box' with the given array
-- of vertices.
-- 
-- If /@nPoints@/ is 0, the returned box is initialized with
-- 'GI.Graphene.Functions.boxEmpty'.
-- 
-- /Since: 1.2/
boxInitFromPoints ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: the t'GI.Graphene.Structs.Box.Box' to initialize
    -> [Graphene.Point3D.Point3D]
    -- ^ /@points@/: an array of t'GI.Graphene.Structs.Point3D.Point3D'
    -> m Box
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Box.Box'
boxInitFromPoints :: Box -> [Point3D] -> m Box
boxInitFromPoints box :: Box
box points :: [Point3D]
points = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    let nPoints :: Word32
nPoints = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Point3D] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Point3D]
points
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    [Ptr Point3D]
points' <- (Point3D -> IO (Ptr Point3D)) -> [Point3D] -> IO [Ptr Point3D]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Point3D]
points
    Ptr Point3D
points'' <- Int -> [Ptr Point3D] -> IO (Ptr Point3D)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 12 [Ptr Point3D]
points'
    Ptr Box
result <- Ptr Box -> Word32 -> Ptr Point3D -> IO (Ptr Box)
graphene_box_init_from_points Ptr Box
box' Word32
nPoints Ptr Point3D
points''
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxInitFromPoints" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    (Point3D -> IO ()) -> [Point3D] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Point3D]
points
    Ptr Point3D -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Point3D
points''
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
data BoxInitFromPointsMethodInfo
instance (signature ~ ([Graphene.Point3D.Point3D] -> m Box), MonadIO m) => O.MethodInfo BoxInitFromPointsMethodInfo Box signature where
    overloadedMethod = boxInitFromPoints

#endif

-- method Box::init_from_vec3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_box_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the coordinates of the minimum vertex"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec3" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the coordinates of the maximum vertex"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Box" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_init_from_vec3" graphene_box_init_from_vec3 :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Graphene.Vec3.Vec3 ->               -- min : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    Ptr Graphene.Vec3.Vec3 ->               -- max : TInterface (Name {namespace = "Graphene", name = "Vec3"})
    IO (Ptr Box)

-- | Initializes the given t'GI.Graphene.Structs.Box.Box' with two vertices
-- stored inside t'GI.Graphene.Structs.Vec3.Vec3'.
-- 
-- /Since: 1.2/
boxInitFromVec3 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: the t'GI.Graphene.Structs.Box.Box' to initialize
    -> Maybe (Graphene.Vec3.Vec3)
    -- ^ /@min@/: the coordinates of the minimum vertex
    -> Maybe (Graphene.Vec3.Vec3)
    -- ^ /@max@/: the coordinates of the maximum vertex
    -> m Box
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Box.Box'
boxInitFromVec3 :: Box -> Maybe Vec3 -> Maybe Vec3 -> m Box
boxInitFromVec3 box :: Box
box min :: Maybe Vec3
min max :: Maybe Vec3
max = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    Ptr Vec3
maybeMin <- case Maybe Vec3
min of
        Nothing -> Ptr Vec3 -> IO (Ptr Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Vec3
forall a. Ptr a
nullPtr
        Just jMin :: Vec3
jMin -> do
            Ptr Vec3
jMin' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
jMin
            Ptr Vec3 -> IO (Ptr Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Vec3
jMin'
    Ptr Vec3
maybeMax <- case Maybe Vec3
max of
        Nothing -> Ptr Vec3 -> IO (Ptr Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Vec3
forall a. Ptr a
nullPtr
        Just jMax :: Vec3
jMax -> do
            Ptr Vec3
jMax' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
jMax
            Ptr Vec3 -> IO (Ptr Vec3)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Vec3
jMax'
    Ptr Box
result <- Ptr Box -> Ptr Vec3 -> Ptr Vec3 -> IO (Ptr Box)
graphene_box_init_from_vec3 Ptr Box
box' Ptr Vec3
maybeMin Ptr Vec3
maybeMax
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxInitFromVec3" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Maybe Vec3 -> (Vec3 -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Vec3
min Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe Vec3 -> (Vec3 -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Vec3
max Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
data BoxInitFromVec3MethodInfo
instance (signature ~ (Maybe (Graphene.Vec3.Vec3) -> Maybe (Graphene.Vec3.Vec3) -> m Box), MonadIO m) => O.MethodInfo BoxInitFromVec3MethodInfo Box signature where
    overloadedMethod = boxInitFromVec3

#endif

-- method Box::init_from_vectors
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_box_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_vectors"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number #graphene_point3d_t in the @vectors array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vectors"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 1
--                 (TInterface Name { namespace = "Graphene" , name = "Vec3" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #graphene_vec3_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_vectors"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number #graphene_point3d_t in the @vectors array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Box" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_box_init_from_vectors" graphene_box_init_from_vectors :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    Word32 ->                               -- n_vectors : TBasicType TUInt
    Ptr Graphene.Vec3.Vec3 ->               -- vectors : TCArray False (-1) 1 (TInterface (Name {namespace = "Graphene", name = "Vec3"}))
    IO (Ptr Box)

-- | Initializes the given t'GI.Graphene.Structs.Box.Box' with the given array
-- of vertices.
-- 
-- If /@nVectors@/ is 0, the returned box is initialized with
-- 'GI.Graphene.Functions.boxEmpty'.
-- 
-- /Since: 1.2/
boxInitFromVectors ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@box@/: the t'GI.Graphene.Structs.Box.Box' to initialize
    -> [Graphene.Vec3.Vec3]
    -- ^ /@vectors@/: an array of t'GI.Graphene.Structs.Vec3.Vec3'
    -> m Box
    -- ^ __Returns:__ the initialized t'GI.Graphene.Structs.Box.Box'
boxInitFromVectors :: Box -> [Vec3] -> m Box
boxInitFromVectors box :: Box
box vectors :: [Vec3]
vectors = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    let nVectors :: Word32
nVectors = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Vec3] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Vec3]
vectors
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    [Ptr Vec3]
vectors' <- (Vec3 -> IO (Ptr Vec3)) -> [Vec3] -> IO [Ptr Vec3]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Vec3]
vectors
    Ptr Vec3
vectors'' <- Int -> [Ptr Vec3] -> IO (Ptr Vec3)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 16 [Ptr Vec3]
vectors'
    Ptr Box
result <- Ptr Box -> Word32 -> Ptr Vec3 -> IO (Ptr Box)
graphene_box_init_from_vectors Ptr Box
box' Word32
nVectors Ptr Vec3
vectors''
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxInitFromVectors" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    (Vec3 -> IO ()) -> [Vec3] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Vec3]
vectors
    Ptr Vec3 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Vec3
vectors''
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
data BoxInitFromVectorsMethodInfo
instance (signature ~ ([Graphene.Vec3.Vec3] -> m Box), MonadIO m) => O.MethodInfo BoxInitFromVectorsMethodInfo Box signature where
    overloadedMethod = boxInitFromVectors

#endif

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

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

-- | Intersects the two given t'GI.Graphene.Structs.Box.Box'.
-- 
-- If the two boxes do not intersect, /@res@/ will contain a degenerate box
-- initialized with 'GI.Graphene.Functions.boxEmpty'.
-- 
-- /Since: 1.2/
boxIntersection ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@a@/: a t'GI.Graphene.Structs.Box.Box'
    -> Box
    -- ^ /@b@/: a t'GI.Graphene.Structs.Box.Box'
    -> m ((Bool, Box))
    -- ^ __Returns:__ true if the two boxes intersect
boxIntersection :: Box -> Box -> m (Bool, Box)
boxIntersection a :: Box
a b :: Box
b = IO (Bool, Box) -> m (Bool, Box)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Box) -> m (Bool, Box))
-> IO (Bool, Box) -> m (Bool, Box)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
a' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
a
    Ptr Box
b' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
b
    Ptr Box
res <- Int -> IO (Ptr Box)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Box)
    CInt
result <- Ptr Box -> Ptr Box -> Ptr Box -> IO CInt
graphene_box_intersection Ptr Box
a' Ptr Box
b' Ptr Box
res
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Box
res' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Box -> Box
Box) Ptr Box
res
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
a
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
b
    (Bool, Box) -> IO (Bool, Box)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Box
res')

#if defined(ENABLE_OVERLOADING)
data BoxIntersectionMethodInfo
instance (signature ~ (Box -> m ((Bool, Box))), MonadIO m) => O.MethodInfo BoxIntersectionMethodInfo Box signature where
    overloadedMethod = boxIntersection

#endif

-- method Box::union
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_box_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the box to union to @a"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Box" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the 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_box_union" graphene_box_union :: 
    Ptr Box ->                              -- a : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Box ->                              -- b : TInterface (Name {namespace = "Graphene", name = "Box"})
    Ptr Box ->                              -- res : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO ()

-- | Unions the two given t'GI.Graphene.Structs.Box.Box'.
-- 
-- /Since: 1.2/
boxUnion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Box
    -- ^ /@a@/: a t'GI.Graphene.Structs.Box.Box'
    -> Box
    -- ^ /@b@/: the box to union to /@a@/
    -> m (Box)
boxUnion :: Box -> Box -> m Box
boxUnion a :: Box
a b :: Box
b = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
a' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
a
    Ptr Box
b' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
b
    Ptr Box
res <- Int -> IO (Ptr Box)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Box)
    Ptr Box -> Ptr Box -> Ptr Box -> IO ()
graphene_box_union Ptr Box
a' Ptr Box
b' Ptr Box
res
    Box
res' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Box -> Box
Box) Ptr Box
res
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
a
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
b
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
res'

#if defined(ENABLE_OVERLOADING)
data BoxUnionMethodInfo
instance (signature ~ (Box -> m (Box)), MonadIO m) => O.MethodInfo BoxUnionMethodInfo Box signature where
    overloadedMethod = boxUnion

#endif

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

foreign import ccall "graphene_box_empty" graphene_box_empty :: 
    IO (Ptr Box)

-- | A degenerate t'GI.Graphene.Structs.Box.Box' that can only be expanded.
-- 
-- The returned value is owned by Graphene and should not be modified or freed.
-- 
-- /Since: 1.2/
boxEmpty ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Box
    -- ^ __Returns:__ a t'GI.Graphene.Structs.Box.Box'
boxEmpty :: m Box
boxEmpty  = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
result <- IO (Ptr Box)
graphene_box_empty
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxEmpty" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_box_infinite" graphene_box_infinite :: 
    IO (Ptr Box)

-- | A degenerate t'GI.Graphene.Structs.Box.Box' that cannot be expanded.
-- 
-- The returned value is owned by Graphene and should not be modified or freed.
-- 
-- /Since: 1.2/
boxInfinite ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Box
    -- ^ __Returns:__ a t'GI.Graphene.Structs.Box.Box'
boxInfinite :: m Box
boxInfinite  = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
result <- IO (Ptr Box)
graphene_box_infinite
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxInfinite" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_box_minus_one" graphene_box_minus_one :: 
    IO (Ptr Box)

-- | A t'GI.Graphene.Structs.Box.Box' with the minimum vertex set at (-1, -1, -1) and the
-- maximum vertex set at (0, 0, 0).
-- 
-- The returned value is owned by Graphene and should not be modified or freed.
-- 
-- /Since: 1.2/
boxMinusOne ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Box
    -- ^ __Returns:__ a t'GI.Graphene.Structs.Box.Box'
boxMinusOne :: m Box
boxMinusOne  = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
result <- IO (Ptr Box)
graphene_box_minus_one
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxMinusOne" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_box_one" graphene_box_one :: 
    IO (Ptr Box)

-- | A t'GI.Graphene.Structs.Box.Box' with the minimum vertex set at (0, 0, 0) and the
-- maximum vertex set at (1, 1, 1).
-- 
-- The returned value is owned by Graphene and should not be modified or freed.
-- 
-- /Since: 1.2/
boxOne ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Box
    -- ^ __Returns:__ a t'GI.Graphene.Structs.Box.Box'
boxOne :: m Box
boxOne  = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
result <- IO (Ptr Box)
graphene_box_one
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxOne" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_box_one_minus_one" graphene_box_one_minus_one :: 
    IO (Ptr Box)

-- | A t'GI.Graphene.Structs.Box.Box' with the minimum vertex set at (-1, -1, -1) and the
-- maximum vertex set at (1, 1, 1).
-- 
-- The returned value is owned by Graphene and should not be modified or freed.
-- 
-- /Since: 1.2/
boxOneMinusOne ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Box
    -- ^ __Returns:__ a t'GI.Graphene.Structs.Box.Box'
boxOneMinusOne :: m Box
boxOneMinusOne  = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
result <- IO (Ptr Box)
graphene_box_one_minus_one
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxOneMinusOne" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "graphene_box_zero" graphene_box_zero :: 
    IO (Ptr Box)

-- | A t'GI.Graphene.Structs.Box.Box' with both the minimum and maximum vertices set at (0, 0, 0).
-- 
-- The returned value is owned by Graphene and should not be modified or freed.
-- 
-- /Since: 1.2/
boxZero ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Box
    -- ^ __Returns:__ a t'GI.Graphene.Structs.Box.Box'
boxZero :: m Box
boxZero  = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
result <- IO (Ptr Box)
graphene_box_zero
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "boxZero" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveBoxMethod (t :: Symbol) (o :: *) :: * where
    ResolveBoxMethod "containsBox" o = BoxContainsBoxMethodInfo
    ResolveBoxMethod "containsPoint" o = BoxContainsPointMethodInfo
    ResolveBoxMethod "equal" o = BoxEqualMethodInfo
    ResolveBoxMethod "expand" o = BoxExpandMethodInfo
    ResolveBoxMethod "expandScalar" o = BoxExpandScalarMethodInfo
    ResolveBoxMethod "expandVec3" o = BoxExpandVec3MethodInfo
    ResolveBoxMethod "free" o = BoxFreeMethodInfo
    ResolveBoxMethod "init" o = BoxInitMethodInfo
    ResolveBoxMethod "initFromBox" o = BoxInitFromBoxMethodInfo
    ResolveBoxMethod "initFromPoints" o = BoxInitFromPointsMethodInfo
    ResolveBoxMethod "initFromVec3" o = BoxInitFromVec3MethodInfo
    ResolveBoxMethod "initFromVectors" o = BoxInitFromVectorsMethodInfo
    ResolveBoxMethod "intersection" o = BoxIntersectionMethodInfo
    ResolveBoxMethod "union" o = BoxUnionMethodInfo
    ResolveBoxMethod "getBoundingSphere" o = BoxGetBoundingSphereMethodInfo
    ResolveBoxMethod "getCenter" o = BoxGetCenterMethodInfo
    ResolveBoxMethod "getDepth" o = BoxGetDepthMethodInfo
    ResolveBoxMethod "getHeight" o = BoxGetHeightMethodInfo
    ResolveBoxMethod "getMax" o = BoxGetMaxMethodInfo
    ResolveBoxMethod "getMin" o = BoxGetMinMethodInfo
    ResolveBoxMethod "getSize" o = BoxGetSizeMethodInfo
    ResolveBoxMethod "getWidth" o = BoxGetWidthMethodInfo
    ResolveBoxMethod l o = O.MethodResolutionFailed l o

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

#endif