{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A 3D volume delimited by 2D clip planes.
-- 
-- The contents of the @graphene_frustum_t@ are private, and should not be
-- modified directly.
-- 
-- /Since: 1.2/

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

module GI.Graphene.Structs.Frustum
    ( 

-- * Exported types
    Frustum(..)                             ,
    newZeroFrustum                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [containsPoint]("GI.Graphene.Structs.Frustum#g:method:containsPoint"), [equal]("GI.Graphene.Structs.Frustum#g:method:equal"), [free]("GI.Graphene.Structs.Frustum#g:method:free"), [init]("GI.Graphene.Structs.Frustum#g:method:init"), [initFromFrustum]("GI.Graphene.Structs.Frustum#g:method:initFromFrustum"), [initFromMatrix]("GI.Graphene.Structs.Frustum#g:method:initFromMatrix"), [intersectsBox]("GI.Graphene.Structs.Frustum#g:method:intersectsBox"), [intersectsSphere]("GI.Graphene.Structs.Frustum#g:method:intersectsSphere").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveFrustumMethod                    ,
#endif

-- ** alloc #method:alloc#

    frustumAlloc                            ,


-- ** containsPoint #method:containsPoint#

#if defined(ENABLE_OVERLOADING)
    FrustumContainsPointMethodInfo          ,
#endif
    frustumContainsPoint                    ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    FrustumEqualMethodInfo                  ,
#endif
    frustumEqual                            ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    FrustumFreeMethodInfo                   ,
#endif
    frustumFree                             ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    FrustumInitMethodInfo                   ,
#endif
    frustumInit                             ,


-- ** initFromFrustum #method:initFromFrustum#

#if defined(ENABLE_OVERLOADING)
    FrustumInitFromFrustumMethodInfo        ,
#endif
    frustumInitFromFrustum                  ,


-- ** initFromMatrix #method:initFromMatrix#

#if defined(ENABLE_OVERLOADING)
    FrustumInitFromMatrixMethodInfo         ,
#endif
    frustumInitFromMatrix                   ,


-- ** intersectsBox #method:intersectsBox#

#if defined(ENABLE_OVERLOADING)
    FrustumIntersectsBoxMethodInfo          ,
#endif
    frustumIntersectsBox                    ,


-- ** intersectsSphere #method:intersectsSphere#

#if defined(ENABLE_OVERLOADING)
    FrustumIntersectsSphereMethodInfo       ,
#endif
    frustumIntersectsSphere                 ,




    ) where

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

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

import {-# SOURCE #-} qualified GI.Graphene.Structs.Box as Graphene.Box
import {-# SOURCE #-} qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import {-# SOURCE #-} qualified GI.Graphene.Structs.Plane as Graphene.Plane
import {-# SOURCE #-} qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import {-# SOURCE #-} qualified GI.Graphene.Structs.Sphere as Graphene.Sphere

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

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

foreign import ccall "graphene_frustum_get_type" c_graphene_frustum_get_type :: 
    IO GType

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

instance B.Types.TypedObject Frustum where
    glibType :: IO GType
glibType = IO GType
c_graphene_frustum_get_type

instance B.Types.GBoxed Frustum

-- | Convert 'Frustum' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Frustum) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_graphene_frustum_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Frustum -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Frustum
P.Nothing = Ptr GValue -> Ptr Frustum -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Frustum
forall a. Ptr a
FP.nullPtr :: FP.Ptr Frustum)
    gvalueSet_ Ptr GValue
gv (P.Just Frustum
obj) = Frustum -> (Ptr Frustum -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Frustum
obj (Ptr GValue -> Ptr Frustum -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Frustum)
gvalueGet_ Ptr GValue
gv = do
        Ptr Frustum
ptr <- Ptr GValue -> IO (Ptr Frustum)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Frustum)
        if Ptr Frustum
ptr Ptr Frustum -> Ptr Frustum -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Frustum
forall a. Ptr a
FP.nullPtr
        then Frustum -> Maybe Frustum
forall a. a -> Maybe a
P.Just (Frustum -> Maybe Frustum) -> IO Frustum -> IO (Maybe Frustum)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Frustum -> Frustum) -> Ptr Frustum -> IO Frustum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Frustum -> Frustum
Frustum Ptr Frustum
ptr
        else Maybe Frustum -> IO (Maybe Frustum)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Frustum
forall a. Maybe a
P.Nothing
        
    

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

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



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

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

foreign import ccall "graphene_frustum_alloc" graphene_frustum_alloc :: 
    IO (Ptr Frustum)

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method Frustum::contains_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "f"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Frustum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_frustum_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 "a #graphene_point3d_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_frustum_contains_point" graphene_frustum_contains_point :: 
    Ptr Frustum ->                          -- f : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    Ptr Graphene.Point3D.Point3D ->         -- point : TInterface (Name {namespace = "Graphene", name = "Point3D"})
    IO CInt

-- | Checks whether a point is inside the volume defined by the given
-- t'GI.Graphene.Structs.Frustum.Frustum'.
-- 
-- /Since: 1.2/
frustumContainsPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Frustum
    -- ^ /@f@/: a t'GI.Graphene.Structs.Frustum.Frustum'
    -> Graphene.Point3D.Point3D
    -- ^ /@point@/: a t'GI.Graphene.Structs.Point3D.Point3D'
    -> m Bool
    -- ^ __Returns:__ @true@ if the point is inside the frustum
frustumContainsPoint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Frustum -> Point3D -> m Bool
frustumContainsPoint Frustum
f 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 Frustum
f' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
f
    Ptr Point3D
point' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
point
    CInt
result <- Ptr Frustum -> Ptr Point3D -> IO CInt
graphene_frustum_contains_point Ptr Frustum
f' Ptr Point3D
point'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
f
    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 FrustumContainsPointMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m Bool), MonadIO m) => O.OverloadedMethod FrustumContainsPointMethodInfo Frustum signature where
    overloadedMethod = frustumContainsPoint

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data FrustumEqualMethodInfo
instance (signature ~ (Frustum -> m Bool), MonadIO m) => O.OverloadedMethod FrustumEqualMethodInfo Frustum signature where
    overloadedMethod = frustumEqual

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


