{-# LANGUAGE TypeApplications #-} -- | Copyright : Will Thompson, Iñaki García Etxebarria and Jonas Platte -- 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 -- ** Overloaded methods #method:Overloaded 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.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.Text as T import qualified Data.ByteString.Char8 as B import qualified Data.Map as Map import qualified Foreign.Ptr as FP import qualified GHC.OverloadedLabels as OL -- | 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 /= :: CClosure -> CClosure -> Bool $c/= :: CClosure -> CClosure -> Bool == :: CClosure -> CClosure -> Bool $c== :: 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 :: m CClosure newZeroCClosure = IO CClosure -> m CClosure 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 (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 :: (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 (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 :: CClosure -> m (Maybe (GClosure ())) getCClosureClosure CClosure s = IO (Maybe (GClosure ())) -> m (Maybe (GClosure ())) 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 (m :: * -> *) a. Monad m => a -> m a return GClosure () val'' Maybe (GClosure ()) -> IO (Maybe (GClosure ())) 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 :: CClosure -> Ptr (GClosure ()) -> m () setCClosureClosure CClosure s Ptr (GClosure ()) val = IO () -> m () 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 :: CClosure -> m () clearCClosureClosure CClosure s = IO () -> m () 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 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 :: CClosure -> m (Ptr ()) getCClosureCallback CClosure s = IO (Ptr ()) -> m (Ptr ()) forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ()) forall a b. (a -> b) -> a -> b $ 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 (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 :: CClosure -> Ptr () -> m () setCClosureCallback CClosure s Ptr () val = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ 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 :: CClosure -> m () clearCClosureCallback CClosure s = IO () -> m () 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 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, *)]) #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 -- , 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 -- , 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 -- , 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 -- , 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 -- , 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 -- , 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 @/GClosureMarshal/@ 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 :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "a #GValue which can store the returned #gboolean" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue array holding instance and arg1" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @gboolean (*callback) (gpointer instance, gint arg1, gpointer user_data)@ where the @/gint/@ parameter -- denotes a flags type. cClosureMarshalBOOLEAN_FLAGS :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: a t'GI.GObject.Structs.Value.Value' which can store the returned t'P.Bool' -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding instance and arg1 -> 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 -> m () cClosureMarshalBOOLEAN_FLAGS :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "a #GValue, which can store the returned string" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "3" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "a #GValue array holding instance, arg1 and arg2" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @gchar* (*callback) (gpointer instance, GObject *arg1, gpointer arg2, gpointer user_data)@. cClosureMarshalSTRING_OBJECTPOINTER :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: a t'GI.GObject.Structs.Value.Value', which can store the returned string -> Word32 -- ^ /@nParamValues@/: 3 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding instance, arg1 and arg2 -> 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 -> m () cClosureMarshalSTRING_OBJECTPOINTER :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gboolean parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gboolean arg1, gpointer user_data)@. cClosureMarshalVOID_BOOLEAN :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the t'P.Bool' parameter -> 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 -> m () cClosureMarshalVOID_BOOLEAN :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #GBoxed* parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, GBoxed *arg1, gpointer user_data)@. cClosureMarshalVOID_BOXED :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/GBoxed/@* parameter -> 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 -> m () cClosureMarshalVOID_BOXED :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gchar parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gchar arg1, gpointer user_data)@. cClosureMarshalVOID_CHAR :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gchar/@ parameter -> 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 -> m () cClosureMarshalVOID_CHAR :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gdouble parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gdouble arg1, gpointer user_data)@. cClosureMarshalVOID_DOUBLE :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gdouble/@ parameter -> 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 -> m () cClosureMarshalVOID_DOUBLE :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the enumeration parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gint arg1, gpointer user_data)@ where the @/gint/@ parameter denotes an enumeration type.. cClosureMarshalVOID_ENUM :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the enumeration parameter -> 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 -> m () cClosureMarshalVOID_ENUM :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "a #GValue array holding the instance and the flags parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gint arg1, gpointer user_data)@ where the @/gint/@ parameter denotes a flags type. cClosureMarshalVOID_FLAGS :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the flags parameter -> 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 -> m () cClosureMarshalVOID_FLAGS :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gfloat parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gfloat arg1, gpointer user_data)@. cClosureMarshalVOID_FLOAT :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gfloat/@ parameter -> 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 -> m () cClosureMarshalVOID_FLOAT :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "a #GValue array holding the instance and the #gint parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gint arg1, gpointer user_data)@. cClosureMarshalVOID_INT :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gint/@ parameter -> 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 -> m () cClosureMarshalVOID_INT :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #glong parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, glong arg1, gpointer user_data)@. cClosureMarshalVOID_LONG :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/glong/@ parameter -> 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 -> m () cClosureMarshalVOID_LONG :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #GObject* parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, GObject *arg1, gpointer user_data)@. cClosureMarshalVOID_OBJECT :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the t'GI.GObject.Objects.Object.Object'* parameter -> 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 -> m () cClosureMarshalVOID_OBJECT :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #GParamSpec* parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, GParamSpec *arg1, gpointer user_data)@. cClosureMarshalVOID_PARAM :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the t'GI.GObject.Objects.ParamSpec.ParamSpec'* parameter -> 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 -> m () cClosureMarshalVOID_PARAM :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gpointer parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gpointer arg1, gpointer user_data)@. cClosureMarshalVOID_POINTER :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gpointer/@ parameter -> 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 -> m () cClosureMarshalVOID_POINTER :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gchar* parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, const gchar *arg1, gpointer user_data)@. cClosureMarshalVOID_STRING :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gchar/@* parameter -> 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 -> m () cClosureMarshalVOID_STRING :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #guchar parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, guchar arg1, gpointer user_data)@. cClosureMarshalVOID_UCHAR :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/guchar/@ parameter -> 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 -> m () cClosureMarshalVOID_UCHAR :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #guint parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, guint arg1, gpointer user_data)@. cClosureMarshalVOID_UINT :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/guint/@ parameter -> 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 -> m () cClosureMarshalVOID_UINT :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "3" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "a #GValue array holding instance, arg1 and arg2" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, guint arg1, gpointer arg2, gpointer user_data)@. cClosureMarshalVOID_UINTPOINTER :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 3 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding instance, arg1 and arg2 -> 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 -> m () cClosureMarshalVOID_UINTPOINTER :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #gulong parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gulong arg1, gpointer user_data)@. cClosureMarshalVOID_ULONG :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the @/gulong/@ parameter -> 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 -> m () cClosureMarshalVOID_ULONG :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "2" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GValue array holding the instance and the #GVariant* parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, GVariant *arg1, gpointer user_data)@. -- -- /Since: 2.26/ cClosureMarshalVOID_VARIANT :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 2 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding the instance and the t'GVariant'* parameter -> 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 -> m () cClosureMarshalVOID_VARIANT :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 "the #GClosure to which the marshaller belongs" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "ignored" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_param_values" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Just "1" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_values" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue array holding only the instance" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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\n to g_closure_invoke()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "marshal_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "additional data specified when registering the marshaller" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = 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 marshaller for a t'GI.GObject.Structs.CClosure.CClosure' with a callback of type -- @void (*callback) (gpointer instance, gpointer user_data)@. cClosureMarshalVOID_VOID :: (B.CallStack.HasCallStack, MonadIO m) => GClosure a -- ^ /@closure@/: the t'GI.GObject.Structs.Closure.Closure' to which the marshaller belongs -> GValue -- ^ /@returnValue@/: ignored -> Word32 -- ^ /@nParamValues@/: 1 -> GValue -- ^ /@paramValues@/: a t'GI.GObject.Structs.Value.Value' array holding only the instance -> 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 -> m () cClosureMarshalVOID_VOID :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnValue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () 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 -- , 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 -- , 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 -- , 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 -- , 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 -- , 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 -- , 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 :: 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 (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 Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue returnGvalue' Ptr GValue -> IO () B.GValue.unsetGValue Ptr GValue paramValues' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) #endif #if defined(ENABLE_OVERLOADING) type family ResolveCClosureMethod (t :: Symbol) (o :: *) :: * where ResolveCClosureMethod l o = O.MethodResolutionFailed l o instance (info ~ ResolveCClosureMethod t CClosure, O.MethodInfo 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 #endif