{-# 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.Hook.Hook' struct represents a single hook function in a t'GI.GLib.Structs.HookList.HookList'.

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

module GI.GLib.Structs.Hook
    ( 

-- * Exported types
    Hook(..)                                ,
    newZeroHook                             ,
    noHook                                  ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveHookMethod                       ,
#endif


-- ** compareIds #method:compareIds#

#if defined(ENABLE_OVERLOADING)
    HookCompareIdsMethodInfo                ,
#endif
    hookCompareIds                          ,


-- ** destroy #method:destroy#

    hookDestroy                             ,


-- ** destroyLink #method:destroyLink#

    hookDestroyLink                         ,


-- ** free #method:free#

    hookFree                                ,


-- ** insertBefore #method:insertBefore#

    hookInsertBefore                        ,


-- ** prepend #method:prepend#

    hookPrepend                             ,


-- ** unref #method:unref#

    hookUnref                               ,




 -- * Properties
-- ** data #attr:data#
-- | data which is passed to func when this hook is invoked

    clearHookData                           ,
    getHookData                             ,
#if defined(ENABLE_OVERLOADING)
    hook_data                               ,
#endif
    setHookData                             ,


-- ** destroy #attr:destroy#
-- | the default /@finalizeHook@/ function of a t'GI.GLib.Structs.HookList.HookList' calls
--     this member of the hook that is being finalized

    clearHookDestroy                        ,
    getHookDestroy                          ,
#if defined(ENABLE_OVERLOADING)
    hook_destroy                            ,
#endif
    setHookDestroy                          ,


-- ** flags #attr:flags#
-- | flags which are set for this hook. See t'GI.GLib.Flags.HookFlagMask' for
--     predefined flags

    getHookFlags                            ,
#if defined(ENABLE_OVERLOADING)
    hook_flags                              ,
#endif
    setHookFlags                            ,


-- ** func #attr:func#
-- | the function to call when this hook is invoked. The possible
--     signatures for this function are t'GI.GLib.Callbacks.HookFunc' and t'GI.GLib.Callbacks.HookCheckFunc'

    clearHookFunc                           ,
    getHookFunc                             ,
#if defined(ENABLE_OVERLOADING)
    hook_func                               ,
#endif
    setHookFunc                             ,


-- ** hookId #attr:hookId#
-- | the id of this hook, which is unique within its list

    getHookHookId                           ,
#if defined(ENABLE_OVERLOADING)
    hook_hookId                             ,
#endif
    setHookHookId                           ,


-- ** next #attr:next#
-- | pointer to the next hook in the list

    clearHookNext                           ,
    getHookNext                             ,
#if defined(ENABLE_OVERLOADING)
    hook_next                               ,
#endif
    setHookNext                             ,


-- ** prev #attr:prev#
-- | pointer to the previous hook in the list

    clearHookPrev                           ,
    getHookPrev                             ,
#if defined(ENABLE_OVERLOADING)
    hook_prev                               ,
#endif
    setHookPrev                             ,


-- ** refCount #attr:refCount#
-- | the reference count of this hook

    getHookRefCount                         ,
#if defined(ENABLE_OVERLOADING)
    hook_refCount                           ,
#endif
    setHookRefCount                         ,




    ) 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.HookList as GLib.HookList

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `Hook`.
noHook :: Maybe Hook
noHook :: Maybe Hook
noHook = Maybe Hook
forall a. Maybe a
Nothing

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

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

-- | Set the value of the “@data@” 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' #data
-- @
clearHookData :: MonadIO m => Hook -> m ()
clearHookData :: Hook -> m ()
clearHookData s :: Hook
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

#if defined(ENABLE_OVERLOADING)
data HookDataFieldInfo
instance AttrInfo HookDataFieldInfo where
    type AttrBaseTypeConstraint HookDataFieldInfo = (~) Hook
    type AttrAllowedOps HookDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookDataFieldInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint HookDataFieldInfo = (~)(Ptr ())
    type AttrTransferType HookDataFieldInfo = (Ptr ())
    type AttrGetType HookDataFieldInfo = Ptr ()
    type AttrLabel HookDataFieldInfo = "data"
    type AttrOrigin HookDataFieldInfo = Hook
    attrGet = getHookData
    attrSet = setHookData
    attrConstruct = undefined
    attrClear = clearHookData
    attrTransfer _ v = do
        return v

hook_data :: AttrLabelProxy "data"
hook_data = AttrLabelProxy

#endif


-- | Get the value of the “@next@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hook #next
-- @
getHookNext :: MonadIO m => Hook -> m (Maybe Hook)
getHookNext :: Hook -> m (Maybe Hook)
getHookNext s :: Hook
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
$ Hook -> (Ptr Hook -> IO (Maybe Hook)) -> IO (Maybe Hook)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO (Maybe Hook)) -> IO (Maybe Hook))
-> (Ptr Hook -> IO (Maybe Hook)) -> IO (Maybe Hook)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr Hook
val <- Ptr (Ptr Hook) -> IO (Ptr Hook)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (Ptr 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
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 “@next@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hook [ #next 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookNext :: MonadIO m => Hook -> Ptr Hook -> m ()
setHookNext :: Hook -> Ptr Hook -> m ()
setHookNext s :: Hook
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
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (Ptr Hook) -> Ptr Hook -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Hook
val :: Ptr Hook)

-- | Set the value of the “@next@” 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' #next
-- @
clearHookNext :: MonadIO m => Hook -> m ()
clearHookNext :: Hook -> m ()
clearHookNext s :: Hook
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (Ptr Hook) -> Ptr Hook -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Hook
forall a. Ptr a
FP.nullPtr :: Ptr Hook)