#endif

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

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

#if defined(ENABLE_OVERLOADING)
data FrustumFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod FrustumFreeMethodInfo Frustum signature where
    overloadedMethod = frustumFree

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


#endif

-- XXX Could not generate method Frustum::get_planes
-- Not implemented: Don't know how to allocate "planes" of type TCArray False 6 (-1) (TInterface (Name {namespace = "Graphene", name = "Plane"}))
-- method Frustum::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "f"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Frustum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_frustum_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p0"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Plane" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clipping plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p1"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Plane" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clipping plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p2"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Plane" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clipping plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p3"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Plane" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clipping plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p4"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Plane" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clipping plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p5"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Plane" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clipping plane" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Graphene" , name = "Frustum" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_frustum_init" graphene_frustum_init :: 
    Ptr Frustum ->                          -- f : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    Ptr Graphene.Plane.Plane ->             -- p0 : TInterface (Name {namespace = "Graphene", name = "Plane"})
    Ptr Graphene.Plane.Plane ->             -- p1 : TInterface (Name {namespace = "Graphene", name = "Plane"})
    Ptr Graphene.Plane.Plane ->             -- p2 : TInterface (Name {namespace = "Graphene", name = "Plane"})
    Ptr Graphene.Plane.Plane ->             -- p3 : TInterface (Name {namespace = "Graphene", name = "Plane"})
    Ptr Graphene.Plane.Plane ->             -- p4 : TInterface (Name {namespace = "Graphene", name = "Plane"})
    Ptr Graphene.Plane.Plane ->             -- p5 : TInterface (Name {namespace = "Graphene", name = "Plane"})
    IO (Ptr Frustum)

