{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.GObject.Structs.CClosure.CClosure' is a specialization of t'GI.GObject.Structs.Closure.Closure' for C function callbacks.

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

module GI.GObject.Structs.CClosure
    ( 

-- * Exported types
    CClosure(..)                            ,
    newZeroCClosure                         ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveCClosureMethod                   ,
#endif

-- ** marshalBOOLEAN_BOXEDBOXED #method:marshalBOOLEAN_BOXEDBOXED#

    cClosureMarshalBOOLEAN_BOXEDBOXED       ,


-- ** marshalBOOLEAN_FLAGS #method:marshalBOOLEAN_FLAGS#

    cClosureMarshalBOOLEAN_FLAGS            ,


-- ** marshalGeneric #method:marshalGeneric#

    cClosureMarshalGeneric                  ,


-- ** marshalSTRING_OBJECTPOINTER #method:marshalSTRING_OBJECTPOINTER#

    cClosureMarshalSTRING_OBJECTPOINTER     ,


-- ** marshalVOID_BOOLEAN #method:marshalVOID_BOOLEAN#

    cClosureMarshalVOID_BOOLEAN             ,


-- ** marshalVOID_BOXED #method:marshalVOID_BOXED#

    cClosureMarshalVOID_BOXED               ,


-- ** marshalVOID_CHAR #method:marshalVOID_CHAR#

    cClosureMarshalVOID_CHAR                ,


-- ** marshalVOID_DOUBLE #method:marshalVOID_DOUBLE#

    cClosureMarshalVOID_DOUBLE              ,


-- ** marshalVOID_ENUM #method:marshalVOID_ENUM#

    cClosureMarshalVOID_ENUM                ,


-- ** marshalVOID_FLAGS #method:marshalVOID_FLAGS#

    cClosureMarshalVOID_FLAGS               ,


-- ** marshalVOID_FLOAT #method:marshalVOID_FLOAT#

    cClosureMarshalVOID_FLOAT               ,


-- ** marshalVOID_INT #method:marshalVOID_INT#

    cClosureMarshalVOID_INT                 ,


-- ** marshalVOID_LONG #method:marshalVOID_LONG#

    cClosureMarshalVOID_LONG                ,


-- ** marshalVOID_OBJECT #method:marshalVOID_OBJECT#

    cClosureMarshalVOID_OBJECT              ,


-- ** marshalVOID_PARAM #method:marshalVOID_PARAM#

    cClosureMarshalVOID_PARAM               ,


-- ** marshalVOID_POINTER #method:marshalVOID_POINTER#

    cClosureMarshalVOID_POINTER             ,


-- ** marshalVOID_STRING #method:marshalVOID_STRING#

    cClosureMarshalVOID_STRING              ,


-- ** marshalVOID_UCHAR #method:marshalVOID_UCHAR#

    cClosureMarshalVOID_UCHAR               ,


-- ** marshalVOID_UINT #method:marshalVOID_UINT#

    cClosureMarshalVOID_UINT                ,


-- ** marshalVOID_UINTPOINTER #method:marshalVOID_UINTPOINTER#

    cClosureMarshalVOID_UINTPOINTER         ,


-- ** marshalVOID_ULONG #method:marshalVOID_ULONG#

    cClosureMarshalVOID_ULONG               ,


-- ** marshalVOID_VARIANT #method:marshalVOID_VARIANT#

    cClosureMarshalVOID_VARIANT             ,


-- ** marshalVOID_VOID #method:marshalVOID_VOID#

    cClosureMarshalVOID_VOID                ,




 -- * Properties


-- ** callback #attr:callback#
-- | the callback function

#if defined(ENABLE_OVERLOADING)
    cClosure_callback                       ,
#endif
    clearCClosureCallback                   ,
    getCClosureCallback                     ,
    setCClosureCallback                     ,


-- ** closure #attr:closure#
-- | the t'GI.GObject.Structs.Closure.Closure'

#if defined(ENABLE_OVERLOADING)
    cClosure_closure                        ,
#endif
    clearCClosureClosure                    ,
    getCClosureClosure                      ,
    setCClosureClosure                      ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)

#else

#endif

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

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

instance BoxedPtr CClosure where
    boxedPtrCopy :: CClosure -> IO CClosure
boxedPtrCopy = \CClosure
p -> CClosure -> (Ptr CClosure -> IO CClosure) -> IO CClosure
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CClosure
p (Int -> Ptr CClosure -> IO (Ptr CClosure)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
72 (Ptr CClosure -> IO (Ptr CClosure))
-> (Ptr CClosure -> IO CClosure) -> Ptr CClosure -> IO CClosure
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr CClosure -> CClosure) -> Ptr CClosure -> IO CClosure
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr CClosure -> CClosure
CClosure)
    boxedPtrFree :: CClosure -> IO ()