#if defined(ENABLE_OVERLOADING)
data HookNextFieldInfo
instance AttrInfo HookNextFieldInfo where
    type AttrBaseTypeConstraint HookNextFieldInfo = (~) Hook
    type AttrAllowedOps HookNextFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookNextFieldInfo = (~) (Ptr Hook)
    type AttrTransferTypeConstraint HookNextFieldInfo = (~)(Ptr Hook)
    type AttrTransferType HookNextFieldInfo = (Ptr Hook)
    type AttrGetType HookNextFieldInfo = Maybe Hook
    type AttrLabel HookNextFieldInfo = "next"
    type AttrOrigin HookNextFieldInfo = Hook
    attrGet = getHookNext
    attrSet = setHookNext
    attrConstruct = undefined
    attrClear = clearHookNext
    attrTransfer _ v = do
        return v

hook_next :: AttrLabelProxy "next"
hook_next = AttrLabelProxy

#endif


-- | Get the value of the “@prev@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hook #prev
-- @
getHookPrev :: MonadIO m => Hook -> m (Maybe Hook)
getHookPrev :: Hook -> m (Maybe Hook)
getHookPrev s :: Hook
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
$ Hook -> (Ptr Hook -> IO (Maybe Hook)) -> IO (Maybe Hook)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO (Maybe Hook)) -> IO (Maybe Hook))
-> (Ptr Hook -> IO (Maybe Hook)) -> IO (Maybe Hook)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr Hook
val <- Ptr (Ptr Hook) -> IO (Ptr Hook)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO (Ptr 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
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 “@prev@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hook [ #prev 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookPrev :: MonadIO m => Hook -> Ptr Hook -> m ()
setHookPrev :: Hook -> Ptr Hook -> m ()
setHookPrev s :: Hook
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
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (Ptr Hook) -> Ptr Hook -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr Hook
val :: Ptr Hook)

-- | Set the value of the “@prev@” 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' #prev
-- @
clearHookPrev :: MonadIO m => Hook -> m ()
clearHookPrev :: Hook -> m ()
clearHookPrev s :: Hook
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (Ptr Hook) -> Ptr Hook -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr Hook)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr Hook
forall a. Ptr a
FP.nullPtr :: Ptr Hook)

#if defined(ENABLE_OVERLOADING)
data HookPrevFieldInfo
instance AttrInfo HookPrevFieldInfo where
    type AttrBaseTypeConstraint HookPrevFieldInfo = (~) Hook
    type AttrAllowedOps HookPrevFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookPrevFieldInfo = (~) (Ptr Hook)
    type AttrTransferTypeConstraint HookPrevFieldInfo = (~)(Ptr Hook)
    type AttrTransferType HookPrevFieldInfo = (Ptr Hook)
    type AttrGetType HookPrevFieldInfo = Maybe Hook
    type AttrLabel HookPrevFieldInfo = "prev"
    type AttrOrigin HookPrevFieldInfo = Hook
    attrGet = getHookPrev
    attrSet = setHookPrev
    attrConstruct = undefined
    attrClear = clearHookPrev
    attrTransfer _ v = do
        return v

