{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

The 'GI.GLib.Structs.Hook.Hook' struct represents a single hook function in a 'GI.GLib.Structs.HookList.HookList'.
-}

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

module GI.GLib.Structs.Hook
    (

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


 -- * Methods
-- ** compareIds #method:compareIds#

#if 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 ENABLE_OVERLOADING
    hook_data                               ,
#endif
    setHookData                             ,


-- ** destroy #attr:destroy#
{- | the default /@finalizeHook@/ function of a 'GI.GLib.Structs.HookList.HookList' calls
    this member of the hook that is being finalized
-}
    clearHookDestroy                        ,
    getHookDestroy                          ,
#if ENABLE_OVERLOADING
    hook_destroy                            ,
#endif
    setHookDestroy                          ,


-- ** flags #attr:flags#
{- | flags which are set for this hook. See 'GI.GLib.Flags.HookFlagMask' for
    predefined flags
-}
    getHookFlags                            ,
#if 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 'GI.GLib.Callbacks.HookFunc' and 'GI.GLib.Callbacks.HookCheckFunc'
-}
    clearHookFunc                           ,
    getHookFunc                             ,
#if ENABLE_OVERLOADING
    hook_func                               ,
#endif
    setHookFunc                             ,


-- ** hookId #attr:hookId#
{- | the id of this hook, which is unique within its list
-}
    getHookHookId                           ,
#if ENABLE_OVERLOADING
    hook_hookId                             ,
#endif
    setHookHookId                           ,


-- ** next #attr:next#
{- | pointer to the next hook in the list
-}
    clearHookNext                           ,
    getHookNext                             ,
#if ENABLE_OVERLOADING
    hook_next                               ,
#endif
    setHookNext                             ,


-- ** prev #attr:prev#
{- | pointer to the previous hook in the list
-}
    clearHookPrev                           ,
    getHookPrev                             ,
#if ENABLE_OVERLOADING
    hook_prev                               ,
#endif
    setHookPrev                             ,


-- ** refCount #attr:refCount#
{- | the reference count of this hook
-}
    getHookRefCount                         ,
#if 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.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)
instance WrappedPtr Hook where
    wrappedPtrCalloc = callocBytes 64
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 64 >=> wrapPtr Hook)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `Hook` struct initialized to zero.
newZeroHook :: MonadIO m => m Hook
newZeroHook = liftIO $ wrappedPtrCalloc >>= wrapPtr Hook

instance tag ~ 'AttrSet => Constructible Hook tag where
    new _ attrs = do
        o <- newZeroHook
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `Hook`.
noHook :: Maybe Hook
noHook = 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr ())
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr ())

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Hook)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr Hook) val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Hook)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (Ptr Hook)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr Hook) val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr Hook)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO Word32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Word32)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO CULong
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: CULong)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO Word32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: Word32)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO (Ptr ())
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (FP.nullPtr :: Ptr ())

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO (FunPtr GLib.Callbacks.C_DestroyNotify)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GLib.Callbacks.dynamic_DestroyNotify val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_DestroyNotify)

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

hook_destroy :: AttrLabelProxy "destroy"
hook_destroy = AttrLabelProxy

#endif



#if 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 '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 'GI.GLib.Structs.Hook.Hook' -}
    -> Hook
    {- ^ /@sibling@/: a '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 newHook sibling = liftIO $ do
    newHook' <- unsafeManagedPtrGetPtr newHook
    sibling' <- unsafeManagedPtrGetPtr sibling
    result <- g_hook_compare_ids newHook' sibling'
    touchManagedPtr newHook
    touchManagedPtr sibling
    return result

#if 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 'GI.GLib.Structs.Hook.Hook', given its ID.
-}
hookDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    {- ^ /@hookList@/: a 'GI.GLib.Structs.HookList.HookList' -}
    -> CULong
    {- ^ /@hookId@/: a hook ID -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the 'GI.GLib.Structs.Hook.Hook' was found in the 'GI.GLib.Structs.HookList.HookList' and destroyed -}