boxedPtrFree = \CClosure
x -> CClosure -> (Ptr CClosure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr CClosure
x Ptr CClosure -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr CClosure where
    boxedPtrCalloc :: IO (Ptr CClosure)
boxedPtrCalloc = Int -> IO (Ptr CClosure)
forall a. Int -> IO (Ptr a)
callocBytes Int
72


-- | Construct a `CClosure` struct initialized to zero.
newZeroCClosure :: MonadIO m => m CClosure
newZeroCClosure :: forall (m :: * -> *). MonadIO m => m CClosure
newZeroCClosure = IO CClosure -> m CClosure
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CClosure -> m CClosure) -> IO CClosure -> m CClosure
forall a b. (a -> b) -> a -> b
$ IO (Ptr CClosure)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr CClosure) -> (Ptr CClosure -> IO CClosure) -> IO CClosure
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr CClosure -> CClosure) -> Ptr CClosure -> IO CClosure
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr CClosure -> CClosure
CClosure

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


-- | Get the value of the “@closure@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cClosure #closure
-- @
getCClosureClosure :: MonadIO m => CClosure -> m (Maybe (GClosure ()))
getCClosureClosure :: forall (m :: * -> *).
MonadIO m =>
CClosure -> m (Maybe (GClosure ()))
getCClosureClosure CClosure
s = IO (Maybe (GClosure ())) -> m (Maybe (GClosure ()))
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (GClosure ())) -> m (Maybe (GClosure ())))
-> IO (Maybe (GClosure ())) -> m (Maybe (GClosure ()))
forall a b. (a -> b) -> a -> b
$ CClosure
-> (Ptr CClosure -> IO (Maybe (GClosure ())))
-> IO (Maybe (GClosure ()))
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr CClosure
s ((Ptr CClosure -> IO (Maybe (GClosure ())))
 -> IO (Maybe (GClosure ())))
-> (Ptr CClosure -> IO (Maybe (GClosure ())))
-> IO (Maybe (GClosure ()))
forall a b. (a -> b) -> a -> b
$ \Ptr CClosure
ptr -> do
    Ptr (GClosure ())
val <- Ptr (Ptr (GClosure ())) -> IO (Ptr (GClosure ()))
forall a. Storable a => Ptr a -> IO a
peek (Ptr CClosure
ptr Ptr CClosure -> Int -> Ptr (Ptr (GClosure ()))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr (GClosure ()))
    Maybe (GClosure ())
result <- Ptr (GClosure ())
-> (Ptr (GClosure ()) -> IO (GClosure ()))
-> IO (Maybe (GClosure ()))
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr (GClosure ())
val ((Ptr (GClosure ()) -> IO (GClosure ()))
 -> IO (Maybe (GClosure ())))
-> (Ptr (GClosure ()) -> IO (GClosure ()))
-> IO (Maybe (GClosure ()))
forall a b. (a -> b) -> a -> b
$ \Ptr (GClosure ())
val' -> do
        GClosure ()