-- | Initializes the given t'GI.Graphene.Structs.Frustum.Frustum' using the provided
-- clipping planes.
-- 
-- /Since: 1.2/
frustumInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Frustum
    -- ^ /@f@/: the t'GI.Graphene.Structs.Frustum.Frustum' to initialize
    -> Graphene.Plane.Plane
    -- ^ /@p0@/: a clipping plane
    -> Graphene.Plane.Plane
    -- ^ /@p1@/: a clipping plane
    -> Graphene.Plane.Plane
    -- ^ /@p2@/: a clipping plane
    -> Graphene.Plane.Plane
    -- ^ /@p3@/: a clipping plane
    -> Graphene.Plane.Plane
    -- ^ /@p4@/: a clipping plane
    -> Graphene.Plane.Plane
    -- ^ /@p5@/: a clipping plane
    -> m Frustum
    -- ^ __Returns:__ the initialized frustum
frustumInit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Frustum
-> Plane -> Plane -> Plane -> Plane -> Plane -> Plane -> m Frustum
frustumInit Frustum
f Plane
p0 Plane
p1 Plane
p2 Plane
p3 Plane
p4 Plane
p5 = IO Frustum -> m Frustum
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Frustum -> m Frustum) -> IO Frustum -> m Frustum
forall a b. (a -> b) -> a -> b
$ do
    Ptr Frustum
f' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
f
    Ptr Plane
p0' <- Plane -> IO (Ptr Plane)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Plane
p0
    Ptr Plane
p1' <- Plane -> IO (Ptr Plane)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Plane
p1
    Ptr Plane
p2' <- Plane -> IO (Ptr Plane)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Plane
p2
    Ptr Plane
p3' <- Plane -> IO (Ptr Plane)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Plane
p3
    Ptr Plane
p4' <- Plane -> IO (Ptr Plane)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Plane
p4
    Ptr Plane
p5' <- Plane -> IO (Ptr Plane)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Plane
p5
    Ptr Frustum
result <- Ptr Frustum
-> Ptr Plane
-> Ptr Plane
-> Ptr Plane
-> Ptr Plane
-> Ptr Plane
-> Ptr Plane
-> IO (Ptr Frustum)
graphene_frustum_init Ptr Frustum
f' Ptr Plane
p0' Ptr Plane
p1' Ptr Plane
p2' Ptr Plane
p3' Ptr Plane
p4' Ptr Plane
p5'
    Text -> Ptr Frustum -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"frustumInit" Ptr Frustum
result
    Frustum
result' <- ((ManagedPtr Frustum -> Frustum) -> Ptr Frustum -> IO Frustum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Frustum -> Frustum
Frustum) Ptr Frustum
result
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
f
    Plane -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Plane
p0
    Plane -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Plane
p1
    Plane -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Plane
p2
    Plane -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Plane
p3
    Plane -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Plane
p4
    Plane -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Plane
p5
    Frustum -> IO Frustum
forall (m :: * -> *) a. Monad m => a -> m a
return Frustum
result'

#if defined(ENABLE_OVERLOADING)
data FrustumInitMethodInfo
instance (signature ~ (Graphene.Plane.Plane -> Graphene.Plane.Plane -> Graphene.Plane.Plane -> Graphene.Plane.Plane -> Graphene.Plane.Plane -> Graphene.Plane.Plane -> m Frustum), MonadIO m) => O.OverloadedMethod FrustumInitMethodInfo Frustum signature where
    overloadedMethod = frustumInit

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


#endif

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

foreign import ccall "graphene_frustum_init_from_frustum" graphene_frustum_init_from_frustum :: 
    Ptr Frustum ->                          -- f : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    Ptr Frustum ->                          -- src : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    IO (Ptr Frustum)

-- | Initializes the given t'GI.Graphene.Structs.Frustum.Frustum' using the clipping
-- planes of another t'GI.Graphene.Structs.Frustum.Frustum'.
-- 
-- /Since: 1.2/
frustumInitFromFrustum ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Frustum
    -- ^ /@f@/: the t'GI.Graphene.Structs.Frustum.Frustum' to initialize
    -> Frustum
    -- ^ /@src@/: a t'GI.Graphene.Structs.Frustum.Frustum'
    -> m Frustum
    -- ^ __Returns:__ the initialized frustum
