{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.GLib.Structs.HookList.HookList' struct represents a list of hook functions.

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

module GI.GLib.Structs.HookList
    ( 

-- * Exported types
    HookList(..)                            ,
    newZeroHookList                         ,
    noHookList                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveHookListMethod                   ,
#endif


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    HookListClearMethodInfo                 ,
#endif
    hookListClear                           ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    HookListInitMethodInfo                  ,
#endif
    hookListInit                            ,


-- ** invoke #method:invoke#

#if defined(ENABLE_OVERLOADING)
    HookListInvokeMethodInfo                ,
#endif
    hookListInvoke                          ,


-- ** invokeCheck #method:invokeCheck#

#if defined(ENABLE_OVERLOADING)
    HookListInvokeCheckMethodInfo           ,
#endif
    hookListInvokeCheck                     ,




 -- * Properties
-- ** dummy3 #attr:dummy3#
-- | unused

    clearHookListDummy3                     ,
    getHookListDummy3                       ,
#if defined(ENABLE_OVERLOADING)
    hookList_dummy3                         ,
#endif
    setHookListDummy3                       ,


-- ** finalizeHook #attr:finalizeHook#
-- | the function to call to finalize a t'GI.GLib.Structs.Hook.Hook' element.
--     The default behaviour is to call the hooks /@destroy@/ function

    clearHookListFinalizeHook               ,
    getHookListFinalizeHook                 ,
#if defined(ENABLE_OVERLOADING)
    hookList_finalizeHook                   ,
#endif
    setHookListFinalizeHook                 ,


-- ** hookSize #attr:hookSize#
-- | the size of the t'GI.GLib.Structs.HookList.HookList' elements, in bytes

    getHookListHookSize                     ,
#if defined(ENABLE_OVERLOADING)
    hookList_hookSize                       ,
#endif
    setHookListHookSize                     ,


-- ** hooks #attr:hooks#
-- | the first t'GI.GLib.Structs.Hook.Hook' element in the list

    clearHookListHooks                      ,
    getHookListHooks                        ,
#if defined(ENABLE_OVERLOADING)
    hookList_hooks                          ,
#endif
    setHookListHooks                        ,


-- ** isSetup #attr:isSetup#
-- | 1 if the t'GI.GLib.Structs.HookList.HookList' has been initialized

    getHookListIsSetup                      ,
#if defined(ENABLE_OVERLOADING)
    hookList_isSetup                        ,
#endif
    setHookListIsSetup                      ,


-- ** seqId #attr:seqId#
-- | the next free t'GI.GLib.Structs.Hook.Hook' id

    getHookListSeqId                        ,
#if defined(ENABLE_OVERLOADING)
    hookList_seqId                          ,
#endif
    setHookListSeqId                        ,




    ) 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 qualified GI.GLib.Callbacks as GLib.Callbacks
import {-# SOURCE #-} qualified GI.GLib.Structs.Hook as GLib.Hook

-- | Memory-managed wrapper type.
newtype HookList = HookList (ManagedPtr HookList)
    deriving (HookList -> HookList -> Bool
(HookList -> HookList -> Bool)
-> (HookList -> HookList -> Bool) -> Eq HookList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HookList -> HookList -> Bool
$c/= :: HookList -> HookList -> Bool
== :: HookList -> HookList -> Bool
$c== :: HookList -> HookList -> Bool
Eq)
instance WrappedPtr HookList where
    wrappedPtrCalloc :: IO (Ptr HookList)
wrappedPtrCalloc = Int -> IO (Ptr HookList)
forall a. Int -> IO (Ptr a)
callocBytes 56
    wrappedPtrCopy :: HookList -> IO HookList
wrappedPtrCopy = \p :: HookList
p -> HookList -> (Ptr HookList -> IO HookList) -> IO HookList
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
p (Int -> Ptr HookList -> IO (Ptr HookList)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 56 (Ptr HookList -> IO (Ptr HookList))
-> (Ptr HookList -> IO HookList) -> Ptr HookList -> IO HookList
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr HookList -> HookList) -> Ptr HookList -> IO HookList
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr HookList -> HookList
HookList)
    wrappedPtrFree :: Maybe (GDestroyNotify HookList)
wrappedPtrFree = GDestroyNotify HookList -> Maybe (GDestroyNotify HookList)
forall a. a -> Maybe a
Just GDestroyNotify HookList
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `HookList` struct initialized to zero.
newZeroHookList :: MonadIO m => m HookList
newZeroHookList :: m HookList
newZeroHookList = IO HookList -> m HookList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO HookList -> m HookList) -> IO HookList -> m HookList
forall a b. (a -> b) -> a -> b
$ IO (Ptr HookList)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr HookList) -> (Ptr HookList -> IO HookList) -> IO HookList
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr HookList -> HookList) -> Ptr HookList -> IO HookList
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr HookList -> HookList
HookList

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