val'' <- (Ptr (GClosure ()) -> IO (GClosure ())
forall a. Ptr (GClosure a) -> IO (GClosure a)
B.GClosure.newGClosureFromPtr (Ptr (GClosure ()) -> IO (GClosure ()))
-> (Ptr (GClosure ()) -> Ptr (GClosure ()))
-> Ptr (GClosure ())
-> IO (GClosure ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (GClosure ()) -> Ptr (GClosure ())
forall a b. Ptr a -> Ptr b
FP.castPtr) Ptr (GClosure ())
val'
        GClosure () -> IO (GClosure ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GClosure ()
val''
    Maybe (GClosure ()) -> IO (Maybe (GClosure ()))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (GClosure ())
result

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

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

#if defined(ENABLE_OVERLOADING)
data CClosureClosureFieldInfo
instance AttrInfo CClosureClosureFieldInfo where
    type AttrBaseTypeConstraint CClosureClosureFieldInfo = (~) CClosure
    type AttrAllowedOps CClosureClosureFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint CClosureClosureFieldInfo = (~) (Ptr (GClosure ()))
    type AttrTransferTypeConstraint CClosureClosureFieldInfo = (~)(Ptr (GClosure ()))
    type AttrTransferType CClosureClosureFieldInfo = (Ptr (GClosure ()))
    type AttrGetType CClosureClosureFieldInfo = Maybe (GClosure ())
    type AttrLabel CClosureClosureFieldInfo = "closure"
    type AttrOrigin CClosureClosureFieldInfo = CClosure
    attrGet = getCClosureClosure
    attrSet = setCClosureClosure
    attrConstruct = undefined
    attrClear = clearCClosureClosure
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.CClosure.closure"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-CClosure.html#g:attr:closure"
        })

cClosure_closure :: AttrLabelProxy "closure"
cClosure_closure = AttrLabelProxy

#endif


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

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

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

#if defined(ENABLE_OVERLOADING)
data CClosureCallbackFieldInfo
instance AttrInfo CClosureCallbackFieldInfo where
    type AttrBaseTypeConstraint CClosureCallbackFieldInfo = (~) CClosure
    type AttrAllowedOps CClosureCallbackFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint CClosureCallbackFieldInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint CClosureCallbackFieldInfo = (~)(Ptr ())
    type AttrTransferType CClosureCallbackFieldInfo = (Ptr ())
    type AttrGetType CClosureCallbackFieldInfo = Ptr ()
    type AttrLabel CClosureCallbackFieldInfo = "callback"
    type AttrOrigin CClosureCallbackFieldInfo = CClosure
    attrGet = getCClosureCallback
    attrSet = setCClosureCallback
    attrConstruct = undefined
    attrClear = clearCClosureCallback
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.CClosure.callback"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-CClosure.html#g:attr:callback"
        })