frustumInitFromFrustum :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Frustum -> Frustum -> m Frustum
frustumInitFromFrustum Frustum
f Frustum
src = IO Frustum -> m Frustum
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Frustum -> m Frustum) -> IO Frustum -> m Frustum
forall a b. (a -> b) -> a -> b
$ do
    Ptr Frustum
f' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
f
    Ptr Frustum
src' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
src
    Ptr Frustum
result <- Ptr Frustum -> Ptr Frustum -> IO (Ptr Frustum)
graphene_frustum_init_from_frustum Ptr Frustum
f' Ptr Frustum
src'
    Text -> Ptr Frustum -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"frustumInitFromFrustum" Ptr Frustum
result
    Frustum
result' <- ((ManagedPtr Frustum -> Frustum) -> Ptr Frustum -> IO Frustum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Frustum -> Frustum
Frustum) Ptr Frustum
result
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
f
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
src
    Frustum -> IO Frustum
forall (m :: * -> *) a. Monad m => a -> m a
return Frustum
result'

#if defined(ENABLE_OVERLOADING)
data FrustumInitFromFrustumMethodInfo
instance (signature ~ (Frustum -> m Frustum), MonadIO m) => O.OverloadedMethod FrustumInitFromFrustumMethodInfo Frustum signature where
    overloadedMethod = frustumInitFromFrustum

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


#endif

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

foreign import ccall "graphene_frustum_init_from_matrix" graphene_frustum_init_from_matrix :: 
    Ptr Frustum ->                          -- f : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    Ptr Graphene.Matrix.Matrix ->           -- matrix : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    IO (Ptr Frustum)

-- | Initializes a t'GI.Graphene.Structs.Frustum.Frustum' using the given /@matrix@/.
-- 
-- /Since: 1.2/
frustumInitFromMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Frustum
    -- ^ /@f@/: a t'GI.Graphene.Structs.Frustum.Frustum'
    -> Graphene.Matrix.Matrix
    -- ^ /@matrix@/: a t'GI.Graphene.Structs.Matrix.Matrix'
    -> m Frustum
    -- ^ __Returns:__ the initialized frustum
frustumInitFromMatrix :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Frustum -> Matrix -> m Frustum
frustumInitFromMatrix Frustum
f Matrix
matrix = IO Frustum -> m Frustum
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Frustum -> m Frustum) -> IO Frustum -> m Frustum
forall a b. (a -> b) -> a -> b
$ do
    Ptr Frustum
f' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
f
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr Frustum
result <- Ptr Frustum -> Ptr Matrix -> IO (Ptr Frustum)
graphene_frustum_init_from_matrix Ptr Frustum
f' Ptr Matrix
matrix'
    Text -> Ptr Frustum -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"frustumInitFromMatrix" Ptr Frustum
result
    Frustum
result' <- ((ManagedPtr Frustum -> Frustum) -> Ptr Frustum -> IO Frustum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Frustum -> Frustum
Frustum) Ptr Frustum
result
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
f
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Frustum -> IO Frustum
forall (m :: * -> *) a. Monad m => a -> m a
return Frustum
result'

#if defined(ENABLE_OVERLOADING)
data FrustumInitFromMatrixMethodInfo
instance (signature ~ (Graphene.Matrix.Matrix -> m Frustum), MonadIO m) => O.OverloadedMethod FrustumInitFromMatrixMethodInfo Frustum signature where
    overloadedMethod = frustumInitFromMatrix

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


#endif

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

foreign import ccall "graphene_frustum_intersects_box" graphene_frustum_intersects_box :: 
    Ptr Frustum ->                          -- f : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    Ptr Graphene.Box.Box ->                 -- box : TInterface (Name {namespace = "Graphene", name = "Box"})
    IO CInt