-- | A convenience alias for `Nothing` :: `Maybe` `HookList`.
noHookList :: Maybe HookList
noHookList :: Maybe HookList
noHookList = Maybe HookList
forall a. Maybe a
Nothing

-- | Get the value of the “@seq_id@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hookList #seqId
-- @
getHookListSeqId :: MonadIO m => HookList -> m CULong
getHookListSeqId :: HookList -> m CULong
getHookListSeqId s :: HookList
s = IO CULong -> m CULong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO CULong) -> IO CULong
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO CULong) -> IO CULong)
-> (Ptr HookList -> IO CULong) -> IO CULong
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    CULong
val <- Ptr CULong -> IO CULong
forall a. Storable a => Ptr a -> IO a
peek (Ptr HookList
ptr Ptr HookList -> Int -> Ptr CULong
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CULong
    CULong -> IO CULong
forall (m :: * -> *) a. Monad m => a -> m a
return CULong
val

-- | Set the value of the “@seq_id@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hookList [ #seqId 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookListSeqId :: MonadIO m => HookList -> CULong -> m ()
setHookListSeqId :: HookList -> CULong -> m ()
setHookListSeqId s :: HookList
s val :: CULong
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr CULong -> CULong -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr CULong
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CULong
val :: CULong)

#if defined(ENABLE_OVERLOADING)
data HookListSeqIdFieldInfo
instance AttrInfo HookListSeqIdFieldInfo where
    type AttrBaseTypeConstraint HookListSeqIdFieldInfo = (~) HookList
    type AttrAllowedOps HookListSeqIdFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint HookListSeqIdFieldInfo = (~) CULong
    type AttrTransferTypeConstraint HookListSeqIdFieldInfo = (~)CULong
    type AttrTransferType HookListSeqIdFieldInfo = CULong
    type AttrGetType HookListSeqIdFieldInfo = CULong
    type AttrLabel HookListSeqIdFieldInfo = "seq_id"
    type AttrOrigin HookListSeqIdFieldInfo = HookList
    attrGet = getHookListSeqId
    attrSet = setHookListSeqId
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

hookList_seqId :: AttrLabelProxy "seqId"
hookList_seqId = AttrLabelProxy

#endif


-- | Get the value of the “@hook_size@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hookList #hookSize
-- @
getHookListHookSize :: MonadIO m => HookList -> m Word32
getHookListHookSize :: HookList -> m Word32
getHookListHookSize s :: HookList
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO Word32) -> IO Word32)
-> (Ptr HookList -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr HookList
ptr Ptr HookList -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@hook_size@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hookList [ #hookSize 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookListHookSize :: MonadIO m => HookList -> Word32 -> m ()
setHookListHookSize :: HookList -> Word32 -> m ()
setHookListHookSize s :: HookList
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data HookListHookSizeFieldInfo
instance AttrInfo HookListHookSizeFieldInfo where
    type AttrBaseTypeConstraint HookListHookSizeFieldInfo = (~) HookList
    type AttrAllowedOps HookListHookSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint HookListHookSizeFieldInfo = (~) Word32
    type AttrTransferTypeConstraint HookListHookSizeFieldInfo = (~)Word32
    type AttrTransferType HookListHookSizeFieldInfo = Word32
    type AttrGetType HookListHookSizeFieldInfo = Word32
    type AttrLabel HookListHookSizeFieldInfo = "hook_size"
    type AttrOrigin HookListHookSizeFieldInfo = HookList
    attrGet = getHookListHookSize
    attrSet = setHookListHookSize
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

hookList_hookSize :: AttrLabelProxy "hookSize"
hookList_hookSize = AttrLabelProxy

#endif


-- | Get the value of the “@is_setup@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hookList #isSetup
-- @
getHookListIsSetup :: MonadIO m => HookList -> m Word32
getHookListIsSetup :: HookList -> m Word32
getHookListIsSetup s :: HookList
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO Word32) -> IO Word32)
-> (Ptr HookList -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr HookList
ptr Ptr HookList -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@is_setup@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hookList [ #isSetup 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookListIsSetup :: MonadIO m => HookList -> Word32 -> m ()
setHookListIsSetup :: HookList -> Word32 -> m ()
setHookListIsSetup s :: HookList
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data HookListIsSetupFieldInfo
instance AttrInfo HookListIsSetupFieldInfo where
    type AttrBaseTypeConstraint HookListIsSetupFieldInfo = (~) HookList
    type AttrAllowedOps HookListIsSetupFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint HookListIsSetupFieldInfo = (~) Word32
    type AttrTransferTypeConstraint HookListIsSetupFieldInfo = (~)Word32
    type AttrTransferType HookListIsSetupFieldInfo = Word32
    type AttrGetType HookListIsSetupFieldInfo = Word32
    type AttrLabel HookListIsSetupFieldInfo = "is_setup"
    type AttrOrigin HookListIsSetupFieldInfo = HookList
    attrGet = getHookListIsSetup
    attrSet = setHookListIsSetup
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

hookList_isSetup :: AttrLabelProxy "isSetup"
hookList_isSetup = AttrLabelProxy

#endif


-- | Get the value of the “@hooks@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hookList #hooks
-- @
getHookListHooks :: MonadIO m => HookList -> m (Maybe GLib.Hook.Hook)
getHookListHooks :: HookList -> m (Maybe Hook)
getHookListHooks s :: HookList
s = IO (Maybe Hook) -> m (Maybe Hook)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Hook) -> m (Maybe Hook))
-> IO (Maybe Hook) -> m (Maybe Hook)
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO (Maybe Hook)) -> IO (Maybe Hook)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO (Maybe Hook)) -> IO (Maybe Hook))
-> (Ptr HookList -> IO (Maybe Hook)) -> IO (Maybe Hook)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr Hook
val <- Ptr (Ptr Hook) -> IO (Ptr Hook)
forall a. Storable a => Ptr a -> IO a
peek (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO (Ptr GLib.Hook.Hook)
    Maybe Hook
result <- Ptr Hook -> (Ptr Hook -> IO Hook) -> IO (Maybe Hook)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Hook
val ((Ptr Hook -> IO Hook) -> IO (Maybe Hook))
-> (Ptr Hook -> IO Hook) -> IO (Maybe Hook)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Hook
val' -> do
        Hook
val'' <- ((ManagedPtr Hook -> Hook) -> Ptr Hook -> IO Hook
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Hook -> Hook
GLib.Hook.Hook) Ptr Hook
val'
        Hook -> IO Hook
forall (m :: * -> *) a. Monad m => a -> m a
return Hook
val''
    Maybe Hook -> IO (Maybe Hook)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Hook
result

-- | Set the value of the “@hooks@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hookList [ #hooks 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookListHooks :: MonadIO m => HookList -> Ptr GLib.Hook.Hook -> m ()
setHookListHooks :: HookList -> Ptr Hook -> m ()
setHookListHooks s :: HookList
s val :: Ptr Hook
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr (Ptr Hook) -> Ptr Hook -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr Hook
val :: Ptr GLib.Hook.Hook)

-- | Set the value of the “@hooks@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #hooks
-- @
clearHookListHooks :: MonadIO m => HookList -> m ()
clearHookListHooks :: HookList -> m ()
clearHookListHooks s :: HookList
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr (Ptr Hook) -> Ptr Hook -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr Hook
forall a. Ptr a
FP.nullPtr :: Ptr GLib.Hook.Hook)