cClosure_callback :: AttrLabelProxy "callback"
cClosure_callback = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CClosure
type instance O.AttributeList CClosure = CClosureAttributeList
type CClosureAttributeList = ('[ '("closure", CClosureClosureFieldInfo), '("callback", CClosureCallbackFieldInfo)] :: [(Symbol, DK.Type)])
#endif

-- method CClosure::marshal_BOOLEAN__BOXED_BOXED
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_BOOLEAN__BOXED_BOXED" g_cclosure_marshal_BOOLEAN__BOXED_BOXED :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with handlers that
-- take two boxed pointers as arguments and return a boolean.  If you
-- have such a signal, you will probably also need to use an
-- accumulator, such as 'GI.GObject.Functions.signalAccumulatorTrueHandled'.
cClosureMarshalBOOLEAN_BOXEDBOXED ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalBOOLEAN_BOXEDBOXED :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalBOOLEAN_BOXEDBOXED GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_BOOLEAN__BOXED_BOXED Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_BOOLEAN__FLAGS
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_BOOLEAN__FLAGS" g_cclosure_marshal_BOOLEAN__FLAGS :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with handlers that
-- take a flags type as an argument and return a boolean.  If you have
-- such a signal, you will probably also need to use an accumulator,
-- such as 'GI.GObject.Functions.signalAccumulatorTrueHandled'.
cClosureMarshalBOOLEAN_FLAGS ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalBOOLEAN_FLAGS :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalBOOLEAN_FLAGS GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_BOOLEAN__FLAGS Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_STRING__OBJECT_POINTER
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_STRING__OBJECT_POINTER" g_cclosure_marshal_STRING__OBJECT_POINTER :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with handlers that
-- take a t'GI.GObject.Objects.Object.Object' and a pointer and produce a string.  It is highly
-- unlikely that your signal handler fits this description.
cClosureMarshalSTRING_OBJECTPOINTER ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalSTRING_OBJECTPOINTER :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalSTRING_OBJECTPOINTER GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_STRING__OBJECT_POINTER Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__BOOLEAN
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__BOOLEAN" g_cclosure_marshal_VOID__BOOLEAN :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- boolean argument.
cClosureMarshalVOID_BOOLEAN ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_BOOLEAN :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_BOOLEAN GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__BOOLEAN Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__BOXED
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__BOXED" g_cclosure_marshal_VOID__BOXED :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- argument which is any boxed pointer type.
cClosureMarshalVOID_BOXED ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_BOXED :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_BOXED GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__BOXED Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__CHAR
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__CHAR" g_cclosure_marshal_VOID__CHAR :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- character argument.
cClosureMarshalVOID_CHAR ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_CHAR :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_CHAR GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__CHAR Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__DOUBLE
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__DOUBLE" g_cclosure_marshal_VOID__DOUBLE :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with one
-- double-precision floating point argument.
cClosureMarshalVOID_DOUBLE ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_DOUBLE :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_DOUBLE GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__DOUBLE Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__ENUM
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__ENUM" g_cclosure_marshal_VOID__ENUM :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- argument with an enumerated type.
cClosureMarshalVOID_ENUM ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_ENUM :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_ENUM GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__ENUM Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__FLAGS
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__FLAGS" g_cclosure_marshal_VOID__FLAGS :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- argument with a flags types.
cClosureMarshalVOID_FLAGS ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_FLAGS :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_FLAGS GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__FLAGS Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__FLOAT
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__FLOAT" g_cclosure_marshal_VOID__FLOAT :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with one
-- single-precision floating point argument.
cClosureMarshalVOID_FLOAT ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_FLOAT :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_FLOAT GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__FLOAT Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__INT
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__INT" g_cclosure_marshal_VOID__INT :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- integer argument.
cClosureMarshalVOID_INT ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_INT :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_INT GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__INT Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__LONG
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__LONG" g_cclosure_marshal_VOID__LONG :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with with a single
-- long integer argument.
cClosureMarshalVOID_LONG ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_LONG :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_LONG GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__LONG Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__OBJECT
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__OBJECT" g_cclosure_marshal_VOID__OBJECT :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- t'GI.GObject.Objects.Object.Object' argument.
cClosureMarshalVOID_OBJECT ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_OBJECT :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_OBJECT GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__OBJECT Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__PARAM
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__PARAM" g_cclosure_marshal_VOID__PARAM :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- argument of type t'GI.GObject.Objects.ParamSpec.ParamSpec'.
cClosureMarshalVOID_PARAM ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_PARAM :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_PARAM GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__PARAM Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__POINTER
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__POINTER" g_cclosure_marshal_VOID__POINTER :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single raw
-- pointer argument type.
-- 
-- If it is possible, it is better to use one of the more specific
-- functions such as 'GI.GObject.Functions.cclosureMarshalVOID_OBJECT' or
-- 'GI.GObject.Functions.cclosureMarshalVOID_OBJECT'.
cClosureMarshalVOID_POINTER ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_POINTER :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_POINTER GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__POINTER Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__STRING
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__STRING" g_cclosure_marshal_VOID__STRING :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single string
-- argument.
cClosureMarshalVOID_STRING ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_STRING :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_STRING GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__STRING Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__UCHAR
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__UCHAR" g_cclosure_marshal_VOID__UCHAR :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- unsigned character argument.
cClosureMarshalVOID_UCHAR ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_UCHAR :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_UCHAR GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__UCHAR Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__UINT
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__UINT" g_cclosure_marshal_VOID__UINT :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with with a single
-- unsigned integer argument.
cClosureMarshalVOID_UINT ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_UINT :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_UINT GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__UINT Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__UINT_POINTER
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__UINT_POINTER" g_cclosure_marshal_VOID__UINT_POINTER :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with an unsigned int
-- and a pointer as arguments.
cClosureMarshalVOID_UINTPOINTER ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_UINTPOINTER :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_UINTPOINTER GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__UINT_POINTER Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__ULONG
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__ULONG" g_cclosure_marshal_VOID__ULONG :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- unsigned long integer argument.
cClosureMarshalVOID_ULONG ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_ULONG :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_ULONG GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__ULONG Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__VARIANT
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__VARIANT" g_cclosure_marshal_VOID__VARIANT :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with a single
-- t'GVariant' argument.
cClosureMarshalVOID_VARIANT ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_VARIANT :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_VARIANT GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__VARIANT Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_VOID__VOID
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_VOID__VOID" g_cclosure_marshal_VOID__VOID :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_value : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A t'GI.GObject.Callbacks.ClosureMarshal' function for use with signals with no arguments.
cClosureMarshalVOID_VOID ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnValue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalVOID_VOID :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalVOID_VOID GClosure a
closure GValue
returnValue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnValue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_VOID__VOID Ptr (GClosure ())
closure' Ptr GValue
returnValue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnValue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method CClosure::marshal_generic
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GClosure." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_gvalue"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GValue to store the return value. May be %NULL\n  if the callback of closure doesn't return a value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_param_values"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the @param_values array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "param_values"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An array of #GValues holding the arguments\n  on which to invoke the callback of closure."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "invocation_hint"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The invocation hint given as the last argument to\n  g_closure_invoke()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "marshal_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Additional data specified when registering the\n  marshaller, see g_closure_set_marshal() and\n  g_closure_set_meta_marshal()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_cclosure_marshal_generic" g_cclosure_marshal_generic :: 
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Ptr GValue ->                           -- return_gvalue : TGValue
    Word32 ->                               -- n_param_values : TBasicType TUInt
    Ptr GValue ->                           -- param_values : TGValue
    Ptr () ->                               -- invocation_hint : TBasicType TPtr
    Ptr () ->                               -- marshal_data : TBasicType TPtr
    IO ()

-- | A generic marshaller function implemented via
-- <http://sourceware.org/libffi/ libffi>.
-- 
-- Normally this function is not passed explicitly to @/g_signal_new()/@,
-- but used automatically by GLib when specifying a 'P.Nothing' marshaller.
-- 
-- /Since: 2.30/
cClosureMarshalGeneric ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GClosure a
    -- ^ /@closure@/: A t'GI.GObject.Structs.Closure.Closure'.
    -> GValue
    -- ^ /@returnGvalue@/: A t'GI.GObject.Structs.Value.Value' to store the return value. May be 'P.Nothing'
    --   if the callback of closure doesn\'t return a value.
    -> Word32
    -- ^ /@nParamValues@/: The length of the /@paramValues@/ array.
    -> GValue
    -- ^ /@paramValues@/: An array of @/GValues/@ holding the arguments
    --   on which to invoke the callback of closure.
    -> Ptr ()
    -- ^ /@invocationHint@/: The invocation hint given as the last argument to
    --   'GI.GObject.Structs.Closure.closureInvoke'.
    -> Ptr ()
    -- ^ /@marshalData@/: Additional data specified when registering the
    --   marshaller, see @/g_closure_set_marshal()/@ and
    --   @/g_closure_set_meta_marshal()/@
    -> m ()
cClosureMarshalGeneric :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GClosure a
-> GValue -> Word32 -> GValue -> Ptr () -> Ptr () -> m ()
cClosureMarshalGeneric GClosure a
closure GValue
returnGvalue Word32
nParamValues GValue
paramValues Ptr ()
invocationHint Ptr ()
marshalData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr GValue
returnGvalue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
returnGvalue
    Ptr GValue
paramValues' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
paramValues
    Ptr (GClosure ())
-> Ptr GValue -> Word32 -> Ptr GValue -> Ptr () -> Ptr () -> IO ()
g_cclosure_marshal_generic Ptr (GClosure ())
closure' Ptr GValue
returnGvalue' Word32
nParamValues Ptr GValue
paramValues' Ptr ()
invocationHint Ptr ()
marshalData
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
returnGvalue
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
paramValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveCClosureMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveCClosureMethod l o = O.MethodResolutionFailed l o

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

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

#endif

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

#endif