-- | Checks whether the given /@box@/ intersects a plane of
-- a t'GI.Graphene.Structs.Frustum.Frustum'.
-- 
-- /Since: 1.2/
frustumIntersectsBox ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Frustum
    -- ^ /@f@/: a t'GI.Graphene.Structs.Frustum.Frustum'
    -> Graphene.Box.Box
    -- ^ /@box@/: a t'GI.Graphene.Structs.Box.Box'
    -> m Bool
    -- ^ __Returns:__ @true@ if the box intersects the frustum
frustumIntersectsBox :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Frustum -> Box -> m Bool
frustumIntersectsBox Frustum
f Box
box = 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 Frustum
f' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
f
    Ptr Box
box' <- Box -> IO (Ptr Box)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Box
box
    CInt
result <- Ptr Frustum -> Ptr Box -> IO CInt
graphene_frustum_intersects_box Ptr Frustum
f' Ptr Box
box'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
f
    Box -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Box
box
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FrustumIntersectsBoxMethodInfo
instance (signature ~ (Graphene.Box.Box -> m Bool), MonadIO m) => O.OverloadedMethod FrustumIntersectsBoxMethodInfo Frustum signature where
    overloadedMethod = frustumIntersectsBox

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


#endif

-- method Frustum::intersects_sphere
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "f"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Frustum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_frustum_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sphere"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Sphere" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_sphere_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_frustum_intersects_sphere" graphene_frustum_intersects_sphere :: 
    Ptr Frustum ->                          -- f : TInterface (Name {namespace = "Graphene", name = "Frustum"})
    Ptr Graphene.Sphere.Sphere ->           -- sphere : TInterface (Name {namespace = "Graphene", name = "Sphere"})
    IO CInt

-- | Checks whether the given /@sphere@/ intersects a plane of
-- a t'GI.Graphene.Structs.Frustum.Frustum'.
-- 
-- /Since: 1.2/
frustumIntersectsSphere ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Frustum
    -- ^ /@f@/: a t'GI.Graphene.Structs.Frustum.Frustum'
    -> Graphene.Sphere.Sphere
    -- ^ /@sphere@/: a t'GI.Graphene.Structs.Sphere.Sphere'
    -> m Bool
    -- ^ __Returns:__ @true@ if the sphere intersects the frustum
frustumIntersectsSphere :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Frustum -> Sphere -> m Bool
frustumIntersectsSphere Frustum
f Sphere
sphere = 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 Frustum
f' <- Frustum -> IO (Ptr Frustum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Frustum
f
    Ptr Sphere
sphere' <- Sphere -> IO (Ptr Sphere)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Sphere
sphere
    CInt
result <- Ptr Frustum -> Ptr Sphere -> IO CInt
graphene_frustum_intersects_sphere Ptr Frustum
f' Ptr Sphere
sphere'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Frustum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Frustum
f
    Sphere -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Sphere
sphere
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FrustumIntersectsSphereMethodInfo
instance (signature ~ (Graphene.Sphere.Sphere -> m Bool), MonadIO m) => O.OverloadedMethod FrustumIntersectsSphereMethodInfo Frustum signature where
    overloadedMethod = frustumIntersectsSphere

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


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveFrustumMethod (t :: Symbol) (o :: *) :: * where
    ResolveFrustumMethod "containsPoint" o = FrustumContainsPointMethodInfo
    ResolveFrustumMethod "equal" o = FrustumEqualMethodInfo
    ResolveFrustumMethod "free" o = FrustumFreeMethodInfo
    ResolveFrustumMethod "init" o = FrustumInitMethodInfo
    ResolveFrustumMethod "initFromFrustum" o = FrustumInitFromFrustumMethodInfo
    ResolveFrustumMethod "initFromMatrix" o = FrustumInitFromMatrixMethodInfo
    ResolveFrustumMethod "intersectsBox" o = FrustumIntersectsBoxMethodInfo
    ResolveFrustumMethod "intersectsSphere" o = FrustumIntersectsSphereMethodInfo
    ResolveFrustumMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFrustumMethod t Frustum, O.OverloadedMethod info Frustum p, R.HasField t Frustum p) => R.HasField t Frustum p where
    getField = O.overloadedMethod @info

#endif

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

#endif