#if defined(ENABLE_OVERLOADING)
data HookListHooksFieldInfo
instance AttrInfo HookListHooksFieldInfo where
    type AttrBaseTypeConstraint HookListHooksFieldInfo = (~) HookList
    type AttrAllowedOps HookListHooksFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookListHooksFieldInfo = (~) (Ptr GLib.Hook.Hook)
    type AttrTransferTypeConstraint HookListHooksFieldInfo = (~)(Ptr GLib.Hook.Hook)
    type AttrTransferType HookListHooksFieldInfo = (Ptr GLib.Hook.Hook)
    type AttrGetType HookListHooksFieldInfo = Maybe GLib.Hook.Hook
    type AttrLabel HookListHooksFieldInfo = "hooks"
    type AttrOrigin HookListHooksFieldInfo = HookList
    attrGet = getHookListHooks
    attrSet = setHookListHooks
    attrConstruct = undefined
    attrClear = clearHookListHooks
    attrTransfer _ v = do
        return v

hookList_hooks :: AttrLabelProxy "hooks"
hookList_hooks = AttrLabelProxy

#endif


-- | Get the value of the “@dummy3@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hookList #dummy3
-- @
getHookListDummy3 :: MonadIO m => HookList -> m (Ptr ())
getHookListDummy3 :: HookList -> m (Ptr ())
getHookListDummy3 s :: HookList
s = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr HookList -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO (Ptr ())
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
val