hookDestroy hookList hookId = liftIO $ do
    hookList' <- unsafeManagedPtrGetPtr hookList
    result <- g_hook_destroy hookList' hookId
    let result' = (/= 0) result
    touchManagedPtr hookList
    return result'

#if 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 'GI.GLib.Structs.Hook.Hook' from a '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 'GI.GLib.Structs.HookList.HookList' -}
    -> Hook
    {- ^ /@hook@/: the 'GI.GLib.Structs.Hook.Hook' to remove -}
    -> m ()
hookDestroyLink hookList hook = liftIO $ do
    hookList' <- unsafeManagedPtrGetPtr hookList
    hook' <- unsafeManagedPtrGetPtr hook
    g_hook_destroy_link hookList' hook'
    touchManagedPtr hookList
    touchManagedPtr hook
    return ()

#if 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 'GI.GLib.Structs.HookList.HookList' /@finalizeHook@/ function if it exists,
and frees the memory allocated for the 'GI.GLib.Structs.Hook.Hook'.
-}
hookFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    {- ^ /@hookList@/: a 'GI.GLib.Structs.HookList.HookList' -}
    -> Hook
    {- ^ /@hook@/: the 'GI.GLib.Structs.Hook.Hook' to free -}
    -> m ()
hookFree hookList hook = liftIO $ do
    hookList' <- unsafeManagedPtrGetPtr hookList
    hook' <- unsafeManagedPtrGetPtr hook
    g_hook_free hookList' hook'
    touchManagedPtr hookList
    touchManagedPtr hook
    return ()

#if 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 'GI.GLib.Structs.Hook.Hook' into a 'GI.GLib.Structs.HookList.HookList', before a given 'GI.GLib.Structs.Hook.Hook'.
-}
hookInsertBefore ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    {- ^ /@hookList@/: a 'GI.GLib.Structs.HookList.HookList' -}
    -> Maybe (Hook)
    {- ^ /@sibling@/: the 'GI.GLib.Structs.Hook.Hook' to insert the new 'GI.GLib.Structs.Hook.Hook' before -}
    -> Hook
    {- ^ /@hook@/: the 'GI.GLib.Structs.Hook.Hook' to insert -}
    -> m ()
hookInsertBefore hookList sibling hook = liftIO $ do
    hookList' <- unsafeManagedPtrGetPtr hookList
    maybeSibling <- case sibling of
        Nothing -> return nullPtr
        Just jSibling -> do
            jSibling' <- unsafeManagedPtrGetPtr jSibling
            return jSibling'
    hook' <- unsafeManagedPtrGetPtr hook
    g_hook_insert_before hookList' maybeSibling hook'
    touchManagedPtr hookList
    whenJust sibling touchManagedPtr
    touchManagedPtr hook
    return ()

#if 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 'GI.GLib.Structs.Hook.Hook' on the start of a 'GI.GLib.Structs.HookList.HookList'.
-}
hookPrepend ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.HookList.HookList
    {- ^ /@hookList@/: a 'GI.GLib.Structs.HookList.HookList' -}
    -> Hook
    {- ^ /@hook@/: the 'GI.GLib.Structs.Hook.Hook' to add to the start of /@hookList@/ -}
    -> m ()
hookPrepend hookList hook = liftIO $ do
    hookList' <- unsafeManagedPtrGetPtr hookList
    hook' <- unsafeManagedPtrGetPtr hook
    g_hook_prepend hookList' hook'
    touchManagedPtr hookList
    touchManagedPtr hook
    return ()

#if 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 'GI.GLib.Structs.Hook.Hook'.
If the reference count falls to 0, the 'GI.GLib.Structs.Hook.Hook' is removed
from the '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 'GI.GLib.Structs.HookList.HookList' -}
    -> Hook
    {- ^ /@hook@/: the 'GI.GLib.Structs.Hook.Hook' to unref -}
    -> m ()
hookUnref hookList hook = liftIO $ do
    hookList' <- unsafeManagedPtrGetPtr hookList
    hook' <- unsafeManagedPtrGetPtr hook
    g_hook_unref hookList' hook'
    touchManagedPtr hookList
    touchManagedPtr hook
    return ()

#if ENABLE_OVERLOADING
#endif

#if 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 (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif

#endif