hook_prev :: AttrLabelProxy "prev"
hook_prev = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data HookRefCountFieldInfo
instance AttrInfo HookRefCountFieldInfo where
    type AttrBaseTypeConstraint HookRefCountFieldInfo = (~) Hook
    type AttrAllowedOps HookRefCountFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint HookRefCountFieldInfo = (~) Word32
    type AttrTransferTypeConstraint HookRefCountFieldInfo = (~)Word32
    type AttrTransferType HookRefCountFieldInfo = Word32
    type AttrGetType HookRefCountFieldInfo = Word32
    type AttrLabel HookRefCountFieldInfo = "ref_count"
    type AttrOrigin HookRefCountFieldInfo = Hook
    attrGet = getHookRefCount
    attrSet = setHookRefCount
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

hook_refCount :: AttrLabelProxy "refCount"
hook_refCount = AttrLabelProxy

#endif


-- | Get the value of the “@hook_id@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' hook #hookId
-- @
getHookHookId :: MonadIO m => Hook -> m CULong
getHookHookId :: Hook -> m CULong
getHookHookId s :: Hook
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
$ Hook -> (Ptr Hook -> IO CULong) -> IO CULong
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO CULong) -> IO CULong)
-> (Ptr Hook -> IO CULong) -> IO CULong
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    CULong
val <- Ptr CULong -> IO CULong
forall a. Storable a => Ptr a -> IO a
peek (Ptr Hook
ptr Ptr Hook -> Int -> Ptr CULong
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO CULong
    CULong -> IO CULong
forall (m :: * -> *) a. Monad m => a -> m a
return CULong
val

-- | Set the value of the “@hook_id@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hook [ #hookId 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookHookId :: MonadIO m => Hook -> CULong -> m ()
setHookHookId :: Hook -> CULong -> m ()
setHookHookId s :: Hook
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
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr CULong -> CULong -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr CULong
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (CULong
val :: CULong)

#if defined(ENABLE_OVERLOADING)
data HookHookIdFieldInfo
instance AttrInfo HookHookIdFieldInfo where
    type AttrBaseTypeConstraint HookHookIdFieldInfo = (~) Hook
    type AttrAllowedOps HookHookIdFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint HookHookIdFieldInfo = (~) CULong
    type AttrTransferTypeConstraint HookHookIdFieldInfo = (~)CULong
    type AttrTransferType HookHookIdFieldInfo = CULong
    type AttrGetType HookHookIdFieldInfo = CULong
    type AttrLabel HookHookIdFieldInfo = "hook_id"
    type AttrOrigin HookHookIdFieldInfo = Hook
    attrGet = getHookHookId
    attrSet = setHookHookId
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

hook_hookId :: AttrLabelProxy "hookId"
hook_hookId = AttrLabelProxy

#endif


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

-- | Set the value of the “@flags@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' hook [ #flags 'Data.GI.Base.Attributes.:=' value ]
-- @
setHookFlags :: MonadIO m => Hook -> Word32 -> m ()
setHookFlags :: Hook -> Word32 -> m ()
setHookFlags s :: Hook
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
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data HookFlagsFieldInfo
instance AttrInfo HookFlagsFieldInfo where
    type AttrBaseTypeConstraint HookFlagsFieldInfo = (~) Hook
    type AttrAllowedOps HookFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint HookFlagsFieldInfo = (~) Word32
    type AttrTransferTypeConstraint HookFlagsFieldInfo = (~)Word32
    type AttrTransferType HookFlagsFieldInfo = Word32
    type AttrGetType HookFlagsFieldInfo = Word32
    type AttrLabel HookFlagsFieldInfo = "flags"
    type AttrOrigin HookFlagsFieldInfo = Hook
    attrGet = getHookFlags
    attrSet = setHookFlags
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

hook_flags :: AttrLabelProxy "flags"
hook_flags = AttrLabelProxy

#endif


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

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

-- | Set the value of the “@func@” 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' #func
-- @
clearHookFunc :: MonadIO m => Hook -> m ()
clearHookFunc :: Hook -> m ()
clearHookFunc s :: Hook
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

#if defined(ENABLE_OVERLOADING)
data HookFuncFieldInfo
instance AttrInfo HookFuncFieldInfo where
    type AttrBaseTypeConstraint HookFuncFieldInfo = (~) Hook
    type AttrAllowedOps HookFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookFuncFieldInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint HookFuncFieldInfo = (~)(Ptr ())
    type AttrTransferType HookFuncFieldInfo = (Ptr ())
    type AttrGetType HookFuncFieldInfo = Ptr ()
    type AttrLabel HookFuncFieldInfo = "func"
    type AttrOrigin HookFuncFieldInfo = Hook
    attrGet = getHookFunc
    attrSet = setHookFunc
    attrConstruct = undefined
    attrClear = clearHookFunc
    attrTransfer _ v = do
        return v

hook_func :: AttrLabelProxy "func"
hook_func = AttrLabelProxy

#endif


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

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

-- | Set the value of the “@destroy@” 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' #destroy
-- @
clearHookDestroy :: MonadIO m => Hook -> m ()
clearHookDestroy :: Hook -> m ()
clearHookDestroy s :: Hook
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Hook -> (Ptr Hook -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Hook
s ((Ptr Hook -> IO ()) -> IO ()) -> (Ptr Hook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Hook
ptr -> do
    Ptr (FunPtr (Ptr () -> IO ())) -> FunPtr (Ptr () -> IO ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Hook
ptr Ptr Hook -> Int -> Ptr (FunPtr (Ptr () -> IO ()))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56) (FunPtr (Ptr () -> IO ())
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GLib.Callbacks.C_DestroyNotify)

#if defined(ENABLE_OVERLOADING)
data HookDestroyFieldInfo
instance AttrInfo HookDestroyFieldInfo where
    type AttrBaseTypeConstraint HookDestroyFieldInfo = (~) Hook
    type AttrAllowedOps HookDestroyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint HookDestroyFieldInfo = (~) (FunPtr GLib.Callbacks.C_DestroyNotify)
    type AttrTransferTypeConstraint HookDestroyFieldInfo = (~)GLib.Callbacks.DestroyNotify
    type AttrTransferType HookDestroyFieldInfo = (FunPtr GLib.Callbacks.C_DestroyNotify)
    type AttrGetType HookDestroyFieldInfo = Maybe GLib.Callbacks.DestroyNotify
    type AttrLabel HookDestroyFieldInfo = "destroy"
    type AttrOrigin HookDestroyFieldInfo = Hook
    attrGet = getHookDestroy
    attrSet = setHookDestroy
    attrConstruct = undefined
    attrClear = clearHookDestroy
    attrTransfer _ v = do
        GLib.Callbacks.mk_DestroyNotify (GLib.Callbacks.wrap_DestroyNotify Nothing v)

hook_destroy :: AttrLabelProxy "destroy"
hook_destroy = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Hook
type instance O.AttributeList Hook = HookAttributeList
type HookAttributeList = ('[ '("data", HookDataFieldInfo), '("next", HookNextFieldInfo), '("prev", HookPrevFieldInfo), '("refCount", HookRefCountFieldInfo), '("hookId", HookHookIdFieldInfo), '("flags", HookFlagsFieldInfo), '("func", HookFuncFieldInfo), '("destroy", HookDestroyFieldInfo)] :: [(Symbol, *)])
#endif

-- method Hook::compare_ids
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "new_hook"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GHook" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GHook to compare with @new_hook"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_compare_ids" g_hook_compare_ids :: 
    Ptr Hook ->                             -- new_hook : TInterface (Name {namespace = "GLib", name = "Hook"})
    Ptr Hook ->                             -- sibling : TInterface (Name {namespace = "GLib", name = "Hook"})
    IO Int32

-- | Compares the ids of two t'GI.GLib.Structs.Hook.Hook' elements, returning a negative value
-- if the second id is greater than the first.
hookCompareIds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Hook
    -- ^ /@newHook@/: a t'GI.GLib.Structs.Hook.Hook'
    -> Hook
    -- ^ /@sibling@/: a t'GI.GLib.Structs.Hook.Hook' to compare with /@newHook@/
    -> m Int32
    -- ^ __Returns:__ a value \<= 0 if the id of /@sibling@/ is >= the id of /@newHook@/
hookCompareIds :: Hook -> Hook -> m Int32
hookCompareIds newHook :: Hook
newHook sibling :: Hook
sibling = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Hook
newHook' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
newHook
    Ptr Hook
sibling' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
sibling
    Int32
result <- Ptr Hook -> Ptr Hook -> IO Int32
g_hook_compare_ids Ptr Hook
newHook' Ptr Hook
sibling'
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
newHook
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
sibling
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data HookCompareIdsMethodInfo
instance (signature ~ (Hook -> m Int32), MonadIO m) => O.MethodInfo HookCompareIdsMethodInfo Hook signature where
    overloadedMethod = hookCompareIds

#endif

-- method Hook::destroy
-- method type : MemberFunction
-- 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_id"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a hook ID" , 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 "g_hook_destroy" g_hook_destroy :: 
    Ptr GLib.HookList.HookList ->           -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    CULong ->                               -- hook_id : TBasicType TULong
    IO CInt

-- | Destroys a t'GI.GLib.Structs.Hook.Hook', given its ID.
hookDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> CULong
    -- ^ /@hookId@/: a hook ID
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.GLib.Structs.Hook.Hook' was found in the t'GI.GLib.Structs.HookList.HookList' and destroyed
hookDestroy :: HookList -> CULong -> m Bool
hookDestroy hookList :: HookList
hookList hookId :: CULong
hookId = 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 HookList
hookList' <- HookList -> IO (Ptr HookList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr HookList
hookList
    CInt
result <- Ptr HookList -> CULong -> IO CInt
g_hook_destroy Ptr HookList
hookList' CULong
hookId
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Hook::destroy_link
-- method type : MemberFunction
-- 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"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GHook to remove"
--                 , 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_destroy_link" g_hook_destroy_link :: 
    Ptr GLib.HookList.HookList ->           -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    Ptr Hook ->                             -- hook : TInterface (Name {namespace = "GLib", name = "Hook"})
    IO ()

-- | Removes one t'GI.GLib.Structs.Hook.Hook' from a t'GI.GLib.Structs.HookList.HookList', marking it
-- inactive and calling 'GI.GLib.Functions.hookUnref' on it.
hookDestroyLink ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Hook
    -- ^ /@hook@/: the t'GI.GLib.Structs.Hook.Hook' to remove
    -> m ()
hookDestroyLink :: HookList -> Hook -> m ()
hookDestroyLink hookList :: HookList
hookList hook :: Hook
hook = 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 Hook
hook' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
hook
    Ptr HookList -> Ptr Hook -> IO ()
g_hook_destroy_link Ptr HookList
hookList' Ptr Hook
hook'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
hook
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Hook::free
-- method type : MemberFunction
-- 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"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GHook to free" , 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_free" g_hook_free :: 
    Ptr GLib.HookList.HookList ->           -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    Ptr Hook ->                             -- hook : TInterface (Name {namespace = "GLib", name = "Hook"})
    IO ()

-- | Calls the t'GI.GLib.Structs.HookList.HookList' /@finalizeHook@/ function if it exists,
-- and frees the memory allocated for the t'GI.GLib.Structs.Hook.Hook'.
hookFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Hook
    -- ^ /@hook@/: the t'GI.GLib.Structs.Hook.Hook' to free
    -> m ()
hookFree :: HookList -> Hook -> m ()
hookFree hookList :: HookList
hookList hook :: Hook
hook = 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 Hook
hook' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
hook
    Ptr HookList -> Ptr Hook -> IO ()
g_hook_free Ptr HookList
hookList' Ptr Hook
hook'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
hook
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Hook::insert_before
-- method type : MemberFunction
-- 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 = "sibling"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GHook to insert the new #GHook before"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hook"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GHook to insert"
--                 , 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_insert_before" g_hook_insert_before :: 
    Ptr GLib.HookList.HookList ->           -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    Ptr Hook ->                             -- sibling : TInterface (Name {namespace = "GLib", name = "Hook"})
    Ptr Hook ->                             -- hook : TInterface (Name {namespace = "GLib", name = "Hook"})
    IO ()

-- | Inserts a t'GI.GLib.Structs.Hook.Hook' into a t'GI.GLib.Structs.HookList.HookList', before a given t'GI.GLib.Structs.Hook.Hook'.
hookInsertBefore ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Maybe (Hook)
    -- ^ /@sibling@/: the t'GI.GLib.Structs.Hook.Hook' to insert the new t'GI.GLib.Structs.Hook.Hook' before
    -> Hook
    -- ^ /@hook@/: the t'GI.GLib.Structs.Hook.Hook' to insert
    -> m ()
hookInsertBefore :: HookList -> Maybe Hook -> Hook -> m ()
hookInsertBefore hookList :: HookList
hookList sibling :: Maybe Hook
sibling hook :: Hook
hook = 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 Hook
maybeSibling <- case Maybe Hook
sibling of
        Nothing -> Ptr Hook -> IO (Ptr Hook)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Hook
forall a. Ptr a
nullPtr
        Just jSibling :: Hook
jSibling -> do
            Ptr Hook
jSibling' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
jSibling
            Ptr Hook -> IO (Ptr Hook)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Hook
jSibling'
    Ptr Hook
hook' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
hook
    Ptr HookList -> Ptr Hook -> Ptr Hook -> IO ()
g_hook_insert_before Ptr HookList
hookList' Ptr Hook
maybeSibling Ptr Hook
hook'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    Maybe Hook -> (Hook -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Hook
sibling Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
hook
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Hook::prepend
-- method type : MemberFunction
-- 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"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GHook to add to the start of @hook_list"
--                 , 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_prepend" g_hook_prepend :: 
    Ptr GLib.HookList.HookList ->           -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    Ptr Hook ->                             -- hook : TInterface (Name {namespace = "GLib", name = "Hook"})
    IO ()

-- | Prepends a t'GI.GLib.Structs.Hook.Hook' on the start of a t'GI.GLib.Structs.HookList.HookList'.
hookPrepend ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Hook
    -- ^ /@hook@/: the t'GI.GLib.Structs.Hook.Hook' to add to the start of /@hookList@/
    -> m ()
hookPrepend :: HookList -> Hook -> m ()
hookPrepend hookList :: HookList
hookList hook :: Hook
hook = 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 Hook
hook' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
hook
    Ptr HookList -> Ptr Hook -> IO ()
g_hook_prepend Ptr HookList
hookList' Ptr Hook
hook'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
hook
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Hook::unref
-- method type : MemberFunction
-- 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"
--           , argType = TInterface Name { namespace = "GLib" , name = "Hook" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GHook to unref"
--                 , 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_unref" g_hook_unref :: 
    Ptr GLib.HookList.HookList ->           -- hook_list : TInterface (Name {namespace = "GLib", name = "HookList"})
    Ptr Hook ->                             -- hook : TInterface (Name {namespace = "GLib", name = "Hook"})
    IO ()

-- | Decrements the reference count of a t'GI.GLib.Structs.Hook.Hook'.
-- If the reference count falls to 0, the t'GI.GLib.Structs.Hook.Hook' is removed
-- from the t'GI.GLib.Structs.HookList.HookList' and 'GI.GLib.Functions.hookFree' is called to free it.
hookUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    -- ^ /@hookList@/: a t'GI.GLib.Structs.HookList.HookList'
    -> Hook
    -- ^ /@hook@/: the t'GI.GLib.Structs.Hook.Hook' to unref
    -> m ()
hookUnref :: HookList -> Hook -> m ()
hookUnref hookList :: HookList
hookList hook :: Hook
hook = 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 Hook
hook' <- Hook -> IO (Ptr Hook)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hook
hook
    Ptr HookList -> Ptr Hook -> IO ()
g_hook_unref Ptr HookList
hookList' Ptr Hook
hook'
    HookList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr HookList
hookList
    Hook -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hook
hook
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveHookMethod (t :: Symbol) (o :: *) :: * where
    ResolveHookMethod "compareIds" o = HookCompareIdsMethodInfo
    ResolveHookMethod l o = O.MethodResolutionFailed l o

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

#endif