-- | Set the value of the “@dummy3@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hookList [ #dummy3 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookListDummy3 :: MonadIO m => HookList -> Ptr () -> m ()
setHookListDummy3 :: HookList -> Ptr () -> m ()
setHookListDummy3 s :: HookList
s val :: Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Ptr ()
val :: Ptr ())

-- | Set the value of the “@dummy3@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #dummy3
-- @
clearHookListDummy3 :: MonadIO m => HookList -> m ()
clearHookListDummy3 :: HookList -> m ()
clearHookListDummy3 s :: HookList
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

#if defined(ENABLE_OVERLOADING)
data HookListDummy3FieldInfo
instance AttrInfo HookListDummy3FieldInfo where
    type AttrBaseTypeConstraint HookListDummy3FieldInfo = (~) HookList
    type AttrAllowedOps HookListDummy3FieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookListDummy3FieldInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint HookListDummy3FieldInfo = (~)(Ptr ())
    type AttrTransferType HookListDummy3FieldInfo = (Ptr ())
    type AttrGetType HookListDummy3FieldInfo = Ptr ()
    type AttrLabel HookListDummy3FieldInfo = "dummy3"
    type AttrOrigin HookListDummy3FieldInfo = HookList
    attrGet = getHookListDummy3
    attrSet = setHookListDummy3
    attrConstruct = undefined
    attrClear = clearHookListDummy3
    attrTransfer _ v = do
        return v

hookList_dummy3 :: AttrLabelProxy "dummy3"
hookList_dummy3 = AttrLabelProxy

#endif


-- | Get the value of the “@finalize_hook@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hookList #finalizeHook
-- @
getHookListFinalizeHook :: MonadIO m => HookList -> m (Maybe GLib.Callbacks.HookFinalizeFunc)
getHookListFinalizeHook :: HookList -> m (Maybe HookFinalizeFunc)
getHookListFinalizeHook s :: HookList
s = IO (Maybe HookFinalizeFunc) -> m (Maybe HookFinalizeFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe HookFinalizeFunc) -> m (Maybe HookFinalizeFunc))
-> IO (Maybe HookFinalizeFunc) -> m (Maybe HookFinalizeFunc)
forall a b. (a -> b) -> a -> b
$ HookList
-> (Ptr HookList -> IO (Maybe HookFinalizeFunc))
-> IO (Maybe HookFinalizeFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO (Maybe HookFinalizeFunc))
 -> IO (Maybe HookFinalizeFunc))
-> (Ptr HookList -> IO (Maybe HookFinalizeFunc))
-> IO (Maybe HookFinalizeFunc)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    FunPtr C_HookFinalizeFunc
val <- Ptr (FunPtr C_HookFinalizeFunc) -> IO (FunPtr C_HookFinalizeFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (FunPtr C_HookFinalizeFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO (FunPtr GLib.Callbacks.C_HookFinalizeFunc)
    Maybe HookFinalizeFunc
result <- FunPtr C_HookFinalizeFunc
-> (FunPtr C_HookFinalizeFunc -> IO HookFinalizeFunc)
-> IO (Maybe HookFinalizeFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_HookFinalizeFunc
val ((FunPtr C_HookFinalizeFunc -> IO HookFinalizeFunc)
 -> IO (Maybe HookFinalizeFunc))
-> (FunPtr C_HookFinalizeFunc -> IO HookFinalizeFunc)
-> IO (Maybe HookFinalizeFunc)
forall a b. (a -> b) -> a -> b
$ \val' :: FunPtr C_HookFinalizeFunc
val' -> do
        let val'' :: HookFinalizeFunc
val'' = FunPtr C_HookFinalizeFunc -> HookFinalizeFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_HookFinalizeFunc -> HookList -> Hook -> m ()
GLib.Callbacks.dynamic_HookFinalizeFunc FunPtr C_HookFinalizeFunc
val'
        HookFinalizeFunc -> IO HookFinalizeFunc
forall (m :: * -> *) a. Monad m => a -> m a
return HookFinalizeFunc
val''
    Maybe HookFinalizeFunc -> IO (Maybe HookFinalizeFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe HookFinalizeFunc
result

-- | Set the value of the “@finalize_hook@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hookList [ #finalizeHook 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookListFinalizeHook :: MonadIO m => HookList -> FunPtr GLib.Callbacks.C_HookFinalizeFunc -> m ()
setHookListFinalizeHook :: HookList -> FunPtr C_HookFinalizeFunc -> m ()
setHookListFinalizeHook s :: HookList
s val :: FunPtr C_HookFinalizeFunc
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr (FunPtr C_HookFinalizeFunc)
-> FunPtr C_HookFinalizeFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (FunPtr C_HookFinalizeFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (FunPtr C_HookFinalizeFunc
val :: FunPtr GLib.Callbacks.C_HookFinalizeFunc)

-- | Set the value of the “@finalize_hook@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #finalizeHook
-- @
clearHookListFinalizeHook :: MonadIO m => HookList -> m ()
clearHookListFinalizeHook :: HookList -> m ()
clearHookListFinalizeHook s :: HookList
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ HookList -> (Ptr HookList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr HookList
s ((Ptr HookList -> IO ()) -> IO ())
-> (Ptr HookList -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr HookList
ptr -> do
    Ptr (FunPtr C_HookFinalizeFunc)
-> FunPtr C_HookFinalizeFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr HookList
ptr Ptr HookList -> Int -> Ptr (FunPtr C_HookFinalizeFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (FunPtr C_HookFinalizeFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GLib.Callbacks.C_HookFinalizeFunc)

#if defined(ENABLE_OVERLOADING)
data HookListFinalizeHookFieldInfo
instance AttrInfo HookListFinalizeHookFieldInfo where
    type AttrBaseTypeConstraint HookListFinalizeHookFieldInfo = (~) HookList
    type AttrAllowedOps HookListFinalizeHookFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookListFinalizeHookFieldInfo = (~) (FunPtr GLib.Callbacks.C_HookFinalizeFunc)
    type AttrTransferTypeConstraint HookListFinalizeHookFieldInfo = (~)GLib.Callbacks.HookFinalizeFunc
    type AttrTransferType HookListFinalizeHookFieldInfo = (FunPtr GLib.Callbacks.C_HookFinalizeFunc)
    type AttrGetType HookListFinalizeHookFieldInfo = Maybe GLib.Callbacks.HookFinalizeFunc
    type AttrLabel HookListFinalizeHookFieldInfo = "finalize_hook"
    type AttrOrigin HookListFinalizeHookFieldInfo = HookList
    attrGet = getHookListFinalizeHook
    attrSet = setHookListFinalizeHook
    attrConstruct = undefined
    attrClear = clearHookListFinalizeHook
    attrTransfer _ v = do
        GLib.Callbacks.mk_HookFinalizeFunc (GLib.Callbacks.wrap_HookFinalizeFunc Nothing v)

hookList_finalizeHook :: AttrLabelProxy "finalizeHook"
hookList_finalizeHook = AttrLabelProxy

#endif


-- XXX Skipped attribute for "HookList:dummy" :: Not implemented: "Don't know how to unpack C array of type TCArray False 2 (-1) (TBasicType TPtr)"

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList HookList
type instance O.AttributeList HookList = HookListAttributeList
type HookListAttributeList = ('[ '("seqId", HookListSeqIdFieldInfo), '("hookSize", HookListHookSizeFieldInfo), '("isSetup", HookListIsSetupFieldInfo), '("hooks", HookListHooksFieldInfo), '("dummy3", HookListDummy3FieldInfo), '("finalizeHook", HookListFinalizeHookFieldInfo)] :: [(Symbol, *)])
#endif

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

foreign import ccall "g_hook_list_clear" g_hook_list_clear :: 
    Ptr HookList ->                         -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    IO ()

-- | Removes all the t'GI.GLib.Structs.Hook.Hook' elements from a t'GI.GLib.Structs.HookList.HookList'.
hookListClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> m ()
hookListClear :: HookList -> m ()
hookListClear hookList :: HookList
hookList = 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 HookList
hookList' <- HookList -> IO (Ptr HookList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr HookList
hookList
    Ptr HookList -> IO ()
g_hook_list_clear Ptr HookList
hookList'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data HookListClearMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo HookListClearMethodInfo HookList signature where
    overloadedMethod = hookListClear

#endif

-- method HookList::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "hook_list"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "HookList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GHookList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hook_size"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the size of each element in the #GHookList,\n    typically `sizeof (GHook)`."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_list_init" g_hook_list_init :: 
    Ptr HookList ->                         -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    Word32 ->                               -- hook_size : TBasicType TUInt
    IO ()

-- | Initializes a t'GI.GLib.Structs.HookList.HookList'.
-- This must be called before the t'GI.GLib.Structs.HookList.HookList' is used.
hookListInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Word32
    -- ^ /@hookSize@/: the size of each element in the t'GI.GLib.Structs.HookList.HookList',
    --     typically @sizeof (GHook)@.
    -> m ()
hookListInit :: HookList -> Word32 -> m ()
hookListInit hookList :: HookList
hookList hookSize :: Word32
hookSize = 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 HookList
hookList' <- HookList -> IO (Ptr HookList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr HookList
hookList
    Ptr HookList -> Word32 -> IO ()
g_hook_list_init Ptr HookList
hookList' Word32
hookSize
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data HookListInitMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.MethodInfo HookListInitMethodInfo HookList signature where
    overloadedMethod = hookListInit

#endif

-- method HookList::invoke
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "hook_list"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "HookList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GHookList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "may_recurse"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "%TRUE if functions which are already running\n    (e.g. in another thread) can be called. If set to %FALSE,\n    these are skipped"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_list_invoke" g_hook_list_invoke :: 
    Ptr HookList ->                         -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    CInt ->                                 -- may_recurse : TBasicType TBoolean
    IO ()

-- | Calls all of the t'GI.GLib.Structs.Hook.Hook' functions in a t'GI.GLib.Structs.HookList.HookList'.
hookListInvoke ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Bool
    -- ^ /@mayRecurse@/: 'P.True' if functions which are already running
    --     (e.g. in another thread) can be called. If set to 'P.False',
    --     these are skipped
    -> m ()
hookListInvoke :: HookList -> Bool -> m ()
hookListInvoke hookList :: HookList
hookList mayRecurse :: Bool
mayRecurse = 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 HookList
hookList' <- HookList -> IO (Ptr HookList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr HookList
hookList
    let mayRecurse' :: CInt
mayRecurse' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
mayRecurse
    Ptr HookList -> CInt -> IO ()
g_hook_list_invoke Ptr HookList
hookList' CInt
mayRecurse'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data HookListInvokeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m) => O.MethodInfo HookListInvokeMethodInfo HookList signature where
    overloadedMethod = hookListInvoke

#endif

-- method HookList::invoke_check
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "hook_list"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "HookList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GHookList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "may_recurse"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "%TRUE if functions which are already running\n    (e.g. in another thread) can be called. If set to %FALSE,\n    these are skipped"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_list_invoke_check" g_hook_list_invoke_check :: 
    Ptr HookList ->                         -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    CInt ->                                 -- may_recurse : TBasicType TBoolean
    IO ()

-- | Calls all of the t'GI.GLib.Structs.Hook.Hook' functions in a t'GI.GLib.Structs.HookList.HookList'.
-- Any function which returns 'P.False' is removed from the t'GI.GLib.Structs.HookList.HookList'.
hookListInvokeCheck ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Bool
    -- ^ /@mayRecurse@/: 'P.True' if functions which are already running
    --     (e.g. in another thread) can be called. If set to 'P.False',
    --     these are skipped
    -> m ()
hookListInvokeCheck :: HookList -> Bool -> m ()
hookListInvokeCheck hookList :: HookList
hookList mayRecurse :: Bool
mayRecurse = 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 HookList
hookList' <- HookList -> IO (Ptr HookList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr HookList
hookList
    let mayRecurse' :: CInt
mayRecurse' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
mayRecurse
    Ptr HookList -> CInt -> IO ()
g_hook_list_invoke_check Ptr HookList
hookList' CInt
mayRecurse'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data HookListInvokeCheckMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m) => O.MethodInfo HookListInvokeCheckMethodInfo HookList signature where
    overloadedMethod = hookListInvokeCheck

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveHookListMethod (t :: Symbol) (o :: *) :: * where
    ResolveHookListMethod "clear" o = HookListClearMethodInfo
    ResolveHookListMethod "init" o = HookListInitMethodInfo
    ResolveHookListMethod "invoke" o = HookListInvokeMethodInfo
    ResolveHookListMethod "invokeCheck" o = HookListInvokeCheckMethodInfo
    ResolveHookListMethod l o = O.MethodResolutionFailed l o

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

#endif