-- | Copyright : Will Thompson, Iñaki García Etxebarria and Jonas Platte -- License : LGPL-2.1 -- Maintainer : Iñaki García Etxebarria #if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__)) #define ENABLE_OVERLOADING #endif module GI.GObject.Functions ( -- * Methods -- ** boxedCopy #method:boxedCopy# boxedCopy , -- ** boxedFree #method:boxedFree# boxedFree , -- ** enumCompleteTypeInfo #method:enumCompleteTypeInfo# enumCompleteTypeInfo , -- ** enumGetValue #method:enumGetValue# enumGetValue , -- ** enumGetValueByName #method:enumGetValueByName# enumGetValueByName , -- ** enumGetValueByNick #method:enumGetValueByNick# enumGetValueByNick , -- ** enumRegisterStatic #method:enumRegisterStatic# enumRegisterStatic , -- ** enumToString #method:enumToString# enumToString , -- ** flagsCompleteTypeInfo #method:flagsCompleteTypeInfo# flagsCompleteTypeInfo , -- ** flagsGetFirstValue #method:flagsGetFirstValue# flagsGetFirstValue , -- ** flagsGetValueByName #method:flagsGetValueByName# flagsGetValueByName , -- ** flagsGetValueByNick #method:flagsGetValueByNick# flagsGetValueByNick , -- ** flagsRegisterStatic #method:flagsRegisterStatic# flagsRegisterStatic , -- ** flagsToString #method:flagsToString# flagsToString , -- ** gtypeGetType #method:gtypeGetType# gtypeGetType , -- ** paramSpecBoolean #method:paramSpecBoolean# paramSpecBoolean , -- ** paramSpecBoxed #method:paramSpecBoxed# paramSpecBoxed , -- ** paramSpecChar #method:paramSpecChar# paramSpecChar , -- ** paramSpecDouble #method:paramSpecDouble# paramSpecDouble , -- ** paramSpecEnum #method:paramSpecEnum# paramSpecEnum , -- ** paramSpecFlags #method:paramSpecFlags# paramSpecFlags , -- ** paramSpecFloat #method:paramSpecFloat# paramSpecFloat , -- ** paramSpecGtype #method:paramSpecGtype# paramSpecGtype , -- ** paramSpecInt #method:paramSpecInt# paramSpecInt , -- ** paramSpecInt64 #method:paramSpecInt64# paramSpecInt64 , -- ** paramSpecLong #method:paramSpecLong# paramSpecLong , -- ** paramSpecObject #method:paramSpecObject# paramSpecObject , -- ** paramSpecParam #method:paramSpecParam# paramSpecParam , -- ** paramSpecPointer #method:paramSpecPointer# paramSpecPointer , -- ** paramSpecString #method:paramSpecString# paramSpecString , -- ** paramSpecUchar #method:paramSpecUchar# paramSpecUchar , -- ** paramSpecUint #method:paramSpecUint# paramSpecUint , -- ** paramSpecUint64 #method:paramSpecUint64# paramSpecUint64 , -- ** paramSpecUlong #method:paramSpecUlong# paramSpecUlong , -- ** paramSpecUnichar #method:paramSpecUnichar# paramSpecUnichar , -- ** paramSpecVariant #method:paramSpecVariant# paramSpecVariant , -- ** paramTypeRegisterStatic #method:paramTypeRegisterStatic# paramTypeRegisterStatic , -- ** paramValueConvert #method:paramValueConvert# paramValueConvert , -- ** paramValueDefaults #method:paramValueDefaults# paramValueDefaults , -- ** paramValueSetDefault #method:paramValueSetDefault# paramValueSetDefault , -- ** paramValueValidate #method:paramValueValidate# paramValueValidate , -- ** paramValuesCmp #method:paramValuesCmp# paramValuesCmp , -- ** pointerTypeRegisterStatic #method:pointerTypeRegisterStatic# pointerTypeRegisterStatic , -- ** signalAccumulatorFirstWins #method:signalAccumulatorFirstWins# signalAccumulatorFirstWins , -- ** signalAccumulatorTrueHandled #method:signalAccumulatorTrueHandled# signalAccumulatorTrueHandled , -- ** signalAddEmissionHook #method:signalAddEmissionHook# signalAddEmissionHook , -- ** signalChainFromOverridden #method:signalChainFromOverridden# signalChainFromOverridden , -- ** signalConnectClosure #method:signalConnectClosure# signalConnectClosure , -- ** signalConnectClosureById #method:signalConnectClosureById# signalConnectClosureById , -- ** signalEmitv #method:signalEmitv# signalEmitv , -- ** signalGetInvocationHint #method:signalGetInvocationHint# signalGetInvocationHint , -- ** signalHandlerBlock #method:signalHandlerBlock# signalHandlerBlock , -- ** signalHandlerDisconnect #method:signalHandlerDisconnect# signalHandlerDisconnect , -- ** signalHandlerFind #method:signalHandlerFind# signalHandlerFind , -- ** signalHandlerIsConnected #method:signalHandlerIsConnected# signalHandlerIsConnected , -- ** signalHandlerUnblock #method:signalHandlerUnblock# signalHandlerUnblock , -- ** signalHandlersBlockMatched #method:signalHandlersBlockMatched# signalHandlersBlockMatched , -- ** signalHandlersDestroy #method:signalHandlersDestroy# signalHandlersDestroy , -- ** signalHandlersDisconnectMatched #method:signalHandlersDisconnectMatched# signalHandlersDisconnectMatched , -- ** signalHandlersUnblockMatched #method:signalHandlersUnblockMatched# signalHandlersUnblockMatched , -- ** signalHasHandlerPending #method:signalHasHandlerPending# signalHasHandlerPending , -- ** signalListIds #method:signalListIds# signalListIds , -- ** signalLookup #method:signalLookup# signalLookup , -- ** signalName #method:signalName# signalName , -- ** signalOverrideClassClosure #method:signalOverrideClassClosure# signalOverrideClassClosure , -- ** signalParseName #method:signalParseName# signalParseName , -- ** signalQuery #method:signalQuery# signalQuery , -- ** signalRemoveEmissionHook #method:signalRemoveEmissionHook# signalRemoveEmissionHook , -- ** signalStopEmission #method:signalStopEmission# signalStopEmission , -- ** signalStopEmissionByName #method:signalStopEmissionByName# signalStopEmissionByName , -- ** signalTypeCclosureNew #method:signalTypeCclosureNew# signalTypeCclosureNew , -- ** sourceSetClosure #method:sourceSetClosure# sourceSetClosure , -- ** sourceSetDummyCallback #method:sourceSetDummyCallback# sourceSetDummyCallback , -- ** strdupValueContents #method:strdupValueContents# strdupValueContents , -- ** typeAddClassPrivate #method:typeAddClassPrivate# typeAddClassPrivate , -- ** typeAddInstancePrivate #method:typeAddInstancePrivate# typeAddInstancePrivate , -- ** typeAddInterfaceDynamic #method:typeAddInterfaceDynamic# typeAddInterfaceDynamic , -- ** typeAddInterfaceStatic #method:typeAddInterfaceStatic# typeAddInterfaceStatic , -- ** typeCheckClassIsA #method:typeCheckClassIsA# typeCheckClassIsA , -- ** typeCheckInstance #method:typeCheckInstance# typeCheckInstance , -- ** typeCheckInstanceIsA #method:typeCheckInstanceIsA# typeCheckInstanceIsA , -- ** typeCheckInstanceIsFundamentallyA #method:typeCheckInstanceIsFundamentallyA# typeCheckInstanceIsFundamentallyA , -- ** typeCheckIsValueType #method:typeCheckIsValueType# typeCheckIsValueType , -- ** typeCheckValue #method:typeCheckValue# typeCheckValue , -- ** typeCheckValueHolds #method:typeCheckValueHolds# typeCheckValueHolds , -- ** typeChildren #method:typeChildren# typeChildren , -- ** typeDefaultInterfacePeek #method:typeDefaultInterfacePeek# typeDefaultInterfacePeek , -- ** typeDefaultInterfaceRef #method:typeDefaultInterfaceRef# typeDefaultInterfaceRef , -- ** typeDefaultInterfaceUnref #method:typeDefaultInterfaceUnref# typeDefaultInterfaceUnref , -- ** typeDepth #method:typeDepth# typeDepth , -- ** typeEnsure #method:typeEnsure# typeEnsure , -- ** typeFreeInstance #method:typeFreeInstance# typeFreeInstance , -- ** typeFromName #method:typeFromName# typeFromName , -- ** typeFundamental #method:typeFundamental# typeFundamental , -- ** typeFundamentalNext #method:typeFundamentalNext# typeFundamentalNext , -- ** typeGetInstanceCount #method:typeGetInstanceCount# typeGetInstanceCount , -- ** typeGetPlugin #method:typeGetPlugin# typeGetPlugin , -- ** typeGetQdata #method:typeGetQdata# typeGetQdata , -- ** typeGetTypeRegistrationSerial #method:typeGetTypeRegistrationSerial# typeGetTypeRegistrationSerial , -- ** typeInit #method:typeInit# typeInit , -- ** typeInitWithDebugFlags #method:typeInitWithDebugFlags# typeInitWithDebugFlags , -- ** typeInterfaces #method:typeInterfaces# typeInterfaces , -- ** typeIsA #method:typeIsA# typeIsA , -- ** typeName #method:typeName# typeName , -- ** typeNameFromClass #method:typeNameFromClass# typeNameFromClass , -- ** typeNameFromInstance #method:typeNameFromInstance# typeNameFromInstance , -- ** typeNextBase #method:typeNextBase# typeNextBase , -- ** typeParent #method:typeParent# typeParent , -- ** typeQname #method:typeQname# typeQname , -- ** typeQuery #method:typeQuery# typeQuery , -- ** typeRegisterDynamic #method:typeRegisterDynamic# typeRegisterDynamic , -- ** typeRegisterFundamental #method:typeRegisterFundamental# typeRegisterFundamental , -- ** typeRegisterStatic #method:typeRegisterStatic# typeRegisterStatic , -- ** typeSetQdata #method:typeSetQdata# typeSetQdata , -- ** typeTestFlags #method:typeTestFlags# typeTestFlags , ) where import Data.GI.Base.ShortPrelude import qualified Data.GI.Base.ShortPrelude as SP import qualified Data.GI.Base.Overloading as O import qualified Prelude as P import qualified Data.GI.Base.Attributes as GI.Attributes import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr import qualified Data.GI.Base.GClosure as B.GClosure import qualified Data.GI.Base.GError as B.GError import qualified Data.GI.Base.GVariant as B.GVariant import qualified Data.GI.Base.GValue as B.GValue import qualified Data.GI.Base.GParamSpec as B.GParamSpec import qualified Data.GI.Base.CallStack as B.CallStack import qualified Data.GI.Base.Properties as B.Properties import qualified Data.GI.Base.Signals as B.Signals import qualified Data.Text as T import qualified Data.ByteString.Char8 as B import qualified Data.Map as Map import qualified Foreign.Ptr as FP import qualified GHC.OverloadedLabels as OL import qualified GI.GLib.Callbacks as GLib.Callbacks import qualified GI.GLib.Structs.Source as GLib.Source import qualified GI.GLib.Structs.VariantType as GLib.VariantType import qualified GI.GObject.Callbacks as GObject.Callbacks import {-# SOURCE #-} qualified GI.GObject.Flags as GObject.Flags import {-# SOURCE #-} qualified GI.GObject.Interfaces.TypePlugin as GObject.TypePlugin import {-# SOURCE #-} qualified GI.GObject.Objects.Object as GObject.Object import {-# SOURCE #-} qualified GI.GObject.Structs.EnumClass as GObject.EnumClass import {-# SOURCE #-} qualified GI.GObject.Structs.EnumValue as GObject.EnumValue import {-# SOURCE #-} qualified GI.GObject.Structs.FlagsClass as GObject.FlagsClass import {-# SOURCE #-} qualified GI.GObject.Structs.FlagsValue as GObject.FlagsValue import {-# SOURCE #-} qualified GI.GObject.Structs.InterfaceInfo as GObject.InterfaceInfo import {-# SOURCE #-} qualified GI.GObject.Structs.ParamSpecTypeInfo as GObject.ParamSpecTypeInfo import {-# SOURCE #-} qualified GI.GObject.Structs.SignalInvocationHint as GObject.SignalInvocationHint import {-# SOURCE #-} qualified GI.GObject.Structs.SignalQuery as GObject.SignalQuery import {-# SOURCE #-} qualified GI.GObject.Structs.TypeClass as GObject.TypeClass import {-# SOURCE #-} qualified GI.GObject.Structs.TypeFundamentalInfo as GObject.TypeFundamentalInfo import {-# SOURCE #-} qualified GI.GObject.Structs.TypeInfo as GObject.TypeInfo import {-# SOURCE #-} qualified GI.GObject.Structs.TypeInstance as GObject.TypeInstance import {-# SOURCE #-} qualified GI.GObject.Structs.TypeInterface as GObject.TypeInterface import {-# SOURCE #-} qualified GI.GObject.Structs.TypeQuery as GObject.TypeQuery -- function g_type_test_flags -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_test_flags" g_type_test_flags :: CGType -> -- type : TBasicType TGType Word32 -> -- flags : TBasicType TUInt IO CInt -- | /No description available in the introspection data./ typeTestFlags :: (B.CallStack.HasCallStack, MonadIO m) => GType -> Word32 -> m Bool typeTestFlags :: GType -> Word32 -> m Bool typeTestFlags type_ :: GType type_ flags :: Word32 flags = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CInt result <- CGType -> Word32 -> IO CInt g_type_test_flags CGType type_' Word32 flags let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_set_qdata -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "quark" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GQuark id to identify the data" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "the data" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_set_qdata" g_type_set_qdata :: CGType -> -- type : TBasicType TGType Word32 -> -- quark : TBasicType TUInt32 Ptr () -> -- data : TBasicType TPtr IO () -- | Attaches arbitrary data to a type. typeSetQdata :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: a t'GType' -> Word32 -- ^ /@quark@/: a @/GQuark/@ id to identify the data -> Ptr () -- ^ /@data@/: the data -> m () typeSetQdata :: GType -> Word32 -> Ptr () -> m () typeSetQdata type_ :: GType type_ quark :: Word32 quark data_ :: Ptr () data_ = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CGType -> Word32 -> Ptr () -> IO () g_type_set_qdata CGType type_' Word32 quark Ptr () data_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_register_static -- Args: [ Arg -- { argCName = "parent_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "type from which this type will be derived" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "type_name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "0-terminated string used as the name of the new type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "info" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInfo" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GTypeInfo structure for this type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "bitwise combination of #GTypeFlags values" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_register_static" g_type_register_static :: CGType -> -- parent_type : TBasicType TGType CString -> -- type_name : TBasicType TUTF8 Ptr GObject.TypeInfo.TypeInfo -> -- info : TInterface (Name {namespace = "GObject", name = "TypeInfo"}) CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "TypeFlags"}) IO CGType -- | Registers /@typeName@/ as the name of a new static type derived from -- /@parentType@/. The type system uses the information contained in the -- t'GI.GObject.Structs.TypeInfo.TypeInfo' structure pointed to by /@info@/ to manage the type and its -- instances (if not abstract). The value of /@flags@/ determines the nature -- (e.g. abstract or not) of the type. typeRegisterStatic :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@parentType@/: type from which this type will be derived -> T.Text -- ^ /@typeName@/: 0-terminated string used as the name of the new type -> GObject.TypeInfo.TypeInfo -- ^ /@info@/: t'GI.GObject.Structs.TypeInfo.TypeInfo' structure for this type -> [GObject.Flags.TypeFlags] -- ^ /@flags@/: bitwise combination of t'GI.GObject.Flags.TypeFlags' values -> m GType -- ^ __Returns:__ the new type identifier typeRegisterStatic :: GType -> Text -> TypeInfo -> [TypeFlags] -> m GType typeRegisterStatic parentType :: GType parentType typeName :: Text typeName info :: TypeInfo info flags :: [TypeFlags] flags = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do let parentType' :: CGType parentType' = GType -> CGType gtypeToCGType GType parentType CString typeName' <- Text -> IO CString textToCString Text typeName Ptr TypeInfo info' <- TypeInfo -> IO (Ptr TypeInfo) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInfo info let flags' :: CUInt flags' = [TypeFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [TypeFlags] flags CGType result <- CGType -> CString -> Ptr TypeInfo -> CUInt -> IO CGType g_type_register_static CGType parentType' CString typeName' Ptr TypeInfo info' CUInt flags' let result' :: GType result' = CGType -> GType GType CGType result TypeInfo -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInfo info CString -> IO () forall a. Ptr a -> IO () freeMem CString typeName' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_register_fundamental -- Args: [ Arg -- { argCName = "type_id" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a predefined type identifier" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "type_name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "0-terminated string used as the name of the new type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "info" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInfo" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GTypeInfo structure for this type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "finfo" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "TypeFundamentalInfo" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GTypeFundamentalInfo structure for this type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "bitwise combination of #GTypeFlags values" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_register_fundamental" g_type_register_fundamental :: CGType -> -- type_id : TBasicType TGType CString -> -- type_name : TBasicType TUTF8 Ptr GObject.TypeInfo.TypeInfo -> -- info : TInterface (Name {namespace = "GObject", name = "TypeInfo"}) Ptr GObject.TypeFundamentalInfo.TypeFundamentalInfo -> -- finfo : TInterface (Name {namespace = "GObject", name = "TypeFundamentalInfo"}) CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "TypeFlags"}) IO CGType -- | Registers /@typeId@/ as the predefined identifier and /@typeName@/ as the -- name of a fundamental type. If /@typeId@/ is already registered, or a -- type named /@typeName@/ is already registered, the behaviour is undefined. -- The type system uses the information contained in the t'GI.GObject.Structs.TypeInfo.TypeInfo' structure -- pointed to by /@info@/ and the t'GI.GObject.Structs.TypeFundamentalInfo.TypeFundamentalInfo' structure pointed to by -- /@finfo@/ to manage the type and its instances. The value of /@flags@/ determines -- additional characteristics of the fundamental type. typeRegisterFundamental :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@typeId@/: a predefined type identifier -> T.Text -- ^ /@typeName@/: 0-terminated string used as the name of the new type -> GObject.TypeInfo.TypeInfo -- ^ /@info@/: t'GI.GObject.Structs.TypeInfo.TypeInfo' structure for this type -> GObject.TypeFundamentalInfo.TypeFundamentalInfo -- ^ /@finfo@/: t'GI.GObject.Structs.TypeFundamentalInfo.TypeFundamentalInfo' structure for this type -> [GObject.Flags.TypeFlags] -- ^ /@flags@/: bitwise combination of t'GI.GObject.Flags.TypeFlags' values -> m GType -- ^ __Returns:__ the predefined type identifier typeRegisterFundamental :: GType -> Text -> TypeInfo -> TypeFundamentalInfo -> [TypeFlags] -> m GType typeRegisterFundamental typeId :: GType typeId typeName :: Text typeName info :: TypeInfo info finfo :: TypeFundamentalInfo finfo flags :: [TypeFlags] flags = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do let typeId' :: CGType typeId' = GType -> CGType gtypeToCGType GType typeId CString typeName' <- Text -> IO CString textToCString Text typeName Ptr TypeInfo info' <- TypeInfo -> IO (Ptr TypeInfo) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInfo info Ptr TypeFundamentalInfo finfo' <- TypeFundamentalInfo -> IO (Ptr TypeFundamentalInfo) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeFundamentalInfo finfo let flags' :: CUInt flags' = [TypeFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [TypeFlags] flags CGType result <- CGType -> CString -> Ptr TypeInfo -> Ptr TypeFundamentalInfo -> CUInt -> IO CGType g_type_register_fundamental CGType typeId' CString typeName' Ptr TypeInfo info' Ptr TypeFundamentalInfo finfo' CUInt flags' let result' :: GType result' = CGType -> GType GType CGType result TypeInfo -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInfo info TypeFundamentalInfo -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeFundamentalInfo finfo CString -> IO () forall a. Ptr a -> IO () freeMem CString typeName' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_register_dynamic -- Args: [ Arg -- { argCName = "parent_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "type from which this type will be derived" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "type_name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "0-terminated string used as the name of the new type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "plugin" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypePlugin" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "#GTypePlugin structure to retrieve the #GTypeInfo from" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "bitwise combination of #GTypeFlags values" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_register_dynamic" g_type_register_dynamic :: CGType -> -- parent_type : TBasicType TGType CString -> -- type_name : TBasicType TUTF8 Ptr GObject.TypePlugin.TypePlugin -> -- plugin : TInterface (Name {namespace = "GObject", name = "TypePlugin"}) CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "TypeFlags"}) IO CGType -- | Registers /@typeName@/ as the name of a new dynamic type derived from -- /@parentType@/. The type system uses the information contained in the -- t'GI.GObject.Interfaces.TypePlugin.TypePlugin' structure pointed to by /@plugin@/ to manage the type and its -- instances (if not abstract). The value of /@flags@/ determines the nature -- (e.g. abstract or not) of the type. typeRegisterDynamic :: (B.CallStack.HasCallStack, MonadIO m, GObject.TypePlugin.IsTypePlugin a) => GType -- ^ /@parentType@/: type from which this type will be derived -> T.Text -- ^ /@typeName@/: 0-terminated string used as the name of the new type -> a -- ^ /@plugin@/: t'GI.GObject.Interfaces.TypePlugin.TypePlugin' structure to retrieve the t'GI.GObject.Structs.TypeInfo.TypeInfo' from -> [GObject.Flags.TypeFlags] -- ^ /@flags@/: bitwise combination of t'GI.GObject.Flags.TypeFlags' values -> m GType -- ^ __Returns:__ the new type identifier or @/G_TYPE_INVALID/@ if registration failed typeRegisterDynamic :: GType -> Text -> a -> [TypeFlags] -> m GType typeRegisterDynamic parentType :: GType parentType typeName :: Text typeName plugin :: a plugin flags :: [TypeFlags] flags = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do let parentType' :: CGType parentType' = GType -> CGType gtypeToCGType GType parentType CString typeName' <- Text -> IO CString textToCString Text typeName Ptr TypePlugin plugin' <- a -> IO (Ptr TypePlugin) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a plugin let flags' :: CUInt flags' = [TypeFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [TypeFlags] flags CGType result <- CGType -> CString -> Ptr TypePlugin -> CUInt -> IO CGType g_type_register_dynamic CGType parentType' CString typeName' Ptr TypePlugin plugin' CUInt flags' let result' :: GType result' = CGType -> GType GType CGType result a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a plugin CString -> IO () forall a. Ptr a -> IO () freeMem CString typeName' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_query -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GType of a static, classed type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "query" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeQuery" } -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a user provided structure that is\n filled in with constant values upon success" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = True -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_query" g_type_query :: CGType -> -- type : TBasicType TGType Ptr GObject.TypeQuery.TypeQuery -> -- query : TInterface (Name {namespace = "GObject", name = "TypeQuery"}) IO () -- | Queries the type system for information about a specific type. -- This function will fill in a user-provided structure to hold -- type-specific information. If an invalid t'GType' is passed in, the -- /@type@/ member of the t'GI.GObject.Structs.TypeQuery.TypeQuery' is 0. All members filled into the -- t'GI.GObject.Structs.TypeQuery.TypeQuery' structure should be considered constant and have to be -- left untouched. typeQuery :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: t'GType' of a static, classed type -> m (GObject.TypeQuery.TypeQuery) typeQuery :: GType -> m TypeQuery typeQuery type_ :: GType type_ = IO TypeQuery -> m TypeQuery forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO TypeQuery -> m TypeQuery) -> IO TypeQuery -> m TypeQuery forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Ptr TypeQuery query <- Int -> IO (Ptr TypeQuery) forall a. Int -> IO (Ptr a) callocBytes 24 :: IO (Ptr GObject.TypeQuery.TypeQuery) CGType -> Ptr TypeQuery -> IO () g_type_query CGType type_' Ptr TypeQuery query TypeQuery query' <- ((ManagedPtr TypeQuery -> TypeQuery) -> Ptr TypeQuery -> IO TypeQuery forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a wrapPtr ManagedPtr TypeQuery -> TypeQuery GObject.TypeQuery.TypeQuery) Ptr TypeQuery query TypeQuery -> IO TypeQuery forall (m :: * -> *) a. Monad m => a -> m a return TypeQuery query' -- function g_type_qname -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "type to return quark of type name for" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUInt32) -- throws : False -- Skip return : False foreign import ccall "g_type_qname" g_type_qname :: CGType -> -- type : TBasicType TGType IO Word32 -- | Get the corresponding quark of the type IDs name. typeQname :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: type to return quark of type name for -> m Word32 -- ^ __Returns:__ the type names quark or 0 typeQname :: GType -> m Word32 typeQname type_ :: GType type_ = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Word32 result <- CGType -> IO Word32 g_type_qname CGType type_' Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_type_parent -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the derived type" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_parent" g_type_parent :: CGType -> -- type : TBasicType TGType IO CGType -- | Return the direct parent type of the passed in type. If the passed -- in type has no parent, i.e. is a fundamental type, 0 is returned. typeParent :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: the derived type -> m GType -- ^ __Returns:__ the parent type typeParent :: GType -> m GType typeParent type_ :: GType type_ = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CGType result <- CGType -> IO CGType g_type_parent CGType type_' let result' :: GType result' = CGType -> GType GType CGType result GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_next_base -- Args: [ Arg -- { argCName = "leaf_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "descendant of @root_type and the type to be returned" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "root_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "immediate parent of the returned type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_next_base" g_type_next_base :: CGType -> -- leaf_type : TBasicType TGType CGType -> -- root_type : TBasicType TGType IO CGType -- | Given a /@leafType@/ and a /@rootType@/ which is contained in its -- anchestry, return the type that /@rootType@/ is the immediate parent -- of. In other words, this function determines the type that is -- derived directly from /@rootType@/ which is also a base class of -- /@leafType@/. Given a root type and a leaf type, this function can -- be used to determine the types and order in which the leaf type is -- descended from the root type. typeNextBase :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@leafType@/: descendant of /@rootType@/ and the type to be returned -> GType -- ^ /@rootType@/: immediate parent of the returned type -> m GType -- ^ __Returns:__ immediate child of /@rootType@/ and anchestor of /@leafType@/ typeNextBase :: GType -> GType -> m GType typeNextBase leafType :: GType leafType rootType :: GType rootType = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do let leafType' :: CGType leafType' = GType -> CGType gtypeToCGType GType leafType let rootType' :: CGType rootType' = GType -> CGType gtypeToCGType GType rootType CGType result <- CGType -> CGType -> IO CGType g_type_next_base CGType leafType' CGType rootType' let result' :: GType result' = CGType -> GType GType CGType result GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_name_from_instance -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInstance" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_type_name_from_instance" g_type_name_from_instance :: Ptr GObject.TypeInstance.TypeInstance -> -- instance : TInterface (Name {namespace = "GObject", name = "TypeInstance"}) IO CString -- | /No description available in the introspection data./ typeNameFromInstance :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeInstance.TypeInstance -> m T.Text typeNameFromInstance :: TypeInstance -> m Text typeNameFromInstance instance_ :: TypeInstance instance_ = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do Ptr TypeInstance instance_' <- TypeInstance -> IO (Ptr TypeInstance) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInstance instance_ CString result <- Ptr TypeInstance -> IO CString g_type_name_from_instance Ptr TypeInstance instance_' Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeNameFromInstance" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result TypeInstance -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInstance instance_ Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_type_name_from_class -- Args: [ Arg -- { argCName = "g_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_type_name_from_class" g_type_name_from_class :: Ptr GObject.TypeClass.TypeClass -> -- g_class : TInterface (Name {namespace = "GObject", name = "TypeClass"}) IO CString -- | /No description available in the introspection data./ typeNameFromClass :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeClass.TypeClass -> m T.Text typeNameFromClass :: TypeClass -> m Text typeNameFromClass gClass :: TypeClass gClass = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do Ptr TypeClass gClass' <- TypeClass -> IO (Ptr TypeClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeClass gClass CString result <- Ptr TypeClass -> IO CString g_type_name_from_class Ptr TypeClass gClass' Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeNameFromClass" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result TypeClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeClass gClass Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_type_name -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "type to return name for" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_type_name" g_type_name :: CGType -> -- type : TBasicType TGType IO CString -- | Get the unique name that is assigned to a type ID. Note that this -- function (like all other GType API) cannot cope with invalid type -- IDs. @/G_TYPE_INVALID/@ may be passed to this function, as may be any -- other validly registered type ID, but randomized type IDs should -- not be passed in and will most likely lead to a crash. typeName :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: type to return name for -> m T.Text -- ^ __Returns:__ static type name or 'P.Nothing' typeName :: GType -> m Text typeName type_ :: GType type_ = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CString result <- CGType -> IO CString g_type_name CGType type_' Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeName" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_type_is_a -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "type to check anchestry for" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "is_a_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "possible anchestor of @type or interface that @type\n could conform to" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_is_a" g_type_is_a :: CGType -> -- type : TBasicType TGType CGType -> -- is_a_type : TBasicType TGType IO CInt -- | If /@isAType@/ is a derivable type, check whether /@type@/ is a -- descendant of /@isAType@/. If /@isAType@/ is an interface, check -- whether /@type@/ conforms to it. typeIsA :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: type to check anchestry for -> GType -- ^ /@isAType@/: possible anchestor of /@type@/ or interface that /@type@/ -- could conform to -> m Bool -- ^ __Returns:__ 'P.True' if /@type@/ is a /@isAType@/ typeIsA :: GType -> GType -> m Bool typeIsA type_ :: GType type_ isAType :: GType isAType = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ let isAType' :: CGType isAType' = GType -> CGType gtypeToCGType GType isAType CInt result <- CGType -> CGType -> IO CInt g_type_is_a CGType type_' CGType isAType' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_interfaces -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the type to list interface types for" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_interfaces" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "location to store the length of\n the returned array, or %NULL" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- ] -- Lengths: [ Arg -- { argCName = "n_interfaces" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "location to store the length of\n the returned array, or %NULL" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- ] -- returnType: Just (TCArray False (-1) 1 (TBasicType TGType)) -- throws : False -- Skip return : False foreign import ccall "g_type_interfaces" g_type_interfaces :: CGType -> -- type : TBasicType TGType Ptr Word32 -> -- n_interfaces : TBasicType TUInt IO (Ptr CGType) -- | Return a newly allocated and 0-terminated array of type IDs, listing -- the interface types that /@type@/ conforms to. typeInterfaces :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: the type to list interface types for -> m [GType] -- ^ __Returns:__ Newly allocated -- and 0-terminated array of interface types, free with 'GI.GLib.Functions.free' typeInterfaces :: GType -> m [GType] typeInterfaces type_ :: GType type_ = IO [GType] -> m [GType] forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO [GType] -> m [GType]) -> IO [GType] -> m [GType] forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Ptr Word32 nInterfaces <- IO (Ptr Word32) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr Word32) Ptr CGType result <- CGType -> Ptr Word32 -> IO (Ptr CGType) g_type_interfaces CGType type_' Ptr Word32 nInterfaces Word32 nInterfaces' <- Ptr Word32 -> IO Word32 forall a. Storable a => Ptr a -> IO a peek Ptr Word32 nInterfaces Text -> Ptr CGType -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeInterfaces" Ptr CGType result [GType] result' <- ((CGType -> GType) -> Word32 -> Ptr CGType -> IO [GType] forall a b c. (Integral a, Storable b) => (b -> c) -> a -> Ptr b -> IO [c] unpackMapStorableArrayWithLength CGType -> GType GType Word32 nInterfaces') Ptr CGType result Ptr CGType -> IO () forall a. Ptr a -> IO () freeMem Ptr CGType result Ptr Word32 -> IO () forall a. Ptr a -> IO () freeMem Ptr Word32 nInterfaces [GType] -> IO [GType] forall (m :: * -> *) a. Monad m => a -> m a return [GType] result' -- function g_type_init_with_debug_flags -- Args: [ Arg -- { argCName = "debug_flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeDebugFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "bitwise combination of #GTypeDebugFlags values for\n debugging purposes" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_init_with_debug_flags" g_type_init_with_debug_flags :: CUInt -> -- debug_flags : TInterface (Name {namespace = "GObject", name = "TypeDebugFlags"}) IO () {-# DEPRECATED typeInitWithDebugFlags ["(Since version 2.36)","the type system is now initialised automatically"] #-} -- | This function used to initialise the type system with debugging -- flags. Since GLib 2.36, the type system is initialised automatically -- and this function does nothing. -- -- If you need to enable debugging features, use the GOBJECT_DEBUG -- environment variable. typeInitWithDebugFlags :: (B.CallStack.HasCallStack, MonadIO m) => [GObject.Flags.TypeDebugFlags] -- ^ /@debugFlags@/: bitwise combination of t'GI.GObject.Flags.TypeDebugFlags' values for -- debugging purposes -> m () typeInitWithDebugFlags :: [TypeDebugFlags] -> m () typeInitWithDebugFlags debugFlags :: [TypeDebugFlags] debugFlags = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let debugFlags' :: CUInt debugFlags' = [TypeDebugFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [TypeDebugFlags] debugFlags CUInt -> IO () g_type_init_with_debug_flags CUInt debugFlags' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_init -- Args: [] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_init" g_type_init :: IO () {-# DEPRECATED typeInit ["(Since version 2.36)","the type system is now initialised automatically"] #-} -- | This function used to initialise the type system. Since GLib 2.36, -- the type system is initialised automatically and this function does -- nothing. typeInit :: (B.CallStack.HasCallStack, MonadIO m) => m () typeInit :: m () typeInit = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do IO () g_type_init () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_get_type_registration_serial -- Args: [] -- Lengths: [] -- returnType: Just (TBasicType TUInt) -- throws : False -- Skip return : False foreign import ccall "g_type_get_type_registration_serial" g_type_get_type_registration_serial :: IO Word32 -- | Returns an opaque serial number that represents the state of the set -- of registered types. Any time a type is registered this serial changes, -- which means you can cache information based on type lookups (such as -- 'GI.GObject.Functions.typeFromName') and know if the cache is still valid at a later -- time by comparing the current serial with the one at the type lookup. -- -- /Since: 2.36/ typeGetTypeRegistrationSerial :: (B.CallStack.HasCallStack, MonadIO m) => m Word32 -- ^ __Returns:__ An unsigned int, representing the state of type registrations typeGetTypeRegistrationSerial :: m Word32 typeGetTypeRegistrationSerial = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do Word32 result <- IO Word32 g_type_get_type_registration_serial Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_type_get_qdata -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "quark" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GQuark id to identify the data" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TPtr) -- throws : False -- Skip return : False foreign import ccall "g_type_get_qdata" g_type_get_qdata :: CGType -> -- type : TBasicType TGType Word32 -> -- quark : TBasicType TUInt32 IO (Ptr ()) -- | Obtains data which has previously been attached to /@type@/ -- with 'GI.GObject.Functions.typeSetQdata'. -- -- Note that this does not take subtyping into account; data -- attached to one type with 'GI.GObject.Functions.typeSetQdata' cannot -- be retrieved from a subtype using 'GI.GObject.Functions.typeGetQdata'. typeGetQdata :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: a t'GType' -> Word32 -- ^ /@quark@/: a @/GQuark/@ id to identify the data -> m (Ptr ()) -- ^ __Returns:__ the data, or 'P.Nothing' if no data was found typeGetQdata :: GType -> Word32 -> m (Ptr ()) typeGetQdata type_ :: GType type_ quark :: Word32 quark = 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 $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Ptr () result <- CGType -> Word32 -> IO (Ptr ()) g_type_get_qdata CGType type_' Word32 quark Ptr () -> IO (Ptr ()) forall (m :: * -> *) a. Monad m => a -> m a return Ptr () result -- function g_type_get_plugin -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GType to retrieve the plugin for" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "TypePlugin" }) -- throws : False -- Skip return : False foreign import ccall "g_type_get_plugin" g_type_get_plugin :: CGType -> -- type : TBasicType TGType IO (Ptr GObject.TypePlugin.TypePlugin) -- | Returns the t'GI.GObject.Interfaces.TypePlugin.TypePlugin' structure for /@type@/. typeGetPlugin :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: t'GType' to retrieve the plugin for -> m GObject.TypePlugin.TypePlugin -- ^ __Returns:__ the corresponding plugin -- if /@type@/ is a dynamic type, 'P.Nothing' otherwise typeGetPlugin :: GType -> m TypePlugin typeGetPlugin type_ :: GType type_ = IO TypePlugin -> m TypePlugin forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO TypePlugin -> m TypePlugin) -> IO TypePlugin -> m TypePlugin forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Ptr TypePlugin result <- CGType -> IO (Ptr TypePlugin) g_type_get_plugin CGType type_' Text -> Ptr TypePlugin -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeGetPlugin" Ptr TypePlugin result TypePlugin result' <- ((ManagedPtr TypePlugin -> TypePlugin) -> Ptr TypePlugin -> IO TypePlugin forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr TypePlugin -> TypePlugin GObject.TypePlugin.TypePlugin) Ptr TypePlugin result TypePlugin -> IO TypePlugin forall (m :: * -> *) a. Monad m => a -> m a return TypePlugin result' -- function g_type_get_instance_count -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TInt) -- throws : False -- Skip return : False foreign import ccall "g_type_get_instance_count" g_type_get_instance_count :: CGType -> -- type : TBasicType TGType IO Int32 -- | Returns the number of instances allocated of the particular type; -- this is only available if GLib is built with debugging support and -- the instance_count debug flag is set (by setting the GOBJECT_DEBUG -- variable to include instance-count). -- -- /Since: 2.44/ typeGetInstanceCount :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: a t'GType' -> m Int32 -- ^ __Returns:__ the number of instances allocated of the given type; -- if instance counts are not available, returns 0. typeGetInstanceCount :: GType -> m Int32 typeGetInstanceCount type_ :: GType type_ = IO Int32 -> m Int32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32 forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Int32 result <- CGType -> IO Int32 g_type_get_instance_count CGType type_' Int32 -> IO Int32 forall (m :: * -> *) a. Monad m => a -> m a return Int32 result -- function g_type_fundamental_next -- Args: [] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_fundamental_next" g_type_fundamental_next :: IO CGType -- | Returns the next free fundamental type id which can be used to -- register a new fundamental type with 'GI.GObject.Functions.typeRegisterFundamental'. -- The returned type ID represents the highest currently registered -- fundamental type identifier. typeFundamentalNext :: (B.CallStack.HasCallStack, MonadIO m) => m GType -- ^ __Returns:__ the next available fundamental type ID to be registered, -- or 0 if the type system ran out of fundamental type IDs typeFundamentalNext :: m GType typeFundamentalNext = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CGType result <- IO CGType g_type_fundamental_next let result' :: GType result' = CGType -> GType GType CGType result GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_fundamental -- Args: [ Arg -- { argCName = "type_id" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "valid type ID" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_fundamental" g_type_fundamental :: CGType -> -- type_id : TBasicType TGType IO CGType -- | Internal function, used to extract the fundamental type ID portion. -- Use @/G_TYPE_FUNDAMENTAL()/@ instead. typeFundamental :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@typeId@/: valid type ID -> m GType -- ^ __Returns:__ fundamental type ID typeFundamental :: GType -> m GType typeFundamental typeId :: GType typeId = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do let typeId' :: CGType typeId' = GType -> CGType gtypeToCGType GType typeId CGType result <- CGType -> IO CGType g_type_fundamental CGType typeId' let result' :: GType result' = CGType -> GType GType CGType result GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_from_name -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "type name to lookup" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_type_from_name" g_type_from_name :: CString -> -- name : TBasicType TUTF8 IO CGType -- | Lookup the type ID from a given type name, returning 0 if no type -- has been registered under this name (this is the preferred method -- to find out by name whether a specific type has been registered -- yet). typeFromName :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: type name to lookup -> m GType -- ^ __Returns:__ corresponding type ID or 0 typeFromName :: Text -> m GType typeFromName name :: Text name = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CGType result <- CString -> IO CGType g_type_from_name CString name' let result' :: GType result' = CGType -> GType GType CGType result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_type_free_instance -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInstance" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an instance of a type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_free_instance" g_type_free_instance :: Ptr GObject.TypeInstance.TypeInstance -> -- instance : TInterface (Name {namespace = "GObject", name = "TypeInstance"}) IO () -- | Frees an instance of a type, returning it to the instance pool for -- the type, if there is one. -- -- Like @/g_type_create_instance()/@, this function is reserved for -- implementors of fundamental types. typeFreeInstance :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeInstance.TypeInstance -- ^ /@instance@/: an instance of a type -> m () typeFreeInstance :: TypeInstance -> m () typeFreeInstance instance_ :: TypeInstance instance_ = 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 TypeInstance instance_' <- TypeInstance -> IO (Ptr TypeInstance) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInstance instance_ Ptr TypeInstance -> IO () g_type_free_instance Ptr TypeInstance instance_' TypeInstance -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInstance instance_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_ensure -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_ensure" g_type_ensure :: CGType -> -- type : TBasicType TGType IO () -- | Ensures that the indicated /@type@/ has been registered with the -- type system, and its @/_class_init()/@ method has been run. -- -- In theory, simply calling the type\'s @/_get_type()/@ method (or using -- the corresponding macro) is supposed take care of this. However, -- @/_get_type()/@ methods are often marked @/G_GNUC_CONST/@ for performance -- reasons, even though this is technically incorrect (since -- @/G_GNUC_CONST/@ requires that the function not have side effects, -- which @/_get_type()/@ methods do on the first call). As a result, if -- you write a bare call to a @/_get_type()/@ macro, it may get optimized -- out by the compiler. Using 'GI.GObject.Functions.typeEnsure' guarantees that the -- type\'s @/_get_type()/@ method is called. -- -- /Since: 2.34/ typeEnsure :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: a t'GType' -> m () typeEnsure :: GType -> m () typeEnsure type_ :: GType type_ = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CGType -> IO () g_type_ensure CGType type_' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_depth -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUInt) -- throws : False -- Skip return : False foreign import ccall "g_type_depth" g_type_depth :: CGType -> -- type : TBasicType TGType IO Word32 -- | Returns the length of the ancestry of the passed in type. This -- includes the type itself, so that e.g. a fundamental type has depth 1. typeDepth :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: a t'GType' -> m Word32 -- ^ __Returns:__ the depth of /@type@/ typeDepth :: GType -> m Word32 typeDepth type_ :: GType type_ = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Word32 result <- CGType -> IO Word32 g_type_depth CGType type_' Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_type_default_interface_unref -- Args: [ Arg -- { argCName = "g_iface" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInterface" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "the default vtable\n structure for a interface, as returned by g_type_default_interface_ref()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_default_interface_unref" g_type_default_interface_unref :: Ptr GObject.TypeInterface.TypeInterface -> -- g_iface : TInterface (Name {namespace = "GObject", name = "TypeInterface"}) IO () -- | Decrements the reference count for the type corresponding to the -- interface default vtable /@gIface@/. If the type is dynamic, then -- when no one is using the interface and all references have -- been released, the finalize function for the interface\'s default -- vtable (the /@classFinalize@/ member of t'GI.GObject.Structs.TypeInfo.TypeInfo') will be called. -- -- /Since: 2.4/ typeDefaultInterfaceUnref :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeInterface.TypeInterface -- ^ /@gIface@/: the default vtable -- structure for a interface, as returned by 'GI.GObject.Functions.typeDefaultInterfaceRef' -> m () typeDefaultInterfaceUnref :: TypeInterface -> m () typeDefaultInterfaceUnref gIface :: TypeInterface gIface = 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 TypeInterface gIface' <- TypeInterface -> IO (Ptr TypeInterface) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInterface gIface Ptr TypeInterface -> IO () g_type_default_interface_unref Ptr TypeInterface gIface' TypeInterface -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInterface gIface () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_default_interface_ref -- Args: [ Arg -- { argCName = "g_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an interface type" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface -- Name { namespace = "GObject" , name = "TypeInterface" }) -- throws : False -- Skip return : False foreign import ccall "g_type_default_interface_ref" g_type_default_interface_ref :: CGType -> -- g_type : TBasicType TGType IO (Ptr GObject.TypeInterface.TypeInterface) -- | Increments the reference count for the interface type /@gType@/, -- and returns the default interface vtable for the type. -- -- If the type is not currently in use, then the default vtable -- for the type will be created and initalized by calling -- the base interface init and default vtable init functions for -- the type (the /@baseInit@/ and /@classInit@/ members of t'GI.GObject.Structs.TypeInfo.TypeInfo'). -- Calling 'GI.GObject.Functions.typeDefaultInterfaceRef' is useful when you -- want to make sure that signals and properties for an interface -- have been installed. -- -- /Since: 2.4/ typeDefaultInterfaceRef :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@gType@/: an interface type -> m GObject.TypeInterface.TypeInterface -- ^ __Returns:__ the default -- vtable for the interface; call 'GI.GObject.Functions.typeDefaultInterfaceUnref' -- when you are done using the interface. typeDefaultInterfaceRef :: GType -> m TypeInterface typeDefaultInterfaceRef gType :: GType gType = IO TypeInterface -> m TypeInterface forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO TypeInterface -> m TypeInterface) -> IO TypeInterface -> m TypeInterface forall a b. (a -> b) -> a -> b $ do let gType' :: CGType gType' = GType -> CGType gtypeToCGType GType gType Ptr TypeInterface result <- CGType -> IO (Ptr TypeInterface) g_type_default_interface_ref CGType gType' Text -> Ptr TypeInterface -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeDefaultInterfaceRef" Ptr TypeInterface result TypeInterface result' <- ((ManagedPtr TypeInterface -> TypeInterface) -> Ptr TypeInterface -> IO TypeInterface forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr TypeInterface -> TypeInterface GObject.TypeInterface.TypeInterface) Ptr TypeInterface result TypeInterface -> IO TypeInterface forall (m :: * -> *) a. Monad m => a -> m a return TypeInterface result' -- function g_type_default_interface_peek -- Args: [ Arg -- { argCName = "g_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an interface type" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface -- Name { namespace = "GObject" , name = "TypeInterface" }) -- throws : False -- Skip return : False foreign import ccall "g_type_default_interface_peek" g_type_default_interface_peek :: CGType -> -- g_type : TBasicType TGType IO (Ptr GObject.TypeInterface.TypeInterface) -- | If the interface type /@gType@/ is currently in use, returns its -- default interface vtable. -- -- /Since: 2.4/ typeDefaultInterfacePeek :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@gType@/: an interface type -> m GObject.TypeInterface.TypeInterface -- ^ __Returns:__ the default -- vtable for the interface, or 'P.Nothing' if the type is not currently -- in use typeDefaultInterfacePeek :: GType -> m TypeInterface typeDefaultInterfacePeek gType :: GType gType = IO TypeInterface -> m TypeInterface forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO TypeInterface -> m TypeInterface) -> IO TypeInterface -> m TypeInterface forall a b. (a -> b) -> a -> b $ do let gType' :: CGType gType' = GType -> CGType gtypeToCGType GType gType Ptr TypeInterface result <- CGType -> IO (Ptr TypeInterface) g_type_default_interface_peek CGType gType' Text -> Ptr TypeInterface -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeDefaultInterfacePeek" Ptr TypeInterface result TypeInterface result' <- ((ManagedPtr TypeInterface -> TypeInterface) -> Ptr TypeInterface -> IO TypeInterface forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr TypeInterface -> TypeInterface GObject.TypeInterface.TypeInterface) Ptr TypeInterface result TypeInterface -> IO TypeInterface forall (m :: * -> *) a. Monad m => a -> m a return TypeInterface result' -- function g_type_children -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the parent type" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_children" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "location to store the length of\n the returned array, or %NULL" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- ] -- Lengths: [ Arg -- { argCName = "n_children" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "location to store the length of\n the returned array, or %NULL" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- ] -- returnType: Just (TCArray False (-1) 1 (TBasicType TGType)) -- throws : False -- Skip return : False foreign import ccall "g_type_children" g_type_children :: CGType -> -- type : TBasicType TGType Ptr Word32 -> -- n_children : TBasicType TUInt IO (Ptr CGType) -- | Return a newly allocated and 0-terminated array of type IDs, listing -- the child types of /@type@/. typeChildren :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@type@/: the parent type -> m [GType] -- ^ __Returns:__ Newly allocated -- and 0-terminated array of child types, free with 'GI.GLib.Functions.free' typeChildren :: GType -> m [GType] typeChildren type_ :: GType type_ = IO [GType] -> m [GType] forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO [GType] -> m [GType]) -> IO [GType] -> m [GType] forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ Ptr Word32 nChildren <- IO (Ptr Word32) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr Word32) Ptr CGType result <- CGType -> Ptr Word32 -> IO (Ptr CGType) g_type_children CGType type_' Ptr Word32 nChildren Word32 nChildren' <- Ptr Word32 -> IO Word32 forall a. Storable a => Ptr a -> IO a peek Ptr Word32 nChildren Text -> Ptr CGType -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "typeChildren" Ptr CGType result [GType] result' <- ((CGType -> GType) -> Word32 -> Ptr CGType -> IO [GType] forall a b c. (Integral a, Storable b) => (b -> c) -> a -> Ptr b -> IO [c] unpackMapStorableArrayWithLength CGType -> GType GType Word32 nChildren') Ptr CGType result Ptr CGType -> IO () forall a. Ptr a -> IO () freeMem Ptr CGType result Ptr Word32 -> IO () forall a. Ptr a -> IO () freeMem Ptr Word32 nChildren [GType] -> IO [GType] forall (m :: * -> *) a. Monad m => a -> m a return [GType] result' -- function g_type_check_value_holds -- Args: [ Arg -- { argCName = "value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_value_holds" g_type_check_value_holds :: Ptr GValue -> -- value : TInterface (Name {namespace = "GObject", name = "Value"}) CGType -> -- type : TBasicType TGType IO CInt -- | /No description available in the introspection data./ typeCheckValueHolds :: (B.CallStack.HasCallStack, MonadIO m) => GValue -> GType -> m Bool typeCheckValueHolds :: GValue -> GType -> m Bool typeCheckValueHolds value :: GValue value type_ :: GType type_ = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr GValue value' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CInt result <- Ptr GValue -> CGType -> IO CInt g_type_check_value_holds Ptr GValue value' CGType type_' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_check_value -- Args: [ Arg -- { argCName = "value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_value" g_type_check_value :: Ptr GValue -> -- value : TInterface (Name {namespace = "GObject", name = "Value"}) IO CInt -- | /No description available in the introspection data./ typeCheckValue :: (B.CallStack.HasCallStack, MonadIO m) => GValue -> m Bool typeCheckValue :: GValue -> m Bool typeCheckValue value :: GValue value = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr GValue value' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value CInt result <- Ptr GValue -> IO CInt g_type_check_value Ptr GValue value' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_check_is_value_type -- Args: [ Arg -- { argCName = "type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_is_value_type" g_type_check_is_value_type :: CGType -> -- type : TBasicType TGType IO CInt -- | /No description available in the introspection data./ typeCheckIsValueType :: (B.CallStack.HasCallStack, MonadIO m) => GType -> m Bool typeCheckIsValueType :: GType -> m Bool typeCheckIsValueType type_ :: GType type_ = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do let type_' :: CGType type_' = GType -> CGType gtypeToCGType GType type_ CInt result <- CGType -> IO CInt g_type_check_is_value_type CGType type_' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_check_instance_is_fundamentally_a -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInstance" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "fundamental_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_instance_is_fundamentally_a" g_type_check_instance_is_fundamentally_a :: Ptr GObject.TypeInstance.TypeInstance -> -- instance : TInterface (Name {namespace = "GObject", name = "TypeInstance"}) CGType -> -- fundamental_type : TBasicType TGType IO CInt -- | /No description available in the introspection data./ typeCheckInstanceIsFundamentallyA :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeInstance.TypeInstance -> GType -> m Bool typeCheckInstanceIsFundamentallyA :: TypeInstance -> GType -> m Bool typeCheckInstanceIsFundamentallyA instance_ :: TypeInstance instance_ fundamentalType :: GType fundamentalType = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr TypeInstance instance_' <- TypeInstance -> IO (Ptr TypeInstance) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInstance instance_ let fundamentalType' :: CGType fundamentalType' = GType -> CGType gtypeToCGType GType fundamentalType CInt result <- Ptr TypeInstance -> CGType -> IO CInt g_type_check_instance_is_fundamentally_a Ptr TypeInstance instance_' CGType fundamentalType' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result TypeInstance -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInstance instance_ Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_check_instance_is_a -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInstance" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "iface_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_instance_is_a" g_type_check_instance_is_a :: Ptr GObject.TypeInstance.TypeInstance -> -- instance : TInterface (Name {namespace = "GObject", name = "TypeInstance"}) CGType -> -- iface_type : TBasicType TGType IO CInt -- | /No description available in the introspection data./ typeCheckInstanceIsA :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeInstance.TypeInstance -> GType -> m Bool typeCheckInstanceIsA :: TypeInstance -> GType -> m Bool typeCheckInstanceIsA instance_ :: TypeInstance instance_ ifaceType :: GType ifaceType = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr TypeInstance instance_' <- TypeInstance -> IO (Ptr TypeInstance) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInstance instance_ let ifaceType' :: CGType ifaceType' = GType -> CGType gtypeToCGType GType ifaceType CInt result <- Ptr TypeInstance -> CGType -> IO CInt g_type_check_instance_is_a Ptr TypeInstance instance_' CGType ifaceType' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result TypeInstance -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInstance instance_ Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_check_instance -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInstance" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a valid #GTypeInstance structure" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_instance" g_type_check_instance :: Ptr GObject.TypeInstance.TypeInstance -> -- instance : TInterface (Name {namespace = "GObject", name = "TypeInstance"}) IO CInt -- | Private helper function to aid implementation of the -- @/G_TYPE_CHECK_INSTANCE()/@ macro. typeCheckInstance :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeInstance.TypeInstance -- ^ /@instance@/: a valid t'GI.GObject.Structs.TypeInstance.TypeInstance' structure -> m Bool -- ^ __Returns:__ 'P.True' if /@instance@/ is valid, 'P.False' otherwise typeCheckInstance :: TypeInstance -> m Bool typeCheckInstance instance_ :: TypeInstance instance_ = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr TypeInstance instance_' <- TypeInstance -> IO (Ptr TypeInstance) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeInstance instance_ CInt result <- Ptr TypeInstance -> IO CInt g_type_check_instance Ptr TypeInstance instance_' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result TypeInstance -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeInstance instance_ Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_check_class_is_a -- Args: [ Arg -- { argCName = "g_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "is_a_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_type_check_class_is_a" g_type_check_class_is_a :: Ptr GObject.TypeClass.TypeClass -> -- g_class : TInterface (Name {namespace = "GObject", name = "TypeClass"}) CGType -> -- is_a_type : TBasicType TGType IO CInt -- | /No description available in the introspection data./ typeCheckClassIsA :: (B.CallStack.HasCallStack, MonadIO m) => GObject.TypeClass.TypeClass -> GType -> m Bool typeCheckClassIsA :: TypeClass -> GType -> m Bool typeCheckClassIsA gClass :: TypeClass gClass isAType :: GType isAType = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr TypeClass gClass' <- TypeClass -> IO (Ptr TypeClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr TypeClass gClass let isAType' :: CGType isAType' = GType -> CGType gtypeToCGType GType isAType CInt result <- Ptr TypeClass -> CGType -> IO CInt g_type_check_class_is_a Ptr TypeClass gClass' CGType isAType' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result TypeClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr TypeClass gClass Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_type_add_interface_static -- Args: [ Arg -- { argCName = "instance_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GType value of an instantiable type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "interface_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GType value of an interface type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "info" -- , argType = -- TInterface Name { namespace = "GObject" , name = "InterfaceInfo" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "#GInterfaceInfo structure for this\n (@instance_type, @interface_type) combination" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_add_interface_static" g_type_add_interface_static :: CGType -> -- instance_type : TBasicType TGType CGType -> -- interface_type : TBasicType TGType Ptr GObject.InterfaceInfo.InterfaceInfo -> -- info : TInterface (Name {namespace = "GObject", name = "InterfaceInfo"}) IO () -- | Adds the static /@interfaceType@/ to /@instantiableType@/. -- The information contained in the t'GI.GObject.Structs.InterfaceInfo.InterfaceInfo' structure -- pointed to by /@info@/ is used to manage the relationship. typeAddInterfaceStatic :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@instanceType@/: t'GType' value of an instantiable type -> GType -- ^ /@interfaceType@/: t'GType' value of an interface type -> GObject.InterfaceInfo.InterfaceInfo -- ^ /@info@/: t'GI.GObject.Structs.InterfaceInfo.InterfaceInfo' structure for this -- (/@instanceType@/, /@interfaceType@/) combination -> m () typeAddInterfaceStatic :: GType -> GType -> InterfaceInfo -> m () typeAddInterfaceStatic instanceType :: GType instanceType interfaceType :: GType interfaceType info :: InterfaceInfo info = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let instanceType' :: CGType instanceType' = GType -> CGType gtypeToCGType GType instanceType let interfaceType' :: CGType interfaceType' = GType -> CGType gtypeToCGType GType interfaceType Ptr InterfaceInfo info' <- InterfaceInfo -> IO (Ptr InterfaceInfo) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr InterfaceInfo info CGType -> CGType -> Ptr InterfaceInfo -> IO () g_type_add_interface_static CGType instanceType' CGType interfaceType' Ptr InterfaceInfo info' InterfaceInfo -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr InterfaceInfo info () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_add_interface_dynamic -- Args: [ Arg -- { argCName = "instance_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GType value of an instantiable type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "interface_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GType value of an interface type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "plugin" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypePlugin" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "#GTypePlugin structure to retrieve the #GInterfaceInfo from" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_add_interface_dynamic" g_type_add_interface_dynamic :: CGType -> -- instance_type : TBasicType TGType CGType -> -- interface_type : TBasicType TGType Ptr GObject.TypePlugin.TypePlugin -> -- plugin : TInterface (Name {namespace = "GObject", name = "TypePlugin"}) IO () -- | Adds the dynamic /@interfaceType@/ to /@instantiableType@/. The information -- contained in the t'GI.GObject.Interfaces.TypePlugin.TypePlugin' structure pointed to by /@plugin@/ -- is used to manage the relationship. typeAddInterfaceDynamic :: (B.CallStack.HasCallStack, MonadIO m, GObject.TypePlugin.IsTypePlugin a) => GType -- ^ /@instanceType@/: t'GType' value of an instantiable type -> GType -- ^ /@interfaceType@/: t'GType' value of an interface type -> a -- ^ /@plugin@/: t'GI.GObject.Interfaces.TypePlugin.TypePlugin' structure to retrieve the t'GI.GObject.Structs.InterfaceInfo.InterfaceInfo' from -> m () typeAddInterfaceDynamic :: GType -> GType -> a -> m () typeAddInterfaceDynamic instanceType :: GType instanceType interfaceType :: GType interfaceType plugin :: a plugin = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let instanceType' :: CGType instanceType' = GType -> CGType gtypeToCGType GType instanceType let interfaceType' :: CGType interfaceType' = GType -> CGType gtypeToCGType GType interfaceType Ptr TypePlugin plugin' <- a -> IO (Ptr TypePlugin) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a plugin CGType -> CGType -> Ptr TypePlugin -> IO () g_type_add_interface_dynamic CGType instanceType' CGType interfaceType' Ptr TypePlugin plugin' a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a plugin () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_type_add_instance_private -- Args: [ Arg -- { argCName = "class_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "private_size" -- , argType = TBasicType TUInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation { rawDocText = Nothing , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TInt) -- throws : False -- Skip return : False foreign import ccall "g_type_add_instance_private" g_type_add_instance_private :: CGType -> -- class_type : TBasicType TGType Word64 -> -- private_size : TBasicType TUInt64 IO Int32 -- | /No description available in the introspection data./ typeAddInstancePrivate :: (B.CallStack.HasCallStack, MonadIO m) => GType -> Word64 -> m Int32 typeAddInstancePrivate :: GType -> CGType -> m Int32 typeAddInstancePrivate classType :: GType classType privateSize :: CGType privateSize = IO Int32 -> m Int32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32 forall a b. (a -> b) -> a -> b $ do let classType' :: CGType classType' = GType -> CGType gtypeToCGType GType classType Int32 result <- CGType -> CGType -> IO Int32 g_type_add_instance_private CGType classType' CGType privateSize Int32 -> IO Int32 forall (m :: * -> *) a. Monad m => a -> m a return Int32 result -- function g_type_add_class_private -- Args: [ Arg -- { argCName = "class_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "GType of an classed type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "private_size" -- , argType = TBasicType TUInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "size of private structure" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_type_add_class_private" g_type_add_class_private :: CGType -> -- class_type : TBasicType TGType Word64 -> -- private_size : TBasicType TUInt64 IO () -- | Registers a private class structure for a classed type; -- when the class is allocated, the private structures for -- the class and all of its parent types are allocated -- sequentially in the same memory block as the public -- structures, and are zero-filled. -- -- This function should be called in the -- type\'s @/get_type()/@ function after the type is registered. -- The private structure can be retrieved using the -- @/G_TYPE_CLASS_GET_PRIVATE()/@ macro. -- -- /Since: 2.24/ typeAddClassPrivate :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@classType@/: GType of an classed type -> Word64 -- ^ /@privateSize@/: size of private structure -> m () typeAddClassPrivate :: GType -> CGType -> m () typeAddClassPrivate classType :: GType classType privateSize :: CGType privateSize = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let classType' :: CGType classType' = GType -> CGType gtypeToCGType GType classType CGType -> CGType -> IO () g_type_add_class_private CGType classType' CGType privateSize () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_strdup_value_contents -- Args: [ Arg -- { argCName = "value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "#GValue which contents are to be described." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_strdup_value_contents" g_strdup_value_contents :: Ptr GValue -> -- value : TInterface (Name {namespace = "GObject", name = "Value"}) IO CString -- | Return a newly allocated string, which describes the contents of a -- t'GI.GObject.Structs.Value.Value'. The main purpose of this function is to describe t'GI.GObject.Structs.Value.Value' -- contents for debugging output, the way in which the contents are -- described may change between different GLib versions. strdupValueContents :: (B.CallStack.HasCallStack, MonadIO m) => GValue -- ^ /@value@/: t'GI.GObject.Structs.Value.Value' which contents are to be described. -> m T.Text -- ^ __Returns:__ Newly allocated string. strdupValueContents :: GValue -> m Text strdupValueContents value :: GValue value = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do Ptr GValue value' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value CString result <- Ptr GValue -> IO CString g_strdup_value_contents Ptr GValue value' Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "strdupValueContents" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result CString -> IO () forall a. Ptr a -> IO () freeMem CString result GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_source_set_dummy_callback -- Args: [ Arg -- { argCName = "source" -- , argType = -- TInterface Name { namespace = "GLib" , name = "Source" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the source" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_source_set_dummy_callback" g_source_set_dummy_callback :: Ptr GLib.Source.Source -> -- source : TInterface (Name {namespace = "GLib", name = "Source"}) IO () -- | Sets a dummy callback for /@source@/. The callback will do nothing, and -- if the source expects a t'P.Bool' return value, it will return 'P.True'. -- (If the source expects any other type of return value, it will return -- a 0\/'P.Nothing' value; whatever 'GI.GObject.Structs.Value.valueInit' initializes a t'GI.GObject.Structs.Value.Value' to for -- that type.) -- -- If the source is not one of the standard GLib types, the -- /@closureCallback@/ and /@closureMarshal@/ fields of the t'GI.GLib.Structs.SourceFuncs.SourceFuncs' -- structure must have been filled in with pointers to appropriate -- functions. sourceSetDummyCallback :: (B.CallStack.HasCallStack, MonadIO m) => GLib.Source.Source -- ^ /@source@/: the source -> m () sourceSetDummyCallback :: Source -> m () sourceSetDummyCallback source :: Source source = 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 Source source' <- Source -> IO (Ptr Source) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr Source source Ptr Source -> IO () g_source_set_dummy_callback Ptr Source source' Source -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr Source source () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_source_set_closure -- Args: [ Arg -- { argCName = "source" -- , argType = -- TInterface Name { namespace = "GLib" , name = "Source" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the source" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , 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 -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_source_set_closure" g_source_set_closure :: Ptr GLib.Source.Source -> -- source : TInterface (Name {namespace = "GLib", name = "Source"}) Ptr (GClosure ()) -> -- closure : TGClosure Nothing IO () -- | Set the callback for a source as a t'GI.GObject.Structs.Closure.Closure'. -- -- If the source is not one of the standard GLib types, the /@closureCallback@/ -- and /@closureMarshal@/ fields of the t'GI.GLib.Structs.SourceFuncs.SourceFuncs' structure must have been -- filled in with pointers to appropriate functions. sourceSetClosure :: (B.CallStack.HasCallStack, MonadIO m) => GLib.Source.Source -- ^ /@source@/: the source -> GClosure a -- ^ /@closure@/: a t'GI.GObject.Structs.Closure.Closure' -> m () sourceSetClosure :: Source -> GClosure a -> m () sourceSetClosure source :: Source source closure :: GClosure a closure = 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 Source source' <- Source -> IO (Ptr Source) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr Source source Ptr (GClosure ()) closure' <- GClosure a -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure a closure Ptr Source -> Ptr (GClosure ()) -> IO () g_source_set_closure Ptr Source source' Ptr (GClosure ()) closure' Source -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr Source source GClosure a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GClosure a closure () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_type_cclosure_new -- Args: [ Arg -- { argCName = "itype" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the #GType identifier of an interface or classed type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "struct_offset" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "the offset of the member function of @itype's class\n structure which is to be invoked by the new closure" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TGClosure Nothing) -- throws : False -- Skip return : False foreign import ccall "g_signal_type_cclosure_new" g_signal_type_cclosure_new :: CGType -> -- itype : TBasicType TGType Word32 -> -- struct_offset : TBasicType TUInt IO (Ptr (GClosure ())) -- | Creates a new closure which invokes the function found at the offset -- /@structOffset@/ in the class structure of the interface or classed type -- identified by /@itype@/. signalTypeCclosureNew :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@itype@/: the t'GType' identifier of an interface or classed type -> Word32 -- ^ /@structOffset@/: the offset of the member function of /@itype@/\'s class -- structure which is to be invoked by the new closure -> m (GClosure a) -- ^ __Returns:__ a floating reference to a new t'GI.GObject.Structs.CClosure.CClosure' signalTypeCclosureNew :: GType -> Word32 -> m (GClosure a) signalTypeCclosureNew itype :: GType itype structOffset :: Word32 structOffset = IO (GClosure a) -> m (GClosure a) forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO (GClosure a) -> m (GClosure a)) -> IO (GClosure a) -> m (GClosure a) forall a b. (a -> b) -> a -> b $ do let itype' :: CGType itype' = GType -> CGType gtypeToCGType GType itype Ptr (GClosure ()) result <- CGType -> Word32 -> IO (Ptr (GClosure ())) g_signal_type_cclosure_new CGType itype' Word32 structOffset Text -> Ptr (GClosure ()) -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "signalTypeCclosureNew" Ptr (GClosure ()) result GClosure a result' <- (Ptr (GClosure a) -> IO (GClosure a) forall a. Ptr (GClosure a) -> IO (GClosure a) B.GClosure.newGClosureFromPtr (Ptr (GClosure a) -> IO (GClosure a)) -> (Ptr (GClosure ()) -> Ptr (GClosure a)) -> Ptr (GClosure ()) -> IO (GClosure a) forall b c a. (b -> c) -> (a -> b) -> a -> c . Ptr (GClosure ()) -> Ptr (GClosure a) forall a b. Ptr a -> Ptr b FP.castPtr) Ptr (GClosure ()) result GClosure a -> IO (GClosure a) forall (m :: * -> *) a. Monad m => a -> m a return GClosure a result' -- function g_signal_stop_emission_by_name -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the object whose signal handlers you wish to stop." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detailed_signal" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a string of the form \"signal-name::detail\"." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_stop_emission_by_name" g_signal_stop_emission_by_name :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CString -> -- detailed_signal : TBasicType TUTF8 IO () -- | Stops a signal\'s current emission. -- -- This is just like 'GI.GObject.Functions.signalStopEmission' except it will look up the -- signal id for you. signalStopEmissionByName :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: the object whose signal handlers you wish to stop. -> T.Text -- ^ /@detailedSignal@/: a string of the form \"signal-name[detail](#signal:detail)\". -> m () signalStopEmissionByName :: a -> Text -> m () signalStopEmissionByName instance_ :: a instance_ detailedSignal :: Text detailedSignal = 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 Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ CString detailedSignal' <- Text -> IO CString textToCString Text detailedSignal Ptr Object -> CString -> IO () g_signal_stop_emission_by_name Ptr Object instance_' CString detailedSignal' a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ CString -> IO () forall a. Ptr a -> IO () freeMem CString detailedSignal' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_stop_emission -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the object whose signal handlers you wish to stop." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the signal identifier, as returned by g_signal_lookup()." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the detail which the signal was emitted with." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_stop_emission" g_signal_stop_emission :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 IO () -- | Stops a signal\'s current emission. -- -- This will prevent the default method from running, if the signal was -- 'GI.GObject.Flags.SignalFlagsRunLast' and you connected normally (i.e. without the \"after\" -- flag). -- -- Prints a warning if used on a signal which isn\'t being emitted. signalStopEmission :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: the object whose signal handlers you wish to stop. -> Word32 -- ^ /@signalId@/: the signal identifier, as returned by 'GI.GObject.Functions.signalLookup'. -> Word32 -- ^ /@detail@/: the detail which the signal was emitted with. -> m () signalStopEmission :: a -> Word32 -> Word32 -> m () signalStopEmission instance_ :: a instance_ signalId :: Word32 signalId detail :: Word32 detail = 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 Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr Object -> Word32 -> Word32 -> IO () g_signal_stop_emission Ptr Object instance_' Word32 signalId Word32 detail a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_remove_emission_hook -- Args: [ Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the id of the signal" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "hook_id" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "the id of the emission hook, as returned by\n g_signal_add_emission_hook()" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_remove_emission_hook" g_signal_remove_emission_hook :: Word32 -> -- signal_id : TBasicType TUInt CULong -> -- hook_id : TBasicType TULong IO () -- | Deletes an emission hook. signalRemoveEmissionHook :: (B.CallStack.HasCallStack, MonadIO m) => Word32 -- ^ /@signalId@/: the id of the signal -> CULong -- ^ /@hookId@/: the id of the emission hook, as returned by -- 'GI.GObject.Functions.signalAddEmissionHook' -> m () signalRemoveEmissionHook :: Word32 -> CULong -> m () signalRemoveEmissionHook signalId :: Word32 signalId hookId :: CULong hookId = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Word32 -> CULong -> IO () g_signal_remove_emission_hook Word32 signalId CULong hookId () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_query -- Args: [ Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The signal id of the signal to query information for." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "query" -- , argType = -- TInterface Name { namespace = "GObject" , name = "SignalQuery" } -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "A user provided structure that is\n filled in with constant values upon success." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = True -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_query" g_signal_query :: Word32 -> -- signal_id : TBasicType TUInt Ptr GObject.SignalQuery.SignalQuery -> -- query : TInterface (Name {namespace = "GObject", name = "SignalQuery"}) IO () -- | Queries the signal system for in-depth information about a -- specific signal. This function will fill in a user-provided -- structure to hold signal-specific information. If an invalid -- signal id is passed in, the /@signalId@/ member of the t'GI.GObject.Structs.SignalQuery.SignalQuery' -- is 0. All members filled into the t'GI.GObject.Structs.SignalQuery.SignalQuery' structure should -- be considered constant and have to be left untouched. signalQuery :: (B.CallStack.HasCallStack, MonadIO m) => Word32 -- ^ /@signalId@/: The signal id of the signal to query information for. -> m (GObject.SignalQuery.SignalQuery) signalQuery :: Word32 -> m SignalQuery signalQuery signalId :: Word32 signalId = IO SignalQuery -> m SignalQuery forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO SignalQuery -> m SignalQuery) -> IO SignalQuery -> m SignalQuery forall a b. (a -> b) -> a -> b $ do Ptr SignalQuery query <- Int -> IO (Ptr SignalQuery) forall a. Int -> IO (Ptr a) callocBytes 56 :: IO (Ptr GObject.SignalQuery.SignalQuery) Word32 -> Ptr SignalQuery -> IO () g_signal_query Word32 signalId Ptr SignalQuery query SignalQuery query' <- ((ManagedPtr SignalQuery -> SignalQuery) -> Ptr SignalQuery -> IO SignalQuery forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a wrapPtr ManagedPtr SignalQuery -> SignalQuery GObject.SignalQuery.SignalQuery) Ptr SignalQuery query SignalQuery -> IO SignalQuery forall (m :: * -> *) a. Monad m => a -> m a return SignalQuery query' -- function g_signal_parse_name -- Args: [ Arg -- { argCName = "detailed_signal" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a string of the form \"signal-name::detail\"." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "itype" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The interface/instance type that introduced \"signal-name\"." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id_p" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Location to store the signal id." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- , Arg -- { argCName = "detail_p" -- , argType = TBasicType TUInt32 -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Location to store the detail quark." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- , Arg -- { argCName = "force_detail_quark" -- , argType = TBasicType TBoolean -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "%TRUE forces creation of a #GQuark for the detail." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_signal_parse_name" g_signal_parse_name :: CString -> -- detailed_signal : TBasicType TUTF8 CGType -> -- itype : TBasicType TGType Ptr Word32 -> -- signal_id_p : TBasicType TUInt Ptr Word32 -> -- detail_p : TBasicType TUInt32 CInt -> -- force_detail_quark : TBasicType TBoolean IO CInt -- | Internal function to parse a signal name into its /@signalId@/ -- and /@detail@/ quark. signalParseName :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@detailedSignal@/: a string of the form \"signal-name[detail](#signal:detail)\". -> GType -- ^ /@itype@/: The interface\/instance type that introduced \"signal-name\". -> Bool -- ^ /@forceDetailQuark@/: 'P.True' forces creation of a @/GQuark/@ for the detail. -> m ((Bool, Word32, Word32)) -- ^ __Returns:__ Whether the signal name could successfully be parsed and /@signalIdP@/ and /@detailP@/ contain valid return values. signalParseName :: Text -> GType -> Bool -> m (Bool, Word32, Word32) signalParseName detailedSignal :: Text detailedSignal itype :: GType itype forceDetailQuark :: Bool forceDetailQuark = IO (Bool, Word32, Word32) -> m (Bool, Word32, Word32) forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO (Bool, Word32, Word32) -> m (Bool, Word32, Word32)) -> IO (Bool, Word32, Word32) -> m (Bool, Word32, Word32) forall a b. (a -> b) -> a -> b $ do CString detailedSignal' <- Text -> IO CString textToCString Text detailedSignal let itype' :: CGType itype' = GType -> CGType gtypeToCGType GType itype Ptr Word32 signalIdP <- IO (Ptr Word32) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr Word32) Ptr Word32 detailP <- IO (Ptr Word32) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr Word32) let forceDetailQuark' :: CInt forceDetailQuark' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Bool -> Int forall a. Enum a => a -> Int fromEnum) Bool forceDetailQuark CInt result <- CString -> CGType -> Ptr Word32 -> Ptr Word32 -> CInt -> IO CInt g_signal_parse_name CString detailedSignal' CGType itype' Ptr Word32 signalIdP Ptr Word32 detailP CInt forceDetailQuark' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result Word32 signalIdP' <- Ptr Word32 -> IO Word32 forall a. Storable a => Ptr a -> IO a peek Ptr Word32 signalIdP Word32 detailP' <- Ptr Word32 -> IO Word32 forall a. Storable a => Ptr a -> IO a peek Ptr Word32 detailP CString -> IO () forall a. Ptr a -> IO () freeMem CString detailedSignal' Ptr Word32 -> IO () forall a. Ptr a -> IO () freeMem Ptr Word32 signalIdP Ptr Word32 -> IO () forall a. Ptr a -> IO () freeMem Ptr Word32 detailP (Bool, Word32, Word32) -> IO (Bool, Word32, Word32) forall (m :: * -> *) a. Monad m => a -> m a return (Bool result', Word32 signalIdP', Word32 detailP') -- function g_signal_override_class_closure -- Args: [ Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the signal id" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "instance_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "the instance type on which to override the class closure\n for the signal." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "class_closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the closure." , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_override_class_closure" g_signal_override_class_closure :: Word32 -> -- signal_id : TBasicType TUInt CGType -> -- instance_type : TBasicType TGType Ptr (GClosure ()) -> -- class_closure : TGClosure Nothing IO () -- | Overrides the class closure (i.e. the default handler) for the given signal -- for emissions on instances of /@instanceType@/. /@instanceType@/ must be derived -- from the type to which the signal belongs. -- -- See 'GI.GObject.Functions.signalChainFromOverridden' and -- @/g_signal_chain_from_overridden_handler()/@ for how to chain up to the -- parent class closure from inside the overridden one. signalOverrideClassClosure :: (B.CallStack.HasCallStack, MonadIO m) => Word32 -- ^ /@signalId@/: the signal id -> GType -- ^ /@instanceType@/: the instance type on which to override the class closure -- for the signal. -> GClosure a -- ^ /@classClosure@/: the closure. -> m () signalOverrideClassClosure :: Word32 -> GType -> GClosure a -> m () signalOverrideClassClosure signalId :: Word32 signalId instanceType :: GType instanceType classClosure :: GClosure a classClosure = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let instanceType' :: CGType instanceType' = GType -> CGType gtypeToCGType GType instanceType Ptr (GClosure ()) classClosure' <- GClosure a -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure a classClosure Word32 -> CGType -> Ptr (GClosure ()) -> IO () g_signal_override_class_closure Word32 signalId CGType instanceType' Ptr (GClosure ()) classClosure' GClosure a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GClosure a classClosure () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_name -- Args: [ Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the signal's identifying number." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_signal_name" g_signal_name :: Word32 -> -- signal_id : TBasicType TUInt IO CString -- | Given the signal\'s identifier, finds its name. -- -- Two different signals may have the same name, if they have differing types. signalName :: (B.CallStack.HasCallStack, MonadIO m) => Word32 -- ^ /@signalId@/: the signal\'s identifying number. -> m T.Text -- ^ __Returns:__ the signal name, or 'P.Nothing' if the signal number was invalid. signalName :: Word32 -> m Text signalName signalId :: Word32 signalId = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do CString result <- Word32 -> IO CString g_signal_name Word32 signalId Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "signalName" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_signal_lookup -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the signal's name." , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "itype" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the type that the signal operates on." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUInt) -- throws : False -- Skip return : False foreign import ccall "g_signal_lookup" g_signal_lookup :: CString -> -- name : TBasicType TUTF8 CGType -> -- itype : TBasicType TGType IO Word32 -- | Given the name of the signal and the type of object it connects to, gets -- the signal\'s identifying integer. Emitting the signal by number is -- somewhat faster than using the name each time. -- -- Also tries the ancestors of the given type. -- -- See @/g_signal_new()/@ for details on allowed signal names. signalLookup :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: the signal\'s name. -> GType -- ^ /@itype@/: the type that the signal operates on. -> m Word32 -- ^ __Returns:__ the signal\'s identifying number, or 0 if no signal was found. signalLookup :: Text -> GType -> m Word32 signalLookup name :: Text name itype :: GType itype = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name let itype' :: CGType itype' = GType -> CGType gtypeToCGType GType itype Word32 result <- CString -> CGType -> IO Word32 g_signal_lookup CString name' CGType itype' CString -> IO () forall a. Ptr a -> IO () freeMem CString name' Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_signal_list_ids -- Args: [ Arg -- { argCName = "itype" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Instance or interface type." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "n_ids" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "Location to store the number of signal ids for @itype." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- ] -- Lengths: [ Arg -- { argCName = "n_ids" -- , argType = TBasicType TUInt -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "Location to store the number of signal ids for @itype." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- ] -- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt)) -- throws : False -- Skip return : False foreign import ccall "g_signal_list_ids" g_signal_list_ids :: CGType -> -- itype : TBasicType TGType Ptr Word32 -> -- n_ids : TBasicType TUInt IO (Ptr Word32) -- | Lists the signals by id that a certain instance or interface type -- created. Further information about the signals can be acquired through -- 'GI.GObject.Functions.signalQuery'. signalListIds :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@itype@/: Instance or interface type. -> m [Word32] -- ^ __Returns:__ Newly allocated array of signal IDs. signalListIds :: GType -> m [Word32] signalListIds itype :: GType itype = IO [Word32] -> m [Word32] forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO [Word32] -> m [Word32]) -> IO [Word32] -> m [Word32] forall a b. (a -> b) -> a -> b $ do let itype' :: CGType itype' = GType -> CGType gtypeToCGType GType itype Ptr Word32 nIds <- IO (Ptr Word32) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr Word32) Ptr Word32 result <- CGType -> Ptr Word32 -> IO (Ptr Word32) g_signal_list_ids CGType itype' Ptr Word32 nIds Word32 nIds' <- Ptr Word32 -> IO Word32 forall a. Storable a => Ptr a -> IO a peek Ptr Word32 nIds Text -> Ptr Word32 -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "signalListIds" Ptr Word32 result [Word32] result' <- (Word32 -> Ptr Word32 -> IO [Word32] forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b] unpackStorableArrayWithLength Word32 nIds') Ptr Word32 result Ptr Word32 -> IO () forall a. Ptr a -> IO () freeMem Ptr Word32 result Ptr Word32 -> IO () forall a. Ptr a -> IO () freeMem Ptr Word32 nIds [Word32] -> IO [Word32] forall (m :: * -> *) a. Monad m => a -> m a return [Word32] result' -- function g_signal_has_handler_pending -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the object whose signal handlers are sought." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the signal id." , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the detail." , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "may_be_blocked" -- , argType = TBasicType TBoolean -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "whether blocked handlers should count as match." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_signal_has_handler_pending" g_signal_has_handler_pending :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 CInt -> -- may_be_blocked : TBasicType TBoolean IO CInt -- | Returns whether there are any handlers connected to /@instance@/ for the -- given signal id and detail. -- -- If /@detail@/ is 0 then it will only match handlers that were connected -- without detail. If /@detail@/ is non-zero then it will match handlers -- connected both without detail and with the given detail. This is -- consistent with how a signal emitted with /@detail@/ would be delivered -- to those handlers. -- -- Since 2.46 this also checks for a non-default class closure being -- installed, as this is basically always what you want. -- -- One example of when you might use this is when the arguments to the -- signal are difficult to compute. A class implementor may opt to not -- emit the signal if no one is attached anyway, thus saving the cost -- of building the arguments. signalHasHandlerPending :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: the object whose signal handlers are sought. -> Word32 -- ^ /@signalId@/: the signal id. -> Word32 -- ^ /@detail@/: the detail. -> Bool -- ^ /@mayBeBlocked@/: whether blocked handlers should count as match. -> m Bool -- ^ __Returns:__ 'P.True' if a handler is connected to the signal, 'P.False' -- otherwise. signalHasHandlerPending :: a -> Word32 -> Word32 -> Bool -> m Bool signalHasHandlerPending instance_ :: a instance_ signalId :: Word32 signalId detail :: Word32 detail mayBeBlocked :: Bool mayBeBlocked = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ let mayBeBlocked' :: CInt mayBeBlocked' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Bool -> Int forall a. Enum a => a -> Int fromEnum) Bool mayBeBlocked CInt result <- Ptr Object -> Word32 -> Word32 -> CInt -> IO CInt g_signal_has_handler_pending Ptr Object instance_' Word32 signalId Word32 detail CInt mayBeBlocked' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_signal_handlers_unblock_matched -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The instance to unblock handlers from." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "mask" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalMatchType" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "Mask indicating which of @signal_id, @detail, @closure, @func\n and/or @data the handlers have to match." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Signal the handlers have to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "Signal detail the handlers have to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure the handlers will invoke." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "func" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "The C closure callback of the handlers (useless for non-C closures)." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure data of the handlers' closures." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUInt) -- throws : False -- Skip return : False foreign import ccall "g_signal_handlers_unblock_matched" g_signal_handlers_unblock_matched :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CUInt -> -- mask : TInterface (Name {namespace = "GObject", name = "SignalMatchType"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 Ptr (GClosure ()) -> -- closure : TGClosure Nothing Ptr () -> -- func : TBasicType TPtr Ptr () -> -- data : TBasicType TPtr IO Word32 -- | Unblocks all handlers on an instance that match a certain selection -- criteria. The criteria mask is passed as an OR-ed combination of -- t'GI.GObject.Flags.SignalMatchType' flags, and the criteria values are passed as arguments. -- Passing at least one of the 'GI.GObject.Flags.SignalMatchTypeClosure', 'GI.GObject.Flags.SignalMatchTypeFunc' -- or 'GI.GObject.Flags.SignalMatchTypeData' match flags is required for successful matches. -- If no handlers were found, 0 is returned, the number of unblocked handlers -- otherwise. The match criteria should not apply to any handlers that are -- not currently blocked. signalHandlersUnblockMatched :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance to unblock handlers from. -> [GObject.Flags.SignalMatchType] -- ^ /@mask@/: Mask indicating which of /@signalId@/, /@detail@/, /@closure@/, /@func@/ -- and\/or /@data@/ the handlers have to match. -> Word32 -- ^ /@signalId@/: Signal the handlers have to be connected to. -> Word32 -- ^ /@detail@/: Signal detail the handlers have to be connected to. -> Maybe (GClosure b) -- ^ /@closure@/: The closure the handlers will invoke. -> Ptr () -- ^ /@func@/: The C closure callback of the handlers (useless for non-C closures). -> Ptr () -- ^ /@data@/: The closure data of the handlers\' closures. -> m Word32 -- ^ __Returns:__ The number of handlers that matched. signalHandlersUnblockMatched :: a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m Word32 signalHandlersUnblockMatched instance_ :: a instance_ mask :: [SignalMatchType] mask signalId :: Word32 signalId detail :: Word32 detail closure :: Maybe (GClosure b) closure func :: Ptr () func data_ :: Ptr () data_ = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ let mask' :: CUInt mask' = [SignalMatchType] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [SignalMatchType] mask Ptr (GClosure ()) maybeClosure <- case Maybe (GClosure b) closure of Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) forall a. Ptr a nullPtr Just jClosure :: GClosure b jClosure -> do Ptr (GClosure ()) jClosure' <- GClosure b -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure b jClosure Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) jClosure' Word32 result <- Ptr Object -> CUInt -> Word32 -> Word32 -> Ptr (GClosure ()) -> Ptr () -> Ptr () -> IO Word32 g_signal_handlers_unblock_matched Ptr Object instance_' CUInt mask' Word32 signalId Word32 detail Ptr (GClosure ()) maybeClosure Ptr () func Ptr () data_ a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ Maybe (GClosure b) -> (GClosure b -> IO ()) -> IO () forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m () whenJust Maybe (GClosure b) closure GClosure b -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_signal_handlers_disconnect_matched -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The instance to remove handlers from." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "mask" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalMatchType" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "Mask indicating which of @signal_id, @detail, @closure, @func\n and/or @data the handlers have to match." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Signal the handlers have to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "Signal detail the handlers have to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure the handlers will invoke." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "func" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "The C closure callback of the handlers (useless for non-C closures)." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure data of the handlers' closures." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUInt) -- throws : False -- Skip return : False foreign import ccall "g_signal_handlers_disconnect_matched" g_signal_handlers_disconnect_matched :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CUInt -> -- mask : TInterface (Name {namespace = "GObject", name = "SignalMatchType"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 Ptr (GClosure ()) -> -- closure : TGClosure Nothing Ptr () -> -- func : TBasicType TPtr Ptr () -> -- data : TBasicType TPtr IO Word32 -- | Disconnects all handlers on an instance that match a certain -- selection criteria. The criteria mask is passed as an OR-ed -- combination of t'GI.GObject.Flags.SignalMatchType' flags, and the criteria values are -- passed as arguments. Passing at least one of the -- 'GI.GObject.Flags.SignalMatchTypeClosure', 'GI.GObject.Flags.SignalMatchTypeFunc' or -- 'GI.GObject.Flags.SignalMatchTypeData' match flags is required for successful -- matches. If no handlers were found, 0 is returned, the number of -- disconnected handlers otherwise. signalHandlersDisconnectMatched :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance to remove handlers from. -> [GObject.Flags.SignalMatchType] -- ^ /@mask@/: Mask indicating which of /@signalId@/, /@detail@/, /@closure@/, /@func@/ -- and\/or /@data@/ the handlers have to match. -> Word32 -- ^ /@signalId@/: Signal the handlers have to be connected to. -> Word32 -- ^ /@detail@/: Signal detail the handlers have to be connected to. -> Maybe (GClosure b) -- ^ /@closure@/: The closure the handlers will invoke. -> Ptr () -- ^ /@func@/: The C closure callback of the handlers (useless for non-C closures). -> Ptr () -- ^ /@data@/: The closure data of the handlers\' closures. -> m Word32 -- ^ __Returns:__ The number of handlers that matched. signalHandlersDisconnectMatched :: a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m Word32 signalHandlersDisconnectMatched instance_ :: a instance_ mask :: [SignalMatchType] mask signalId :: Word32 signalId detail :: Word32 detail closure :: Maybe (GClosure b) closure func :: Ptr () func data_ :: Ptr () data_ = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ let mask' :: CUInt mask' = [SignalMatchType] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [SignalMatchType] mask Ptr (GClosure ()) maybeClosure <- case Maybe (GClosure b) closure of Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) forall a. Ptr a nullPtr Just jClosure :: GClosure b jClosure -> do Ptr (GClosure ()) jClosure' <- GClosure b -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure b jClosure Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) jClosure' Word32 result <- Ptr Object -> CUInt -> Word32 -> Word32 -> Ptr (GClosure ()) -> Ptr () -> Ptr () -> IO Word32 g_signal_handlers_disconnect_matched Ptr Object instance_' CUInt mask' Word32 signalId Word32 detail Ptr (GClosure ()) maybeClosure Ptr () func Ptr () data_ a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ Maybe (GClosure b) -> (GClosure b -> IO ()) -> IO () forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m () whenJust Maybe (GClosure b) closure GClosure b -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_signal_handlers_destroy -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The instance whose signal handlers are destroyed" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_handlers_destroy" g_signal_handlers_destroy :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) IO () -- | Destroy all signal handlers of a type instance. This function is -- an implementation detail of the t'GI.GObject.Objects.Object.Object' dispose implementation, -- and should not be used outside of the type system. signalHandlersDestroy :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance whose signal handlers are destroyed -> m () signalHandlersDestroy :: a -> m () signalHandlersDestroy instance_ :: a instance_ = 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 Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr Object -> IO () g_signal_handlers_destroy Ptr Object instance_' a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_handlers_block_matched -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The instance to block handlers from." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "mask" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalMatchType" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "Mask indicating which of @signal_id, @detail, @closure, @func\n and/or @data the handlers have to match." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Signal the handlers have to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "Signal detail the handlers have to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure the handlers will invoke." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "func" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "The C closure callback of the handlers (useless for non-C closures)." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure data of the handlers' closures." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUInt) -- throws : False -- Skip return : False foreign import ccall "g_signal_handlers_block_matched" g_signal_handlers_block_matched :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CUInt -> -- mask : TInterface (Name {namespace = "GObject", name = "SignalMatchType"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 Ptr (GClosure ()) -> -- closure : TGClosure Nothing Ptr () -> -- func : TBasicType TPtr Ptr () -> -- data : TBasicType TPtr IO Word32 -- | Blocks all handlers on an instance that match a certain selection criteria. -- The criteria mask is passed as an OR-ed combination of t'GI.GObject.Flags.SignalMatchType' -- flags, and the criteria values are passed as arguments. -- Passing at least one of the 'GI.GObject.Flags.SignalMatchTypeClosure', 'GI.GObject.Flags.SignalMatchTypeFunc' -- or 'GI.GObject.Flags.SignalMatchTypeData' match flags is required for successful matches. -- If no handlers were found, 0 is returned, the number of blocked handlers -- otherwise. signalHandlersBlockMatched :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance to block handlers from. -> [GObject.Flags.SignalMatchType] -- ^ /@mask@/: Mask indicating which of /@signalId@/, /@detail@/, /@closure@/, /@func@/ -- and\/or /@data@/ the handlers have to match. -> Word32 -- ^ /@signalId@/: Signal the handlers have to be connected to. -> Word32 -- ^ /@detail@/: Signal detail the handlers have to be connected to. -> Maybe (GClosure b) -- ^ /@closure@/: The closure the handlers will invoke. -> Ptr () -- ^ /@func@/: The C closure callback of the handlers (useless for non-C closures). -> Ptr () -- ^ /@data@/: The closure data of the handlers\' closures. -> m Word32 -- ^ __Returns:__ The number of handlers that matched. signalHandlersBlockMatched :: a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m Word32 signalHandlersBlockMatched instance_ :: a instance_ mask :: [SignalMatchType] mask signalId :: Word32 signalId detail :: Word32 detail closure :: Maybe (GClosure b) closure func :: Ptr () func data_ :: Ptr () data_ = IO Word32 -> m Word32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32 forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ let mask' :: CUInt mask' = [SignalMatchType] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [SignalMatchType] mask Ptr (GClosure ()) maybeClosure <- case Maybe (GClosure b) closure of Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) forall a. Ptr a nullPtr Just jClosure :: GClosure b jClosure -> do Ptr (GClosure ()) jClosure' <- GClosure b -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure b jClosure Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) jClosure' Word32 result <- Ptr Object -> CUInt -> Word32 -> Word32 -> Ptr (GClosure ()) -> Ptr () -> Ptr () -> IO Word32 g_signal_handlers_block_matched Ptr Object instance_' CUInt mask' Word32 signalId Word32 detail Ptr (GClosure ()) maybeClosure Ptr () func Ptr () data_ a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ Maybe (GClosure b) -> (GClosure b -> IO ()) -> IO () forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m () whenJust Maybe (GClosure b) closure GClosure b -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr Word32 -> IO Word32 forall (m :: * -> *) a. Monad m => a -> m a return Word32 result -- function g_signal_handler_unblock -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The instance to unblock the signal handler of." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "handler_id" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Handler id of the handler to be unblocked." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_handler_unblock" g_signal_handler_unblock :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CULong -> -- handler_id : TBasicType TULong IO () -- | Undoes the effect of a previous 'GI.GObject.Functions.signalHandlerBlock' call. A -- blocked handler is skipped during signal emissions and will not be -- invoked, unblocking it (for exactly the amount of times it has been -- blocked before) reverts its \"blocked\" state, so the handler will be -- recognized by the signal system and is called upon future or -- currently ongoing signal emissions (since the order in which -- handlers are called during signal emissions is deterministic, -- whether the unblocked handler in question is called as part of a -- currently ongoing emission depends on how far that emission has -- proceeded yet). -- -- The /@handlerId@/ has to be a valid id of a signal handler that is -- connected to a signal of /@instance@/ and is currently blocked. signalHandlerUnblock :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance to unblock the signal handler of. -> CULong -- ^ /@handlerId@/: Handler id of the handler to be unblocked. -> m () signalHandlerUnblock :: a -> CULong -> m () signalHandlerUnblock instance_ :: a instance_ handlerId :: CULong handlerId = 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 Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr Object -> CULong -> IO () g_signal_handler_unblock Ptr Object instance_' CULong handlerId a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_handler_is_connected -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The instance where a signal handler is sought." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "handler_id" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the handler ID." , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_signal_handler_is_connected" g_signal_handler_is_connected :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CULong -> -- handler_id : TBasicType TULong IO CInt -- | Returns whether /@handlerId@/ is the ID of a handler connected to /@instance@/. signalHandlerIsConnected :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance where a signal handler is sought. -> CULong -- ^ /@handlerId@/: the handler ID. -> m Bool -- ^ __Returns:__ whether /@handlerId@/ identifies a handler connected to /@instance@/. signalHandlerIsConnected :: a -> CULong -> m Bool signalHandlerIsConnected instance_ :: a instance_ handlerId :: CULong handlerId = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ CInt result <- Ptr Object -> CULong -> IO CInt g_signal_handler_is_connected Ptr Object instance_' CULong handlerId let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_signal_handler_find -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The instance owning the signal handler to be found." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "mask" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalMatchType" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "Mask indicating which of @signal_id, @detail, @closure, @func\n and/or @data the handler has to match." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Signal the handler has to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "Signal detail the handler has to be connected to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure the handler will invoke." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "func" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "The C closure callback of the handler (useless for non-C closures)." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "The closure data of the handler's closure." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TULong) -- throws : False -- Skip return : False foreign import ccall "g_signal_handler_find" g_signal_handler_find :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CUInt -> -- mask : TInterface (Name {namespace = "GObject", name = "SignalMatchType"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 Ptr (GClosure ()) -> -- closure : TGClosure Nothing Ptr () -> -- func : TBasicType TPtr Ptr () -> -- data : TBasicType TPtr IO CULong -- | Finds the first signal handler that matches certain selection criteria. -- The criteria mask is passed as an OR-ed combination of t'GI.GObject.Flags.SignalMatchType' -- flags, and the criteria values are passed as arguments. -- The match /@mask@/ has to be non-0 for successful matches. -- If no handler was found, 0 is returned. signalHandlerFind :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance owning the signal handler to be found. -> [GObject.Flags.SignalMatchType] -- ^ /@mask@/: Mask indicating which of /@signalId@/, /@detail@/, /@closure@/, /@func@/ -- and\/or /@data@/ the handler has to match. -> Word32 -- ^ /@signalId@/: Signal the handler has to be connected to. -> Word32 -- ^ /@detail@/: Signal detail the handler has to be connected to. -> Maybe (GClosure b) -- ^ /@closure@/: The closure the handler will invoke. -> Ptr () -- ^ /@func@/: The C closure callback of the handler (useless for non-C closures). -> Ptr () -- ^ /@data@/: The closure data of the handler\'s closure. -> m CULong -- ^ __Returns:__ A valid non-0 signal handler id for a successful match. signalHandlerFind :: a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m CULong signalHandlerFind instance_ :: a instance_ mask :: [SignalMatchType] mask signalId :: Word32 signalId detail :: Word32 detail closure :: Maybe (GClosure b) closure func :: Ptr () func data_ :: Ptr () data_ = IO CULong -> m CULong forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ let mask' :: CUInt mask' = [SignalMatchType] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [SignalMatchType] mask Ptr (GClosure ()) maybeClosure <- case Maybe (GClosure b) closure of Nothing -> Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) forall a. Ptr a nullPtr Just jClosure :: GClosure b jClosure -> do Ptr (GClosure ()) jClosure' <- GClosure b -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure b jClosure Ptr (GClosure ()) -> IO (Ptr (GClosure ())) forall (m :: * -> *) a. Monad m => a -> m a return Ptr (GClosure ()) jClosure' CULong result <- Ptr Object -> CUInt -> Word32 -> Word32 -> Ptr (GClosure ()) -> Ptr () -> Ptr () -> IO CULong g_signal_handler_find Ptr Object instance_' CUInt mask' Word32 signalId Word32 detail Ptr (GClosure ()) maybeClosure Ptr () func Ptr () data_ a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ Maybe (GClosure b) -> (GClosure b -> IO ()) -> IO () forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m () whenJust Maybe (GClosure b) closure GClosure b -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr CULong -> IO CULong forall (m :: * -> *) a. Monad m => a -> m a return CULong result -- function g_signal_handler_disconnect -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The instance to remove the signal handler from." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "handler_id" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Handler id of the handler to be disconnected." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_handler_disconnect" g_signal_handler_disconnect :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CULong -> -- handler_id : TBasicType TULong IO () -- | Disconnects a handler from an instance so it will not be called during -- any future or currently ongoing emissions of the signal it has been -- connected to. The /@handlerId@/ becomes invalid and may be reused. -- -- The /@handlerId@/ has to be a valid signal handler id, connected to a -- signal of /@instance@/. signalHandlerDisconnect :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance to remove the signal handler from. -> CULong -- ^ /@handlerId@/: Handler id of the handler to be disconnected. -> m () signalHandlerDisconnect :: a -> CULong -> m () signalHandlerDisconnect instance_ :: a instance_ handlerId :: CULong handlerId = 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 Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr Object -> CULong -> IO () g_signal_handler_disconnect Ptr Object instance_' CULong handlerId a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_handler_block -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The instance to block the signal handler of." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "handler_id" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Handler id of the handler to be blocked." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_handler_block" g_signal_handler_block :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CULong -> -- handler_id : TBasicType TULong IO () -- | Blocks a handler of an instance so it will not be called during any -- signal emissions unless it is unblocked again. Thus \"blocking\" a -- signal handler means to temporarily deactive it, a signal handler -- has to be unblocked exactly the same amount of times it has been -- blocked before to become active again. -- -- The /@handlerId@/ has to be a valid signal handler id, connected to a -- signal of /@instance@/. signalHandlerBlock :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: The instance to block the signal handler of. -> CULong -- ^ /@handlerId@/: Handler id of the handler to be blocked. -> m () signalHandlerBlock :: a -> CULong -> m () signalHandlerBlock instance_ :: a instance_ handlerId :: CULong handlerId = 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 Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr Object -> CULong -> IO () g_signal_handler_block Ptr Object instance_' CULong handlerId a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_get_invocation_hint -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the instance to query" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface -- Name { namespace = "GObject" , name = "SignalInvocationHint" }) -- throws : False -- Skip return : False foreign import ccall "g_signal_get_invocation_hint" g_signal_get_invocation_hint :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) IO (Ptr GObject.SignalInvocationHint.SignalInvocationHint) -- | Returns the invocation hint of the innermost signal emission of instance. signalGetInvocationHint :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: the instance to query -> m GObject.SignalInvocationHint.SignalInvocationHint -- ^ __Returns:__ the invocation hint of the innermost signal emission. signalGetInvocationHint :: a -> m SignalInvocationHint signalGetInvocationHint instance_ :: a instance_ = IO SignalInvocationHint -> m SignalInvocationHint forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO SignalInvocationHint -> m SignalInvocationHint) -> IO SignalInvocationHint -> m SignalInvocationHint forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr SignalInvocationHint result <- Ptr Object -> IO (Ptr SignalInvocationHint) g_signal_get_invocation_hint Ptr Object instance_' Text -> Ptr SignalInvocationHint -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "signalGetInvocationHint" Ptr SignalInvocationHint result SignalInvocationHint result' <- ((ManagedPtr SignalInvocationHint -> SignalInvocationHint) -> Ptr SignalInvocationHint -> IO SignalInvocationHint forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr SignalInvocationHint -> SignalInvocationHint GObject.SignalInvocationHint.SignalInvocationHint) Ptr SignalInvocationHint result a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ SignalInvocationHint -> IO SignalInvocationHint forall (m :: * -> *) a. Monad m => a -> m a return SignalInvocationHint result' -- function g_signal_emitv -- Args: [ Arg -- { argCName = "instance_and_params" -- , argType = -- TCArray -- False -- (-1) -- (-1) -- (TInterface Name { namespace = "GObject" , name = "Value" }) -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "argument list for the signal emission.\n The first element in the array is a #GValue for the instance the signal\n is being emitted on. The rest are any arguments to be passed to the signal." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the signal id" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the detail" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "Location to\nstore the return value of the signal emission. This must be provided if the\nspecified signal returns a value, but may be ignored otherwise." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = True -- , transfer = TransferEverything -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_emitv" g_signal_emitv :: Ptr GValue -> -- instance_and_params : TCArray False (-1) (-1) (TInterface (Name {namespace = "GObject", name = "Value"})) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 Ptr GValue -> -- return_value : TInterface (Name {namespace = "GObject", name = "Value"}) IO () -- | Emits a signal. -- -- Note that 'GI.GObject.Functions.signalEmitv' doesn\'t change /@returnValue@/ if no handlers are -- connected, in contrast to @/g_signal_emit()/@ and @/g_signal_emit_valist()/@. signalEmitv :: (B.CallStack.HasCallStack, MonadIO m) => [GValue] -- ^ /@instanceAndParams@/: argument list for the signal emission. -- The first element in the array is a t'GI.GObject.Structs.Value.Value' for the instance the signal -- is being emitted on. The rest are any arguments to be passed to the signal. -> Word32 -- ^ /@signalId@/: the signal id -> Word32 -- ^ /@detail@/: the detail -> m (GValue) signalEmitv :: [GValue] -> Word32 -> Word32 -> m GValue signalEmitv instanceAndParams :: [GValue] instanceAndParams signalId :: Word32 signalId detail :: Word32 detail = IO GValue -> m GValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue forall a b. (a -> b) -> a -> b $ do [Ptr GValue] instanceAndParams' <- (GValue -> IO (Ptr GValue)) -> [GValue] -> IO [Ptr GValue] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) mapM GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr [GValue] instanceAndParams Ptr GValue instanceAndParams'' <- Int -> [Ptr GValue] -> IO (Ptr GValue) forall a. Int -> [Ptr a] -> IO (Ptr a) packBlockArray 24 [Ptr GValue] instanceAndParams' Ptr GValue returnValue <- Int -> IO (Ptr GValue) forall a. BoxedObject a => Int -> IO (Ptr a) callocBoxedBytes 24 :: IO (Ptr GValue) Ptr GValue -> Word32 -> Word32 -> Ptr GValue -> IO () g_signal_emitv Ptr GValue instanceAndParams'' Word32 signalId Word32 detail Ptr GValue returnValue GValue returnValue' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue forall a. (HasCallStack, BoxedObject a) => (ManagedPtr a -> a) -> Ptr a -> IO a wrapBoxed ManagedPtr GValue -> GValue GValue) Ptr GValue returnValue (GValue -> IO ()) -> [GValue] -> IO () forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr [GValue] instanceAndParams Ptr GValue -> IO () forall a. Ptr a -> IO () freeMem Ptr GValue instanceAndParams'' GValue -> IO GValue forall (m :: * -> *) a. Monad m => a -> m a return GValue returnValue' -- function g_signal_connect_closure_by_id -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the instance to connect to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the id of the signal." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the detail." , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the closure to connect." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "after" -- , argType = TBasicType TBoolean -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "whether the handler should be called before or after the\n default handler of the signal." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TULong) -- throws : False -- Skip return : False foreign import ccall "g_signal_connect_closure_by_id" g_signal_connect_closure_by_id :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 Ptr (GClosure ()) -> -- closure : TGClosure Nothing CInt -> -- after : TBasicType TBoolean IO CULong -- | Connects a closure to a signal for a particular object. signalConnectClosureById :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: the instance to connect to. -> Word32 -- ^ /@signalId@/: the id of the signal. -> Word32 -- ^ /@detail@/: the detail. -> GClosure b -- ^ /@closure@/: the closure to connect. -> Bool -- ^ /@after@/: whether the handler should be called before or after the -- default handler of the signal. -> m CULong -- ^ __Returns:__ the handler ID (always greater than 0 for successful connections) signalConnectClosureById :: a -> Word32 -> Word32 -> GClosure b -> Bool -> m CULong signalConnectClosureById instance_ :: a instance_ signalId :: Word32 signalId detail :: Word32 detail closure :: GClosure b closure after :: Bool after = IO CULong -> m CULong forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ Ptr (GClosure ()) closure' <- GClosure b -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure b closure let after' :: CInt after' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Bool -> Int forall a. Enum a => a -> Int fromEnum) Bool after CULong result <- Ptr Object -> Word32 -> Word32 -> Ptr (GClosure ()) -> CInt -> IO CULong g_signal_connect_closure_by_id Ptr Object instance_' Word32 signalId Word32 detail Ptr (GClosure ()) closure' CInt after' a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ GClosure b -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GClosure b closure CULong -> IO CULong forall (m :: * -> *) a. Monad m => a -> m a return CULong result -- function g_signal_connect_closure -- Args: [ Arg -- { argCName = "instance" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the instance to connect to." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detailed_signal" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a string of the form \"signal-name::detail\"." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "closure" -- , argType = TGClosure Nothing -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the closure to connect." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "after" -- , argType = TBasicType TBoolean -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "whether the handler should be called before or after the\n default handler of the signal." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TULong) -- throws : False -- Skip return : False foreign import ccall "g_signal_connect_closure" g_signal_connect_closure :: Ptr GObject.Object.Object -> -- instance : TInterface (Name {namespace = "GObject", name = "Object"}) CString -> -- detailed_signal : TBasicType TUTF8 Ptr (GClosure ()) -> -- closure : TGClosure Nothing CInt -> -- after : TBasicType TBoolean IO CULong -- | Connects a closure to a signal for a particular object. signalConnectClosure :: (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) => a -- ^ /@instance@/: the instance to connect to. -> T.Text -- ^ /@detailedSignal@/: a string of the form \"signal-name[detail](#signal:detail)\". -> GClosure b -- ^ /@closure@/: the closure to connect. -> Bool -- ^ /@after@/: whether the handler should be called before or after the -- default handler of the signal. -> m CULong -- ^ __Returns:__ the handler ID (always greater than 0 for successful connections) signalConnectClosure :: a -> Text -> GClosure b -> Bool -> m CULong signalConnectClosure instance_ :: a instance_ detailedSignal :: Text detailedSignal closure :: GClosure b closure after :: Bool after = IO CULong -> m CULong forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong forall a b. (a -> b) -> a -> b $ do Ptr Object instance_' <- a -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a instance_ CString detailedSignal' <- Text -> IO CString textToCString Text detailedSignal Ptr (GClosure ()) closure' <- GClosure b -> IO (Ptr (GClosure ())) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr GClosure b closure let after' :: CInt after' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Bool -> Int forall a. Enum a => a -> Int fromEnum) Bool after CULong result <- Ptr Object -> CString -> Ptr (GClosure ()) -> CInt -> IO CULong g_signal_connect_closure Ptr Object instance_' CString detailedSignal' Ptr (GClosure ()) closure' CInt after' a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a instance_ GClosure b -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GClosure b closure CString -> IO () forall a. Ptr a -> IO () freeMem CString detailedSignal' CULong -> IO CULong forall (m :: * -> *) a. Monad m => a -> m a return CULong result -- function g_signal_chain_from_overridden -- Args: [ Arg -- { argCName = "instance_and_params" -- , argType = -- TCArray -- False -- (-1) -- (-1) -- (TInterface Name { namespace = "GObject" , name = "Value" }) -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "the argument list of the signal emission.\n The first element in the array is a #GValue for the instance the signal\n is being emitted on. The rest are any arguments to be passed to the signal." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "Location for the return value." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_signal_chain_from_overridden" g_signal_chain_from_overridden :: Ptr GValue -> -- instance_and_params : TCArray False (-1) (-1) (TInterface (Name {namespace = "GObject", name = "Value"})) Ptr GValue -> -- return_value : TInterface (Name {namespace = "GObject", name = "Value"}) IO () -- | Calls the original class closure of a signal. This function should only -- be called from an overridden class closure; see -- 'GI.GObject.Functions.signalOverrideClassClosure' and -- @/g_signal_override_class_handler()/@. signalChainFromOverridden :: (B.CallStack.HasCallStack, MonadIO m) => [GValue] -- ^ /@instanceAndParams@/: the argument list of the signal emission. -- The first element in the array is a t'GI.GObject.Structs.Value.Value' for the instance the signal -- is being emitted on. The rest are any arguments to be passed to the signal. -> GValue -- ^ /@returnValue@/: Location for the return value. -> m () signalChainFromOverridden :: [GValue] -> GValue -> m () signalChainFromOverridden instanceAndParams :: [GValue] instanceAndParams returnValue :: GValue returnValue = 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 GValue] instanceAndParams' <- (GValue -> IO (Ptr GValue)) -> [GValue] -> IO [Ptr GValue] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) mapM GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr [GValue] instanceAndParams Ptr GValue instanceAndParams'' <- Int -> [Ptr GValue] -> IO (Ptr GValue) forall a. Int -> [Ptr a] -> IO (Ptr a) packBlockArray 24 [Ptr GValue] instanceAndParams' Ptr GValue returnValue' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue returnValue Ptr GValue -> Ptr GValue -> IO () g_signal_chain_from_overridden Ptr GValue instanceAndParams'' Ptr GValue returnValue' (GValue -> IO ()) -> [GValue] -> IO () forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr [GValue] instanceAndParams GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue returnValue Ptr GValue -> IO () forall a. Ptr a -> IO () freeMem Ptr GValue instanceAndParams'' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_signal_add_emission_hook -- Args: [ Arg -- { argCName = "signal_id" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the signal identifier, as returned by g_signal_lookup()." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "detail" -- , argType = TBasicType TUInt32 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the detail on which to call the hook." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "hook_func" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalEmissionHook" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GSignalEmissionHook function." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeNotified -- , argClosure = 3 -- , argDestroy = 4 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "hook_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "user data for @hook_func." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "data_destroy" -- , argType = -- TInterface Name { namespace = "GLib" , name = "DestroyNotify" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GDestroyNotify for @hook_data." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeAsync -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TULong) -- throws : False -- Skip return : False foreign import ccall "g_signal_add_emission_hook" g_signal_add_emission_hook :: Word32 -> -- signal_id : TBasicType TUInt Word32 -> -- detail : TBasicType TUInt32 FunPtr GObject.Callbacks.C_SignalEmissionHook -> -- hook_func : TInterface (Name {namespace = "GObject", name = "SignalEmissionHook"}) Ptr () -> -- hook_data : TBasicType TPtr FunPtr GLib.Callbacks.C_DestroyNotify -> -- data_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"}) IO CULong -- | Adds an emission hook for a signal, which will get called for any emission -- of that signal, independent of the instance. This is possible only -- for signals which don\'t have @/G_SIGNAL_NO_HOOKS/@ flag set. signalAddEmissionHook :: (B.CallStack.HasCallStack, MonadIO m) => Word32 -- ^ /@signalId@/: the signal identifier, as returned by 'GI.GObject.Functions.signalLookup'. -> Word32 -- ^ /@detail@/: the detail on which to call the hook. -> GObject.Callbacks.SignalEmissionHook -- ^ /@hookFunc@/: a t'GI.GObject.Callbacks.SignalEmissionHook' function. -> m CULong -- ^ __Returns:__ the hook id, for later use with 'GI.GObject.Functions.signalRemoveEmissionHook'. signalAddEmissionHook :: Word32 -> Word32 -> SignalEmissionHook -> m CULong signalAddEmissionHook signalId :: Word32 signalId detail :: Word32 detail hookFunc :: SignalEmissionHook hookFunc = IO CULong -> m CULong forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong forall a b. (a -> b) -> a -> b $ do FunPtr C_SignalEmissionHook hookFunc' <- C_SignalEmissionHook -> IO (FunPtr C_SignalEmissionHook) GObject.Callbacks.mk_SignalEmissionHook (Maybe (Ptr (FunPtr C_SignalEmissionHook)) -> SignalEmissionHook -> C_SignalEmissionHook GObject.Callbacks.wrap_SignalEmissionHook Maybe (Ptr (FunPtr C_SignalEmissionHook)) forall a. Maybe a Nothing SignalEmissionHook hookFunc) let hookData :: Ptr () hookData = FunPtr C_SignalEmissionHook -> Ptr () forall a b. FunPtr a -> Ptr b castFunPtrToPtr FunPtr C_SignalEmissionHook hookFunc' let dataDestroy :: FunPtr (Ptr a -> IO ()) dataDestroy = FunPtr (Ptr a -> IO ()) forall a. FunPtr (Ptr a -> IO ()) safeFreeFunPtrPtr CULong result <- Word32 -> Word32 -> FunPtr C_SignalEmissionHook -> Ptr () -> FunPtr (Ptr () -> IO ()) -> IO CULong g_signal_add_emission_hook Word32 signalId Word32 detail FunPtr C_SignalEmissionHook hookFunc' Ptr () hookData FunPtr (Ptr () -> IO ()) forall a. FunPtr (Ptr a -> IO ()) dataDestroy CULong -> IO CULong forall (m :: * -> *) a. Monad m => a -> m a return CULong result -- function g_signal_accumulator_true_handled -- Args: [ Arg -- { argCName = "ihint" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalInvocationHint" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_accu" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "handler_return" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "dummy" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_signal_accumulator_true_handled" g_signal_accumulator_true_handled :: Ptr GObject.SignalInvocationHint.SignalInvocationHint -> -- ihint : TInterface (Name {namespace = "GObject", name = "SignalInvocationHint"}) Ptr GValue -> -- return_accu : TInterface (Name {namespace = "GObject", name = "Value"}) Ptr GValue -> -- handler_return : TInterface (Name {namespace = "GObject", name = "Value"}) Ptr () -> -- dummy : TBasicType TPtr IO CInt -- | A predefined t'GI.GObject.Callbacks.SignalAccumulator' for signals that return a -- boolean values. The behavior that this accumulator gives is -- that a return of 'P.True' stops the signal emission: no further -- callbacks will be invoked, while a return of 'P.False' allows -- the emission to continue. The idea here is that a 'P.True' return -- indicates that the callback handled the signal, and no further -- handling is needed. -- -- /Since: 2.4/ signalAccumulatorTrueHandled :: (B.CallStack.HasCallStack, MonadIO m) => GObject.SignalInvocationHint.SignalInvocationHint -- ^ /@ihint@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> GValue -- ^ /@returnAccu@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> GValue -- ^ /@handlerReturn@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> Ptr () -- ^ /@dummy@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> m Bool -- ^ __Returns:__ standard t'GI.GObject.Callbacks.SignalAccumulator' result signalAccumulatorTrueHandled :: SignalInvocationHint -> GValue -> GValue -> Ptr () -> m Bool signalAccumulatorTrueHandled ihint :: SignalInvocationHint ihint returnAccu :: GValue returnAccu handlerReturn :: GValue handlerReturn dummy :: Ptr () dummy = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr SignalInvocationHint ihint' <- SignalInvocationHint -> IO (Ptr SignalInvocationHint) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr SignalInvocationHint ihint Ptr GValue returnAccu' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue returnAccu Ptr GValue handlerReturn' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue handlerReturn CInt result <- Ptr SignalInvocationHint -> Ptr GValue -> Ptr GValue -> Ptr () -> IO CInt g_signal_accumulator_true_handled Ptr SignalInvocationHint ihint' Ptr GValue returnAccu' Ptr GValue handlerReturn' Ptr () dummy let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result SignalInvocationHint -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr SignalInvocationHint ihint GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue returnAccu GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue handlerReturn Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_signal_accumulator_first_wins -- Args: [ Arg -- { argCName = "ihint" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "SignalInvocationHint" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "return_accu" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "handler_return" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "dummy" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "standard #GSignalAccumulator parameter" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_signal_accumulator_first_wins" g_signal_accumulator_first_wins :: Ptr GObject.SignalInvocationHint.SignalInvocationHint -> -- ihint : TInterface (Name {namespace = "GObject", name = "SignalInvocationHint"}) Ptr GValue -> -- return_accu : TInterface (Name {namespace = "GObject", name = "Value"}) Ptr GValue -> -- handler_return : TInterface (Name {namespace = "GObject", name = "Value"}) Ptr () -> -- dummy : TBasicType TPtr IO CInt -- | A predefined t'GI.GObject.Callbacks.SignalAccumulator' for signals intended to be used as a -- hook for application code to provide a particular value. Usually -- only one such value is desired and multiple handlers for the same -- signal don\'t make much sense (except for the case of the default -- handler defined in the class structure, in which case you will -- usually want the signal connection to override the class handler). -- -- This accumulator will use the return value from the first signal -- handler that is run as the return value for the signal and not run -- any further handlers (ie: the first handler \"wins\"). -- -- /Since: 2.28/ signalAccumulatorFirstWins :: (B.CallStack.HasCallStack, MonadIO m) => GObject.SignalInvocationHint.SignalInvocationHint -- ^ /@ihint@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> GValue -- ^ /@returnAccu@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> GValue -- ^ /@handlerReturn@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> Ptr () -- ^ /@dummy@/: standard t'GI.GObject.Callbacks.SignalAccumulator' parameter -> m Bool -- ^ __Returns:__ standard t'GI.GObject.Callbacks.SignalAccumulator' result signalAccumulatorFirstWins :: SignalInvocationHint -> GValue -> GValue -> Ptr () -> m Bool signalAccumulatorFirstWins ihint :: SignalInvocationHint ihint returnAccu :: GValue returnAccu handlerReturn :: GValue handlerReturn dummy :: Ptr () dummy = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr SignalInvocationHint ihint' <- SignalInvocationHint -> IO (Ptr SignalInvocationHint) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr SignalInvocationHint ihint Ptr GValue returnAccu' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue returnAccu Ptr GValue handlerReturn' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue handlerReturn CInt result <- Ptr SignalInvocationHint -> Ptr GValue -> Ptr GValue -> Ptr () -> IO CInt g_signal_accumulator_first_wins Ptr SignalInvocationHint ihint' Ptr GValue returnAccu' Ptr GValue handlerReturn' Ptr () dummy let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result SignalInvocationHint -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr SignalInvocationHint ihint GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue returnAccu GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue handlerReturn Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_pointer_type_register_static -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the name of the new pointer type." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_pointer_type_register_static" g_pointer_type_register_static :: CString -> -- name : TBasicType TUTF8 IO CGType -- | Creates a new @/G_TYPE_POINTER/@ derived type id for a new -- pointer type with name /@name@/. pointerTypeRegisterStatic :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: the name of the new pointer type. -> m GType -- ^ __Returns:__ a new @/G_TYPE_POINTER/@ derived type id for /@name@/. pointerTypeRegisterStatic :: Text -> m GType pointerTypeRegisterStatic name :: Text name = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CGType result <- CString -> IO CGType g_pointer_type_register_static CString name' let result' :: GType result' = CGType -> GType GType CGType result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_param_values_cmp -- Args: [ Arg -- { argCName = "pspec" -- , argType = TParamSpec -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a valid #GParamSpec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value1" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue of correct type for @pspec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value2" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue of correct type for @pspec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TInt) -- throws : False -- Skip return : False foreign import ccall "g_param_values_cmp" g_param_values_cmp :: Ptr GParamSpec -> -- pspec : TParamSpec Ptr GValue -> -- value1 : TInterface (Name {namespace = "GObject", name = "Value"}) Ptr GValue -> -- value2 : TInterface (Name {namespace = "GObject", name = "Value"}) IO Int32 -- | Compares /@value1@/ with /@value2@/ according to /@pspec@/, and return -1, 0 or +1, -- if /@value1@/ is found to be less than, equal to or greater than /@value2@/, -- respectively. paramValuesCmp :: (B.CallStack.HasCallStack, MonadIO m) => GParamSpec -- ^ /@pspec@/: a valid t'GI.GObject.Objects.ParamSpec.ParamSpec' -> GValue -- ^ /@value1@/: a t'GI.GObject.Structs.Value.Value' of correct type for /@pspec@/ -> GValue -- ^ /@value2@/: a t'GI.GObject.Structs.Value.Value' of correct type for /@pspec@/ -> m Int32 -- ^ __Returns:__ -1, 0 or +1, for a less than, equal to or greater than result paramValuesCmp :: GParamSpec -> GValue -> GValue -> m Int32 paramValuesCmp pspec :: GParamSpec pspec value1 :: GValue value1 value2 :: GValue value2 = IO Int32 -> m Int32 forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32 forall a b. (a -> b) -> a -> b $ do Ptr GParamSpec pspec' <- GParamSpec -> IO (Ptr GParamSpec) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GParamSpec pspec Ptr GValue value1' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value1 Ptr GValue value2' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value2 Int32 result <- Ptr GParamSpec -> Ptr GValue -> Ptr GValue -> IO Int32 g_param_values_cmp Ptr GParamSpec pspec' Ptr GValue value1' Ptr GValue value2' GParamSpec -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GParamSpec pspec GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value1 GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value2 Int32 -> IO Int32 forall (m :: * -> *) a. Monad m => a -> m a return Int32 result -- function g_param_value_validate -- Args: [ Arg -- { argCName = "pspec" -- , argType = TParamSpec -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a valid #GParamSpec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue of correct type for @pspec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_param_value_validate" g_param_value_validate :: Ptr GParamSpec -> -- pspec : TParamSpec Ptr GValue -> -- value : TInterface (Name {namespace = "GObject", name = "Value"}) IO CInt -- | Ensures that the contents of /@value@/ comply with the specifications -- set out by /@pspec@/. For example, a t'GI.GObject.Objects.ParamSpecInt.ParamSpecInt' might require -- that integers stored in /@value@/ may not be smaller than -42 and not be -- greater than +42. If /@value@/ contains an integer outside of this range, -- it is modified accordingly, so the resulting value will fit into the -- range -42 .. +42. paramValueValidate :: (B.CallStack.HasCallStack, MonadIO m) => GParamSpec -- ^ /@pspec@/: a valid t'GI.GObject.Objects.ParamSpec.ParamSpec' -> GValue -- ^ /@value@/: a t'GI.GObject.Structs.Value.Value' of correct type for /@pspec@/ -> m Bool -- ^ __Returns:__ whether modifying /@value@/ was necessary to ensure validity paramValueValidate :: GParamSpec -> GValue -> m Bool paramValueValidate pspec :: GParamSpec pspec value :: GValue value = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr GParamSpec pspec' <- GParamSpec -> IO (Ptr GParamSpec) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GParamSpec pspec Ptr GValue value' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value CInt result <- Ptr GParamSpec -> Ptr GValue -> IO CInt g_param_value_validate Ptr GParamSpec pspec' Ptr GValue value' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result GParamSpec -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GParamSpec pspec GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_param_value_set_default -- Args: [ Arg -- { argCName = "pspec" -- , argType = TParamSpec -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a valid #GParamSpec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue of correct type for @pspec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_param_value_set_default" g_param_value_set_default :: Ptr GParamSpec -> -- pspec : TParamSpec Ptr GValue -> -- value : TInterface (Name {namespace = "GObject", name = "Value"}) IO () -- | Sets /@value@/ to its default value as specified in /@pspec@/. paramValueSetDefault :: (B.CallStack.HasCallStack, MonadIO m) => GParamSpec -- ^ /@pspec@/: a valid t'GI.GObject.Objects.ParamSpec.ParamSpec' -> GValue -- ^ /@value@/: a t'GI.GObject.Structs.Value.Value' of correct type for /@pspec@/ -> m () paramValueSetDefault :: GParamSpec -> GValue -> m () paramValueSetDefault pspec :: GParamSpec pspec value :: GValue value = 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 GParamSpec pspec' <- GParamSpec -> IO (Ptr GParamSpec) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GParamSpec pspec Ptr GValue value' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value Ptr GParamSpec -> Ptr GValue -> IO () g_param_value_set_default Ptr GParamSpec pspec' Ptr GValue value' GParamSpec -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GParamSpec pspec GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_param_value_defaults -- Args: [ Arg -- { argCName = "pspec" -- , argType = TParamSpec -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a valid #GParamSpec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GValue of correct type for @pspec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_param_value_defaults" g_param_value_defaults :: Ptr GParamSpec -> -- pspec : TParamSpec Ptr GValue -> -- value : TInterface (Name {namespace = "GObject", name = "Value"}) IO CInt -- | Checks whether /@value@/ contains the default value as specified in /@pspec@/. paramValueDefaults :: (B.CallStack.HasCallStack, MonadIO m) => GParamSpec -- ^ /@pspec@/: a valid t'GI.GObject.Objects.ParamSpec.ParamSpec' -> GValue -- ^ /@value@/: a t'GI.GObject.Structs.Value.Value' of correct type for /@pspec@/ -> m Bool -- ^ __Returns:__ whether /@value@/ contains the canonical default for this /@pspec@/ paramValueDefaults :: GParamSpec -> GValue -> m Bool paramValueDefaults pspec :: GParamSpec pspec value :: GValue value = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr GParamSpec pspec' <- GParamSpec -> IO (Ptr GParamSpec) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GParamSpec pspec Ptr GValue value' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue value CInt result <- Ptr GParamSpec -> Ptr GValue -> IO CInt g_param_value_defaults Ptr GParamSpec pspec' Ptr GValue value' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result GParamSpec -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GParamSpec pspec GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue value Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_param_value_convert -- Args: [ Arg -- { argCName = "pspec" -- , argType = TParamSpec -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a valid #GParamSpec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "src_value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "souce #GValue" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "dest_value" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Value" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "destination #GValue of correct type for @pspec" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "strict_validation" -- , argType = TBasicType TBoolean -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "%TRUE requires @dest_value to conform to @pspec\nwithout modifications" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "g_param_value_convert" g_param_value_convert :: Ptr GParamSpec -> -- pspec : TParamSpec Ptr GValue -> -- src_value : TInterface (Name {namespace = "GObject", name = "Value"}) Ptr GValue -> -- dest_value : TInterface (Name {namespace = "GObject", name = "Value"}) CInt -> -- strict_validation : TBasicType TBoolean IO CInt -- | Transforms /@srcValue@/ into /@destValue@/ if possible, and then -- validates /@destValue@/, in order for it to conform to /@pspec@/. If -- /@strictValidation@/ is 'P.True' this function will only succeed if the -- transformed /@destValue@/ complied to /@pspec@/ without modifications. -- -- See also 'GI.GObject.Functions.valueTypeTransformable', 'GI.GObject.Structs.Value.valueTransform' and -- 'GI.GObject.Functions.paramValueValidate'. paramValueConvert :: (B.CallStack.HasCallStack, MonadIO m) => GParamSpec -- ^ /@pspec@/: a valid t'GI.GObject.Objects.ParamSpec.ParamSpec' -> GValue -- ^ /@srcValue@/: souce t'GI.GObject.Structs.Value.Value' -> GValue -- ^ /@destValue@/: destination t'GI.GObject.Structs.Value.Value' of correct type for /@pspec@/ -> Bool -- ^ /@strictValidation@/: 'P.True' requires /@destValue@/ to conform to /@pspec@/ -- without modifications -> m Bool -- ^ __Returns:__ 'P.True' if transformation and validation were successful, -- 'P.False' otherwise and /@destValue@/ is left untouched. paramValueConvert :: GParamSpec -> GValue -> GValue -> Bool -> m Bool paramValueConvert pspec :: GParamSpec pspec srcValue :: GValue srcValue destValue :: GValue destValue strictValidation :: Bool strictValidation = IO Bool -> m Bool forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do Ptr GParamSpec pspec' <- GParamSpec -> IO (Ptr GParamSpec) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GParamSpec pspec Ptr GValue srcValue' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue srcValue Ptr GValue destValue' <- GValue -> IO (Ptr GValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr GValue destValue let strictValidation' :: CInt strictValidation' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Bool -> Int forall a. Enum a => a -> Int fromEnum) Bool strictValidation CInt result <- Ptr GParamSpec -> Ptr GValue -> Ptr GValue -> CInt -> IO CInt g_param_value_convert Ptr GParamSpec pspec' Ptr GValue srcValue' Ptr GValue destValue' CInt strictValidation' let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= 0) CInt result GParamSpec -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GParamSpec pspec GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue srcValue GValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr GValue destValue Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' -- function g_param_type_register_static -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "0-terminated string used as the name of the new #GParamSpec type." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "pspec_info" -- , argType = -- TInterface -- Name { namespace = "GObject" , name = "ParamSpecTypeInfo" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "The #GParamSpecTypeInfo for this #GParamSpec type." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_param_type_register_static" g_param_type_register_static :: CString -> -- name : TBasicType TUTF8 Ptr GObject.ParamSpecTypeInfo.ParamSpecTypeInfo -> -- pspec_info : TInterface (Name {namespace = "GObject", name = "ParamSpecTypeInfo"}) IO CGType -- | Registers /@name@/ as the name of a new static type derived from -- @/G_TYPE_PARAM/@. The type system uses the information contained in -- the t'GI.GObject.Structs.ParamSpecTypeInfo.ParamSpecTypeInfo' structure pointed to by /@info@/ to manage the -- t'GI.GObject.Objects.ParamSpec.ParamSpec' type and its instances. paramTypeRegisterStatic :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: 0-terminated string used as the name of the new t'GI.GObject.Objects.ParamSpec.ParamSpec' type. -> GObject.ParamSpecTypeInfo.ParamSpecTypeInfo -- ^ /@pspecInfo@/: The t'GI.GObject.Structs.ParamSpecTypeInfo.ParamSpecTypeInfo' for this t'GI.GObject.Objects.ParamSpec.ParamSpec' type. -> m GType -- ^ __Returns:__ The new type identifier. paramTypeRegisterStatic :: Text -> ParamSpecTypeInfo -> m GType paramTypeRegisterStatic name :: Text name pspecInfo :: ParamSpecTypeInfo pspecInfo = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name Ptr ParamSpecTypeInfo pspecInfo' <- ParamSpecTypeInfo -> IO (Ptr ParamSpecTypeInfo) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr ParamSpecTypeInfo pspecInfo CGType result <- CString -> Ptr ParamSpecTypeInfo -> IO CGType g_param_type_register_static CString name' Ptr ParamSpecTypeInfo pspecInfo' let result' :: GType result' = CGType -> GType GType CGType result ParamSpecTypeInfo -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr ParamSpecTypeInfo pspecInfo CString -> IO () forall a. Ptr a -> IO () freeMem CString name' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_param_spec_variant -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "type" -- , argType = -- TInterface Name { namespace = "GLib" , name = "VariantType" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GVariantType" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TVariant -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GVariant of type @type to\n use as the default value, or %NULL" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_variant" g_param_spec_variant :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Ptr GLib.VariantType.VariantType -> -- type : TInterface (Name {namespace = "GLib", name = "VariantType"}) Ptr GVariant -> -- default_value : TVariant CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecVariant.ParamSpecVariant' instance specifying a t'GVariant' -- property. -- -- If /@defaultValue@/ is floating, it is consumed. -- -- See @/g_param_spec_internal()/@ for details on property names. -- -- /Since: 2.26/ paramSpecVariant :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GLib.VariantType.VariantType -- ^ /@type@/: a t'GI.GLib.Structs.VariantType.VariantType' -> Maybe (GVariant) -- ^ /@defaultValue@/: a t'GVariant' of type /@type@/ to -- use as the default value, or 'P.Nothing' -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ the newly created t'GI.GObject.Objects.ParamSpec.ParamSpec' paramSpecVariant :: Text -> Text -> Text -> VariantType -> Maybe GVariant -> [ParamFlags] -> m GParamSpec paramSpecVariant name :: Text name nick :: Text nick blurb :: Text blurb type_ :: VariantType type_ defaultValue :: Maybe GVariant defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb Ptr VariantType type_' <- VariantType -> IO (Ptr VariantType) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr VariantType type_ Ptr GVariant maybeDefaultValue <- case Maybe GVariant defaultValue of Nothing -> Ptr GVariant -> IO (Ptr GVariant) forall (m :: * -> *) a. Monad m => a -> m a return Ptr GVariant forall a. Ptr a nullPtr Just jDefaultValue :: GVariant jDefaultValue -> do Ptr GVariant jDefaultValue' <- GVariant -> IO (Ptr GVariant) B.GVariant.disownGVariant GVariant jDefaultValue Ptr GVariant -> IO (Ptr GVariant) forall (m :: * -> *) a. Monad m => a -> m a return Ptr GVariant jDefaultValue' let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> Ptr VariantType -> Ptr GVariant -> CUInt -> IO (Ptr GParamSpec) g_param_spec_variant CString name' CString nick' CString blurb' Ptr VariantType type_' Ptr GVariant maybeDefaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecVariant" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result VariantType -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr VariantType type_ Maybe GVariant -> (GVariant -> IO ()) -> IO () forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m () whenJust Maybe GVariant defaultValue GVariant -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_unichar -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TUniChar -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_unichar" g_param_spec_unichar :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CInt -> -- default_value : TBasicType TUniChar CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecUnichar.ParamSpecUnichar' instance specifying a @/G_TYPE_UINT/@ -- property. t'GI.GObject.Structs.Value.Value' structures for this property can be accessed with -- 'GI.GObject.Structs.Value.valueSetUint' and 'GI.GObject.Structs.Value.valueGetUint'. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecUnichar :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Char -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecUnichar :: Text -> Text -> Text -> Char -> [ParamFlags] -> m GParamSpec paramSpecUnichar name :: Text name nick :: Text nick blurb :: Text blurb defaultValue :: Char defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let defaultValue' :: CInt defaultValue' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Char -> Int) -> Char -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> Int ord) Char defaultValue let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CInt -> CUInt -> IO (Ptr GParamSpec) g_param_spec_unichar CString name' CString nick' CString blurb' CInt defaultValue' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecUnichar" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_ulong -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TULong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_ulong" g_param_spec_ulong :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CULong -> -- minimum : TBasicType TULong CULong -> -- maximum : TBasicType TULong CULong -> -- default_value : TBasicType TULong CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecULong.ParamSpecULong' instance specifying a @/G_TYPE_ULONG/@ -- property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecUlong :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> CULong -- ^ /@minimum@/: minimum value for the property specified -> CULong -- ^ /@maximum@/: maximum value for the property specified -> CULong -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecUlong :: Text -> Text -> Text -> CULong -> CULong -> CULong -> [ParamFlags] -> m GParamSpec paramSpecUlong name :: Text name nick :: Text nick blurb :: Text blurb minimum :: CULong minimum maximum :: CULong maximum defaultValue :: CULong defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CULong -> CULong -> CULong -> CUInt -> IO (Ptr GParamSpec) g_param_spec_ulong CString name' CString nick' CString blurb' CULong minimum CULong maximum CULong defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecUlong" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_uint64 -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TUInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TUInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TUInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_uint64" g_param_spec_uint64 :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Word64 -> -- minimum : TBasicType TUInt64 Word64 -> -- maximum : TBasicType TUInt64 Word64 -> -- default_value : TBasicType TUInt64 CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecUInt64.ParamSpecUInt64' instance specifying a @/G_TYPE_UINT64/@ -- property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecUint64 :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Word64 -- ^ /@minimum@/: minimum value for the property specified -> Word64 -- ^ /@maximum@/: maximum value for the property specified -> Word64 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecUint64 :: Text -> Text -> Text -> CGType -> CGType -> CGType -> [ParamFlags] -> m GParamSpec paramSpecUint64 name :: Text name nick :: Text nick blurb :: Text blurb minimum :: CGType minimum maximum :: CGType maximum defaultValue :: CGType defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> CGType -> CGType -> CUInt -> IO (Ptr GParamSpec) g_param_spec_uint64 CString name' CString nick' CString blurb' CGType minimum CGType maximum CGType defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecUint64" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_uint -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_uint" g_param_spec_uint :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Word32 -> -- minimum : TBasicType TUInt Word32 -> -- maximum : TBasicType TUInt Word32 -> -- default_value : TBasicType TUInt CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecUInt.ParamSpecUInt' instance specifying a @/G_TYPE_UINT/@ property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecUint :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Word32 -- ^ /@minimum@/: minimum value for the property specified -> Word32 -- ^ /@maximum@/: maximum value for the property specified -> Word32 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecUint :: Text -> Text -> Text -> Word32 -> Word32 -> Word32 -> [ParamFlags] -> m GParamSpec paramSpecUint name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Word32 minimum maximum :: Word32 maximum defaultValue :: Word32 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> Word32 -> Word32 -> Word32 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_uint CString name' CString nick' CString blurb' Word32 minimum Word32 maximum Word32 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecUint" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_uchar -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TUInt8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TUInt8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TUInt8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_uchar" g_param_spec_uchar :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Word8 -> -- minimum : TBasicType TUInt8 Word8 -> -- maximum : TBasicType TUInt8 Word8 -> -- default_value : TBasicType TUInt8 CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecUChar.ParamSpecUChar' instance specifying a @/G_TYPE_UCHAR/@ property. paramSpecUchar :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Word8 -- ^ /@minimum@/: minimum value for the property specified -> Word8 -- ^ /@maximum@/: maximum value for the property specified -> Word8 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecUchar :: Text -> Text -> Text -> Word8 -> Word8 -> Word8 -> [ParamFlags] -> m GParamSpec paramSpecUchar name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Word8 minimum maximum :: Word8 maximum defaultValue :: Word8 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> Word8 -> Word8 -> Word8 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_uchar CString name' CString nick' CString blurb' Word8 minimum Word8 maximum Word8 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecUchar" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_string -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_string" g_param_spec_string :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CString -> -- default_value : TBasicType TUTF8 CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecString.ParamSpecString' instance. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecString :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Maybe (T.Text) -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecString :: Text -> Text -> Text -> Maybe Text -> [ParamFlags] -> m GParamSpec paramSpecString name :: Text name nick :: Text nick blurb :: Text blurb defaultValue :: Maybe Text defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb CString maybeDefaultValue <- case Maybe Text defaultValue of Nothing -> CString -> IO CString forall (m :: * -> *) a. Monad m => a -> m a return CString forall a. Ptr a nullPtr Just jDefaultValue :: Text jDefaultValue -> do CString jDefaultValue' <- Text -> IO CString textToCString Text jDefaultValue CString -> IO CString forall (m :: * -> *) a. Monad m => a -> m a return CString jDefaultValue' let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CString -> CUInt -> IO (Ptr GParamSpec) g_param_spec_string CString name' CString nick' CString blurb' CString maybeDefaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecString" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' CString -> IO () forall a. Ptr a -> IO () freeMem CString maybeDefaultValue GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_pointer -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_pointer" g_param_spec_pointer :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecPointer.ParamSpecPointer' instance specifying a pointer property. -- Where possible, it is better to use 'GI.GObject.Functions.paramSpecObject' or -- 'GI.GObject.Functions.paramSpecBoxed' to expose memory management information. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecPointer :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecPointer :: Text -> Text -> Text -> [ParamFlags] -> m GParamSpec paramSpecPointer name :: Text name nick :: Text nick blurb :: Text blurb flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CUInt -> IO (Ptr GParamSpec) g_param_spec_pointer CString name' CString nick' CString blurb' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecPointer" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_param -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "param_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType derived from %G_TYPE_PARAM" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_param" g_param_spec_param :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CGType -> -- param_type : TBasicType TGType CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecParam.ParamSpecParam' instance specifying a @/G_TYPE_PARAM/@ -- property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecParam :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GType -- ^ /@paramType@/: a t'GType' derived from @/G_TYPE_PARAM/@ -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecParam :: Text -> Text -> Text -> GType -> [ParamFlags] -> m GParamSpec paramSpecParam name :: Text name nick :: Text nick blurb :: Text blurb paramType :: GType paramType flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let paramType' :: CGType paramType' = GType -> CGType gtypeToCGType GType paramType let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> CUInt -> IO (Ptr GParamSpec) g_param_spec_param CString name' CString nick' CString blurb' CGType paramType' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecParam" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_object -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "object_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "%G_TYPE_OBJECT derived type of this property" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_object" g_param_spec_object :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CGType -> -- object_type : TBasicType TGType CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecBoxed.ParamSpecBoxed' instance specifying a @/G_TYPE_OBJECT/@ -- derived property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecObject :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GType -- ^ /@objectType@/: @/G_TYPE_OBJECT/@ derived type of this property -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecObject :: Text -> Text -> Text -> GType -> [ParamFlags] -> m GParamSpec paramSpecObject name :: Text name nick :: Text nick blurb :: Text blurb objectType :: GType objectType flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let objectType' :: CGType objectType' = GType -> CGType gtypeToCGType GType objectType let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> CUInt -> IO (Ptr GParamSpec) g_param_spec_object CString name' CString nick' CString blurb' CGType objectType' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecObject" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_long -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TLong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TLong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TLong -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_long" g_param_spec_long :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CLong -> -- minimum : TBasicType TLong CLong -> -- maximum : TBasicType TLong CLong -> -- default_value : TBasicType TLong CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecLong.ParamSpecLong' instance specifying a @/G_TYPE_LONG/@ property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecLong :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> CLong -- ^ /@minimum@/: minimum value for the property specified -> CLong -- ^ /@maximum@/: maximum value for the property specified -> CLong -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecLong :: Text -> Text -> Text -> CLong -> CLong -> CLong -> [ParamFlags] -> m GParamSpec paramSpecLong name :: Text name nick :: Text nick blurb :: Text blurb minimum :: CLong minimum maximum :: CLong maximum defaultValue :: CLong defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CLong -> CLong -> CLong -> CUInt -> IO (Ptr GParamSpec) g_param_spec_long CString name' CString nick' CString blurb' CLong minimum CLong maximum CLong defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecLong" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_int64 -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TInt64 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_int64" g_param_spec_int64 :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Int64 -> -- minimum : TBasicType TInt64 Int64 -> -- maximum : TBasicType TInt64 Int64 -> -- default_value : TBasicType TInt64 CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecInt64.ParamSpecInt64' instance specifying a @/G_TYPE_INT64/@ property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecInt64 :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Int64 -- ^ /@minimum@/: minimum value for the property specified -> Int64 -- ^ /@maximum@/: maximum value for the property specified -> Int64 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecInt64 :: Text -> Text -> Text -> Int64 -> Int64 -> Int64 -> [ParamFlags] -> m GParamSpec paramSpecInt64 name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Int64 minimum maximum :: Int64 maximum defaultValue :: Int64 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> Int64 -> Int64 -> Int64 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_int64 CString name' CString nick' CString blurb' Int64 minimum Int64 maximum Int64 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecInt64" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_int -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_int" g_param_spec_int :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Int32 -> -- minimum : TBasicType TInt Int32 -> -- maximum : TBasicType TInt Int32 -> -- default_value : TBasicType TInt CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecInt.ParamSpecInt' instance specifying a @/G_TYPE_INT/@ property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecInt :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Int32 -- ^ /@minimum@/: minimum value for the property specified -> Int32 -- ^ /@maximum@/: maximum value for the property specified -> Int32 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecInt :: Text -> Text -> Text -> Int32 -> Int32 -> Int32 -> [ParamFlags] -> m GParamSpec paramSpecInt name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Int32 minimum maximum :: Int32 maximum defaultValue :: Int32 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> Int32 -> Int32 -> Int32 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_int CString name' CString nick' CString blurb' Int32 minimum Int32 maximum Int32 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecInt" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_gtype -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "is_a_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "a #GType whose subtypes are allowed as values\n of the property (use %G_TYPE_NONE for any type)" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_gtype" g_param_spec_gtype :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CGType -> -- is_a_type : TBasicType TGType CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecGType.ParamSpecGType' instance specifying a -- @/G_TYPE_GTYPE/@ property. -- -- See @/g_param_spec_internal()/@ for details on property names. -- -- /Since: 2.10/ paramSpecGtype :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GType -- ^ /@isAType@/: a t'GType' whose subtypes are allowed as values -- of the property (use @/G_TYPE_NONE/@ for any type) -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecGtype :: Text -> Text -> Text -> GType -> [ParamFlags] -> m GParamSpec paramSpecGtype name :: Text name nick :: Text nick blurb :: Text blurb isAType :: GType isAType flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let isAType' :: CGType isAType' = GType -> CGType gtypeToCGType GType isAType let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> CUInt -> IO (Ptr GParamSpec) g_param_spec_gtype CString name' CString nick' CString blurb' CGType isAType' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecGtype" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_float -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TFloat -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TFloat -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TFloat -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_float" g_param_spec_float :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CFloat -> -- minimum : TBasicType TFloat CFloat -> -- maximum : TBasicType TFloat CFloat -> -- default_value : TBasicType TFloat CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecFloat.ParamSpecFloat' instance specifying a @/G_TYPE_FLOAT/@ property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecFloat :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Float -- ^ /@minimum@/: minimum value for the property specified -> Float -- ^ /@maximum@/: maximum value for the property specified -> Float -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecFloat :: Text -> Text -> Text -> Float -> Float -> Float -> [ParamFlags] -> m GParamSpec paramSpecFloat name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Float minimum maximum :: Float maximum defaultValue :: Float defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let minimum' :: CFloat minimum' = Float -> CFloat forall a b. (Real a, Fractional b) => a -> b realToFrac Float minimum let maximum' :: CFloat maximum' = Float -> CFloat forall a b. (Real a, Fractional b) => a -> b realToFrac Float maximum let defaultValue' :: CFloat defaultValue' = Float -> CFloat forall a b. (Real a, Fractional b) => a -> b realToFrac Float defaultValue let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CFloat -> CFloat -> CFloat -> CUInt -> IO (Ptr GParamSpec) g_param_spec_float CString name' CString nick' CString blurb' CFloat minimum' CFloat maximum' CFloat defaultValue' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecFloat" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_flags -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType derived from %G_TYPE_FLAGS" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_flags" g_param_spec_flags :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CGType -> -- flags_type : TBasicType TGType Word32 -> -- default_value : TBasicType TUInt CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecFlags.ParamSpecFlags' instance specifying a @/G_TYPE_FLAGS/@ -- property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecFlags :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GType -- ^ /@flagsType@/: a t'GType' derived from @/G_TYPE_FLAGS/@ -> Word32 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecFlags :: Text -> Text -> Text -> GType -> Word32 -> [ParamFlags] -> m GParamSpec paramSpecFlags name :: Text name nick :: Text nick blurb :: Text blurb flagsType :: GType flagsType defaultValue :: Word32 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flagsType' :: CGType flagsType' = GType -> CGType gtypeToCGType GType flagsType let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> Word32 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_flags CString name' CString nick' CString blurb' CGType flagsType' Word32 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecFlags" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_enum -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "enum_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GType derived from %G_TYPE_ENUM" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_enum" g_param_spec_enum :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CGType -> -- enum_type : TBasicType TGType Int32 -> -- default_value : TBasicType TInt CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecEnum.ParamSpecEnum' instance specifying a @/G_TYPE_ENUM/@ -- property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecEnum :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GType -- ^ /@enumType@/: a t'GType' derived from @/G_TYPE_ENUM/@ -> Int32 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecEnum :: Text -> Text -> Text -> GType -> Int32 -> [ParamFlags] -> m GParamSpec paramSpecEnum name :: Text name nick :: Text nick blurb :: Text blurb enumType :: GType enumType defaultValue :: Int32 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let enumType' :: CGType enumType' = GType -> CGType gtypeToCGType GType enumType let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> Int32 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_enum CString name' CString nick' CString blurb' CGType enumType' Int32 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecEnum" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_double -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TDouble -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TDouble -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TDouble -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_double" g_param_spec_double :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CDouble -> -- minimum : TBasicType TDouble CDouble -> -- maximum : TBasicType TDouble CDouble -> -- default_value : TBasicType TDouble CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecDouble.ParamSpecDouble' instance specifying a @/G_TYPE_DOUBLE/@ -- property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecDouble :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Double -- ^ /@minimum@/: minimum value for the property specified -> Double -- ^ /@maximum@/: maximum value for the property specified -> Double -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecDouble :: Text -> Text -> Text -> Double -> Double -> Double -> [ParamFlags] -> m GParamSpec paramSpecDouble name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Double minimum maximum :: Double maximum defaultValue :: Double defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let minimum' :: CDouble minimum' = Double -> CDouble forall a b. (Real a, Fractional b) => a -> b realToFrac Double minimum let maximum' :: CDouble maximum' = Double -> CDouble forall a b. (Real a, Fractional b) => a -> b realToFrac Double maximum let defaultValue' :: CDouble defaultValue' = Double -> CDouble forall a b. (Real a, Fractional b) => a -> b realToFrac Double defaultValue let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> CUInt -> IO (Ptr GParamSpec) g_param_spec_double CString name' CString nick' CString blurb' CDouble minimum' CDouble maximum' CDouble defaultValue' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecDouble" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_char -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "minimum" -- , argType = TBasicType TInt8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "minimum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "maximum" -- , argType = TBasicType TInt8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "maximum value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TInt8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_char" g_param_spec_char :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 Int8 -> -- minimum : TBasicType TInt8 Int8 -> -- maximum : TBasicType TInt8 Int8 -> -- default_value : TBasicType TInt8 CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecChar.ParamSpecChar' instance specifying a @/G_TYPE_CHAR/@ property. paramSpecChar :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Int8 -- ^ /@minimum@/: minimum value for the property specified -> Int8 -- ^ /@maximum@/: maximum value for the property specified -> Int8 -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecChar :: Text -> Text -> Text -> Int8 -> Int8 -> Int8 -> [ParamFlags] -> m GParamSpec paramSpecChar name :: Text name nick :: Text nick blurb :: Text blurb minimum :: Int8 minimum maximum :: Int8 maximum defaultValue :: Int8 defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> Int8 -> Int8 -> Int8 -> CUInt -> IO (Ptr GParamSpec) g_param_spec_char CString name' CString nick' CString blurb' Int8 minimum Int8 maximum Int8 defaultValue CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecChar" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_boxed -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "boxed_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "%G_TYPE_BOXED derived type of this property" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_boxed" g_param_spec_boxed :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CGType -> -- boxed_type : TBasicType TGType CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecBoxed.ParamSpecBoxed' instance specifying a @/G_TYPE_BOXED/@ -- derived property. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecBoxed :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> GType -- ^ /@boxedType@/: @/G_TYPE_BOXED/@ derived type of this property -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecBoxed :: Text -> Text -> Text -> GType -> [ParamFlags] -> m GParamSpec paramSpecBoxed name :: Text name nick :: Text nick blurb :: Text blurb boxedType :: GType boxedType flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let boxedType' :: CGType boxedType' = GType -> CGType gtypeToCGType GType boxedType let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CGType -> CUInt -> IO (Ptr GParamSpec) g_param_spec_boxed CString name' CString nick' CString blurb' CGType boxedType' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecBoxed" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_param_spec_boolean -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "canonical name of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "nick name for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "blurb" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "description of the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "default_value" -- , argType = TBasicType TBoolean -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "default value for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "flags" -- , argType = -- TInterface Name { namespace = "GObject" , name = "ParamFlags" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "flags for the property specified" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just TParamSpec -- throws : False -- Skip return : False foreign import ccall "g_param_spec_boolean" g_param_spec_boolean :: CString -> -- name : TBasicType TUTF8 CString -> -- nick : TBasicType TUTF8 CString -> -- blurb : TBasicType TUTF8 CInt -> -- default_value : TBasicType TBoolean CUInt -> -- flags : TInterface (Name {namespace = "GObject", name = "ParamFlags"}) IO (Ptr GParamSpec) -- | Creates a new t'GI.GObject.Objects.ParamSpecBoolean.ParamSpecBoolean' instance specifying a @/G_TYPE_BOOLEAN/@ -- property. In many cases, it may be more appropriate to use an enum with -- 'GI.GObject.Functions.paramSpecEnum', both to improve code clarity by using explicitly named -- values, and to allow for more values to be added in future without breaking -- API. -- -- See @/g_param_spec_internal()/@ for details on property names. paramSpecBoolean :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: canonical name of the property specified -> T.Text -- ^ /@nick@/: nick name for the property specified -> T.Text -- ^ /@blurb@/: description of the property specified -> Bool -- ^ /@defaultValue@/: default value for the property specified -> [GObject.Flags.ParamFlags] -- ^ /@flags@/: flags for the property specified -> m GParamSpec -- ^ __Returns:__ a newly created parameter specification paramSpecBoolean :: Text -> Text -> Text -> Bool -> [ParamFlags] -> m GParamSpec paramSpecBoolean name :: Text name nick :: Text nick blurb :: Text blurb defaultValue :: Bool defaultValue flags :: [ParamFlags] flags = IO GParamSpec -> m GParamSpec forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name CString nick' <- Text -> IO CString textToCString Text nick CString blurb' <- Text -> IO CString textToCString Text blurb let defaultValue' :: CInt defaultValue' = (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt forall b c a. (b -> c) -> (a -> b) -> a -> c . Bool -> Int forall a. Enum a => a -> Int fromEnum) Bool defaultValue let flags' :: CUInt flags' = [ParamFlags] -> CUInt forall b a. (Num b, IsGFlag a) => [a] -> b gflagsToWord [ParamFlags] flags Ptr GParamSpec result <- CString -> CString -> CString -> CInt -> CUInt -> IO (Ptr GParamSpec) g_param_spec_boolean CString name' CString nick' CString blurb' CInt defaultValue' CUInt flags' Text -> Ptr GParamSpec -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "paramSpecBoolean" Ptr GParamSpec result GParamSpec result' <- Ptr GParamSpec -> IO GParamSpec B.GParamSpec.wrapGParamSpecPtr Ptr GParamSpec result CString -> IO () forall a. Ptr a -> IO () freeMem CString name' CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' CString -> IO () forall a. Ptr a -> IO () freeMem CString blurb' GParamSpec -> IO GParamSpec forall (m :: * -> *) a. Monad m => a -> m a return GParamSpec result' -- function g_gtype_get_type -- Args: [] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_gtype_get_type" g_gtype_get_type :: IO CGType -- | /No description available in the introspection data./ gtypeGetType :: (B.CallStack.HasCallStack, MonadIO m) => m GType gtypeGetType :: m GType gtypeGetType = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CGType result <- IO CGType g_gtype_get_type let result' :: GType result' = CGType -> GType GType CGType result GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_flags_to_string -- Args: [ Arg -- { argCName = "flags_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the type identifier of a #GFlagsClass type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the value" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_flags_to_string" g_flags_to_string :: CGType -> -- flags_type : TBasicType TGType Word32 -> -- value : TBasicType TUInt IO CString -- | Pretty-prints /@value@/ in the form of the flag names separated by @ | @ and -- sorted. Any extra bits will be shown at the end as a hexadecimal number. -- -- This is intended to be used for debugging purposes. The format of the output -- may change in the future. -- -- /Since: 2.54/ flagsToString :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@flagsType@/: the type identifier of a t'GI.GObject.Structs.FlagsClass.FlagsClass' type -> Word32 -- ^ /@value@/: the value -> m T.Text -- ^ __Returns:__ a newly-allocated text string flagsToString :: GType -> Word32 -> m Text flagsToString flagsType :: GType flagsType value :: Word32 value = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do let flagsType' :: CGType flagsType' = GType -> CGType gtypeToCGType GType flagsType CString result <- CGType -> Word32 -> IO CString g_flags_to_string CGType flagsType' Word32 value Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "flagsToString" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result CString -> IO () forall a. Ptr a -> IO () freeMem CString result Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_flags_register_static -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "A nul-terminated string used as the name of the new type." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "const_static_values" -- , argType = -- TInterface Name { namespace = "GObject" , name = "FlagsValue" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "An array of #GFlagsValue structs for the possible\n flags values. The array is terminated by a struct with all members being 0.\n GObject keeps a reference to the data, so it cannot be stack-allocated." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_flags_register_static" g_flags_register_static :: CString -> -- name : TBasicType TUTF8 Ptr GObject.FlagsValue.FlagsValue -> -- const_static_values : TInterface (Name {namespace = "GObject", name = "FlagsValue"}) IO CGType -- | Registers a new static flags type with the name /@name@/. -- -- It is normally more convenient to let [glib-mkenums][glib-mkenums] -- generate a @/my_flags_get_type()/@ function from a usual C enumeration -- definition than to write one yourself using 'GI.GObject.Functions.flagsRegisterStatic'. flagsRegisterStatic :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: A nul-terminated string used as the name of the new type. -> GObject.FlagsValue.FlagsValue -- ^ /@constStaticValues@/: An array of t'GI.GObject.Structs.FlagsValue.FlagsValue' structs for the possible -- flags values. The array is terminated by a struct with all members being 0. -- GObject keeps a reference to the data, so it cannot be stack-allocated. -> m GType -- ^ __Returns:__ The new type identifier. flagsRegisterStatic :: Text -> FlagsValue -> m GType flagsRegisterStatic name :: Text name constStaticValues :: FlagsValue constStaticValues = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name Ptr FlagsValue constStaticValues' <- FlagsValue -> IO (Ptr FlagsValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr FlagsValue constStaticValues CGType result <- CString -> Ptr FlagsValue -> IO CGType g_flags_register_static CString name' Ptr FlagsValue constStaticValues' let result' :: GType result' = CGType -> GType GType CGType result FlagsValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr FlagsValue constStaticValues CString -> IO () forall a. Ptr a -> IO () freeMem CString name' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_flags_get_value_by_nick -- Args: [ Arg -- { argCName = "flags_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "FlagsClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GFlagsClass" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the nickname to look up" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "FlagsValue" }) -- throws : False -- Skip return : False foreign import ccall "g_flags_get_value_by_nick" g_flags_get_value_by_nick :: Ptr GObject.FlagsClass.FlagsClass -> -- flags_class : TInterface (Name {namespace = "GObject", name = "FlagsClass"}) CString -> -- nick : TBasicType TUTF8 IO (Ptr GObject.FlagsValue.FlagsValue) -- | Looks up a t'GI.GObject.Structs.FlagsValue.FlagsValue' by nickname. flagsGetValueByNick :: (B.CallStack.HasCallStack, MonadIO m) => GObject.FlagsClass.FlagsClass -- ^ /@flagsClass@/: a t'GI.GObject.Structs.FlagsClass.FlagsClass' -> T.Text -- ^ /@nick@/: the nickname to look up -> m GObject.FlagsValue.FlagsValue -- ^ __Returns:__ the t'GI.GObject.Structs.FlagsValue.FlagsValue' with nickname /@nick@/, -- or 'P.Nothing' if there is no flag with that nickname flagsGetValueByNick :: FlagsClass -> Text -> m FlagsValue flagsGetValueByNick flagsClass :: FlagsClass flagsClass nick :: Text nick = IO FlagsValue -> m FlagsValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO FlagsValue -> m FlagsValue) -> IO FlagsValue -> m FlagsValue forall a b. (a -> b) -> a -> b $ do Ptr FlagsClass flagsClass' <- FlagsClass -> IO (Ptr FlagsClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr FlagsClass flagsClass CString nick' <- Text -> IO CString textToCString Text nick Ptr FlagsValue result <- Ptr FlagsClass -> CString -> IO (Ptr FlagsValue) g_flags_get_value_by_nick Ptr FlagsClass flagsClass' CString nick' Text -> Ptr FlagsValue -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "flagsGetValueByNick" Ptr FlagsValue result FlagsValue result' <- ((ManagedPtr FlagsValue -> FlagsValue) -> Ptr FlagsValue -> IO FlagsValue forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr FlagsValue -> FlagsValue GObject.FlagsValue.FlagsValue) Ptr FlagsValue result FlagsClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr FlagsClass flagsClass CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' FlagsValue -> IO FlagsValue forall (m :: * -> *) a. Monad m => a -> m a return FlagsValue result' -- function g_flags_get_value_by_name -- Args: [ Arg -- { argCName = "flags_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "FlagsClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GFlagsClass" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the name to look up" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "FlagsValue" }) -- throws : False -- Skip return : False foreign import ccall "g_flags_get_value_by_name" g_flags_get_value_by_name :: Ptr GObject.FlagsClass.FlagsClass -> -- flags_class : TInterface (Name {namespace = "GObject", name = "FlagsClass"}) CString -> -- name : TBasicType TUTF8 IO (Ptr GObject.FlagsValue.FlagsValue) -- | Looks up a t'GI.GObject.Structs.FlagsValue.FlagsValue' by name. flagsGetValueByName :: (B.CallStack.HasCallStack, MonadIO m) => GObject.FlagsClass.FlagsClass -- ^ /@flagsClass@/: a t'GI.GObject.Structs.FlagsClass.FlagsClass' -> T.Text -- ^ /@name@/: the name to look up -> m GObject.FlagsValue.FlagsValue -- ^ __Returns:__ the t'GI.GObject.Structs.FlagsValue.FlagsValue' with name /@name@/, -- or 'P.Nothing' if there is no flag with that name flagsGetValueByName :: FlagsClass -> Text -> m FlagsValue flagsGetValueByName flagsClass :: FlagsClass flagsClass name :: Text name = IO FlagsValue -> m FlagsValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO FlagsValue -> m FlagsValue) -> IO FlagsValue -> m FlagsValue forall a b. (a -> b) -> a -> b $ do Ptr FlagsClass flagsClass' <- FlagsClass -> IO (Ptr FlagsClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr FlagsClass flagsClass CString name' <- Text -> IO CString textToCString Text name Ptr FlagsValue result <- Ptr FlagsClass -> CString -> IO (Ptr FlagsValue) g_flags_get_value_by_name Ptr FlagsClass flagsClass' CString name' Text -> Ptr FlagsValue -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "flagsGetValueByName" Ptr FlagsValue result FlagsValue result' <- ((ManagedPtr FlagsValue -> FlagsValue) -> Ptr FlagsValue -> IO FlagsValue forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr FlagsValue -> FlagsValue GObject.FlagsValue.FlagsValue) Ptr FlagsValue result FlagsClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr FlagsClass flagsClass CString -> IO () forall a. Ptr a -> IO () freeMem CString name' FlagsValue -> IO FlagsValue forall (m :: * -> *) a. Monad m => a -> m a return FlagsValue result' -- function g_flags_get_first_value -- Args: [ Arg -- { argCName = "flags_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "FlagsClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GFlagsClass" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = TBasicType TUInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the value" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "FlagsValue" }) -- throws : False -- Skip return : False foreign import ccall "g_flags_get_first_value" g_flags_get_first_value :: Ptr GObject.FlagsClass.FlagsClass -> -- flags_class : TInterface (Name {namespace = "GObject", name = "FlagsClass"}) Word32 -> -- value : TBasicType TUInt IO (Ptr GObject.FlagsValue.FlagsValue) -- | Returns the first t'GI.GObject.Structs.FlagsValue.FlagsValue' which is set in /@value@/. flagsGetFirstValue :: (B.CallStack.HasCallStack, MonadIO m) => GObject.FlagsClass.FlagsClass -- ^ /@flagsClass@/: a t'GI.GObject.Structs.FlagsClass.FlagsClass' -> Word32 -- ^ /@value@/: the value -> m GObject.FlagsValue.FlagsValue -- ^ __Returns:__ the first t'GI.GObject.Structs.FlagsValue.FlagsValue' which is set in -- /@value@/, or 'P.Nothing' if none is set flagsGetFirstValue :: FlagsClass -> Word32 -> m FlagsValue flagsGetFirstValue flagsClass :: FlagsClass flagsClass value :: Word32 value = IO FlagsValue -> m FlagsValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO FlagsValue -> m FlagsValue) -> IO FlagsValue -> m FlagsValue forall a b. (a -> b) -> a -> b $ do Ptr FlagsClass flagsClass' <- FlagsClass -> IO (Ptr FlagsClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr FlagsClass flagsClass Ptr FlagsValue result <- Ptr FlagsClass -> Word32 -> IO (Ptr FlagsValue) g_flags_get_first_value Ptr FlagsClass flagsClass' Word32 value Text -> Ptr FlagsValue -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "flagsGetFirstValue" Ptr FlagsValue result FlagsValue result' <- ((ManagedPtr FlagsValue -> FlagsValue) -> Ptr FlagsValue -> IO FlagsValue forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr FlagsValue -> FlagsValue GObject.FlagsValue.FlagsValue) Ptr FlagsValue result FlagsClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr FlagsClass flagsClass FlagsValue -> IO FlagsValue forall (m :: * -> *) a. Monad m => a -> m a return FlagsValue result' -- function g_flags_complete_type_info -- Args: [ Arg -- { argCName = "g_flags_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the type identifier of the type being completed" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "info" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInfo" } -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the #GTypeInfo struct to be filled in" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- , Arg -- { argCName = "const_values" -- , argType = -- TInterface Name { namespace = "GObject" , name = "FlagsValue" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "An array of #GFlagsValue structs for the possible\n enumeration values. The array is terminated by a struct with all\n members being 0." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_flags_complete_type_info" g_flags_complete_type_info :: CGType -> -- g_flags_type : TBasicType TGType Ptr (Ptr GObject.TypeInfo.TypeInfo) -> -- info : TInterface (Name {namespace = "GObject", name = "TypeInfo"}) Ptr GObject.FlagsValue.FlagsValue -> -- const_values : TInterface (Name {namespace = "GObject", name = "FlagsValue"}) IO () -- | This function is meant to be called from the @/complete_type_info()/@ -- function of a t'GI.GObject.Interfaces.TypePlugin.TypePlugin' implementation, see the example for -- 'GI.GObject.Functions.enumCompleteTypeInfo' above. flagsCompleteTypeInfo :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@gFlagsType@/: the type identifier of the type being completed -> GObject.FlagsValue.FlagsValue -- ^ /@constValues@/: An array of t'GI.GObject.Structs.FlagsValue.FlagsValue' structs for the possible -- enumeration values. The array is terminated by a struct with all -- members being 0. -> m (GObject.TypeInfo.TypeInfo) flagsCompleteTypeInfo :: GType -> FlagsValue -> m TypeInfo flagsCompleteTypeInfo gFlagsType :: GType gFlagsType constValues :: FlagsValue constValues = IO TypeInfo -> m TypeInfo forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO TypeInfo -> m TypeInfo) -> IO TypeInfo -> m TypeInfo forall a b. (a -> b) -> a -> b $ do let gFlagsType' :: CGType gFlagsType' = GType -> CGType gtypeToCGType GType gFlagsType Ptr (Ptr TypeInfo) info <- IO (Ptr (Ptr TypeInfo)) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr (Ptr GObject.TypeInfo.TypeInfo)) Ptr FlagsValue constValues' <- FlagsValue -> IO (Ptr FlagsValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr FlagsValue constValues CGType -> Ptr (Ptr TypeInfo) -> Ptr FlagsValue -> IO () g_flags_complete_type_info CGType gFlagsType' Ptr (Ptr TypeInfo) info Ptr FlagsValue constValues' Ptr TypeInfo info' <- Ptr (Ptr TypeInfo) -> IO (Ptr TypeInfo) forall a. Storable a => Ptr a -> IO a peek Ptr (Ptr TypeInfo) info TypeInfo info'' <- ((ManagedPtr TypeInfo -> TypeInfo) -> Ptr TypeInfo -> IO TypeInfo forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a wrapPtr ManagedPtr TypeInfo -> TypeInfo GObject.TypeInfo.TypeInfo) Ptr TypeInfo info' FlagsValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr FlagsValue constValues Ptr (Ptr TypeInfo) -> IO () forall a. Ptr a -> IO () freeMem Ptr (Ptr TypeInfo) info TypeInfo -> IO TypeInfo forall (m :: * -> *) a. Monad m => a -> m a return TypeInfo info'' -- function g_enum_to_string -- Args: [ Arg -- { argCName = "g_enum_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the type identifier of a #GEnumClass type" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the value" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "g_enum_to_string" g_enum_to_string :: CGType -> -- g_enum_type : TBasicType TGType Int32 -> -- value : TBasicType TInt IO CString -- | Pretty-prints /@value@/ in the form of the enum’s name. -- -- This is intended to be used for debugging purposes. The format of the output -- may change in the future. -- -- /Since: 2.54/ enumToString :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@gEnumType@/: the type identifier of a t'GI.GObject.Structs.EnumClass.EnumClass' type -> Int32 -- ^ /@value@/: the value -> m T.Text -- ^ __Returns:__ a newly-allocated text string enumToString :: GType -> Int32 -> m Text enumToString gEnumType :: GType gEnumType value :: Int32 value = IO Text -> m Text forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Text -> m Text) -> IO Text -> m Text forall a b. (a -> b) -> a -> b $ do let gEnumType' :: CGType gEnumType' = GType -> CGType gtypeToCGType GType gEnumType CString result <- CGType -> Int32 -> IO CString g_enum_to_string CGType gEnumType' Int32 value Text -> CString -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "enumToString" CString result Text result' <- HasCallStack => CString -> IO Text CString -> IO Text cstringToText CString result CString -> IO () forall a. Ptr a -> IO () freeMem CString result Text -> IO Text forall (m :: * -> *) a. Monad m => a -> m a return Text result' -- function g_enum_register_static -- Args: [ Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "A nul-terminated string used as the name of the new type." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "const_static_values" -- , argType = -- TInterface Name { namespace = "GObject" , name = "EnumValue" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "An array of #GEnumValue structs for the possible\n enumeration values. The array is terminated by a struct with all\n members being 0. GObject keeps a reference to the data, so it cannot\n be stack-allocated." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "g_enum_register_static" g_enum_register_static :: CString -> -- name : TBasicType TUTF8 Ptr GObject.EnumValue.EnumValue -> -- const_static_values : TInterface (Name {namespace = "GObject", name = "EnumValue"}) IO CGType -- | Registers a new static enumeration type with the name /@name@/. -- -- It is normally more convenient to let [glib-mkenums][glib-mkenums], -- generate a @/my_enum_get_type()/@ function from a usual C enumeration -- definition than to write one yourself using 'GI.GObject.Functions.enumRegisterStatic'. enumRegisterStatic :: (B.CallStack.HasCallStack, MonadIO m) => T.Text -- ^ /@name@/: A nul-terminated string used as the name of the new type. -> GObject.EnumValue.EnumValue -- ^ /@constStaticValues@/: An array of t'GI.GObject.Structs.EnumValue.EnumValue' structs for the possible -- enumeration values. The array is terminated by a struct with all -- members being 0. GObject keeps a reference to the data, so it cannot -- be stack-allocated. -> m GType -- ^ __Returns:__ The new type identifier. enumRegisterStatic :: Text -> EnumValue -> m GType enumRegisterStatic name :: Text name constStaticValues :: EnumValue constStaticValues = IO GType -> m GType forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do CString name' <- Text -> IO CString textToCString Text name Ptr EnumValue constStaticValues' <- EnumValue -> IO (Ptr EnumValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr EnumValue constStaticValues CGType result <- CString -> Ptr EnumValue -> IO CGType g_enum_register_static CString name' Ptr EnumValue constStaticValues' let result' :: GType result' = CGType -> GType GType CGType result EnumValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr EnumValue constStaticValues CString -> IO () forall a. Ptr a -> IO () freeMem CString name' GType -> IO GType forall (m :: * -> *) a. Monad m => a -> m a return GType result' -- function g_enum_get_value_by_nick -- Args: [ Arg -- { argCName = "enum_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "EnumClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GEnumClass" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "nick" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the nickname to look up" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "EnumValue" }) -- throws : False -- Skip return : False foreign import ccall "g_enum_get_value_by_nick" g_enum_get_value_by_nick :: Ptr GObject.EnumClass.EnumClass -> -- enum_class : TInterface (Name {namespace = "GObject", name = "EnumClass"}) CString -> -- nick : TBasicType TUTF8 IO (Ptr GObject.EnumValue.EnumValue) -- | Looks up a t'GI.GObject.Structs.EnumValue.EnumValue' by nickname. enumGetValueByNick :: (B.CallStack.HasCallStack, MonadIO m) => GObject.EnumClass.EnumClass -- ^ /@enumClass@/: a t'GI.GObject.Structs.EnumClass.EnumClass' -> T.Text -- ^ /@nick@/: the nickname to look up -> m GObject.EnumValue.EnumValue -- ^ __Returns:__ the t'GI.GObject.Structs.EnumValue.EnumValue' with nickname /@nick@/, -- or 'P.Nothing' if the enumeration doesn\'t have a member -- with that nickname enumGetValueByNick :: EnumClass -> Text -> m EnumValue enumGetValueByNick enumClass :: EnumClass enumClass nick :: Text nick = IO EnumValue -> m EnumValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO EnumValue -> m EnumValue) -> IO EnumValue -> m EnumValue forall a b. (a -> b) -> a -> b $ do Ptr EnumClass enumClass' <- EnumClass -> IO (Ptr EnumClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr EnumClass enumClass CString nick' <- Text -> IO CString textToCString Text nick Ptr EnumValue result <- Ptr EnumClass -> CString -> IO (Ptr EnumValue) g_enum_get_value_by_nick Ptr EnumClass enumClass' CString nick' Text -> Ptr EnumValue -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "enumGetValueByNick" Ptr EnumValue result EnumValue result' <- ((ManagedPtr EnumValue -> EnumValue) -> Ptr EnumValue -> IO EnumValue forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr EnumValue -> EnumValue GObject.EnumValue.EnumValue) Ptr EnumValue result EnumClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr EnumClass enumClass CString -> IO () forall a. Ptr a -> IO () freeMem CString nick' EnumValue -> IO EnumValue forall (m :: * -> *) a. Monad m => a -> m a return EnumValue result' -- function g_enum_get_value_by_name -- Args: [ Arg -- { argCName = "enum_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "EnumClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GEnumClass" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "name" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the name to look up" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "EnumValue" }) -- throws : False -- Skip return : False foreign import ccall "g_enum_get_value_by_name" g_enum_get_value_by_name :: Ptr GObject.EnumClass.EnumClass -> -- enum_class : TInterface (Name {namespace = "GObject", name = "EnumClass"}) CString -> -- name : TBasicType TUTF8 IO (Ptr GObject.EnumValue.EnumValue) -- | Looks up a t'GI.GObject.Structs.EnumValue.EnumValue' by name. enumGetValueByName :: (B.CallStack.HasCallStack, MonadIO m) => GObject.EnumClass.EnumClass -- ^ /@enumClass@/: a t'GI.GObject.Structs.EnumClass.EnumClass' -> T.Text -- ^ /@name@/: the name to look up -> m GObject.EnumValue.EnumValue -- ^ __Returns:__ the t'GI.GObject.Structs.EnumValue.EnumValue' with name /@name@/, -- or 'P.Nothing' if the enumeration doesn\'t have a member -- with that name enumGetValueByName :: EnumClass -> Text -> m EnumValue enumGetValueByName enumClass :: EnumClass enumClass name :: Text name = IO EnumValue -> m EnumValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO EnumValue -> m EnumValue) -> IO EnumValue -> m EnumValue forall a b. (a -> b) -> a -> b $ do Ptr EnumClass enumClass' <- EnumClass -> IO (Ptr EnumClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr EnumClass enumClass CString name' <- Text -> IO CString textToCString Text name Ptr EnumValue result <- Ptr EnumClass -> CString -> IO (Ptr EnumValue) g_enum_get_value_by_name Ptr EnumClass enumClass' CString name' Text -> Ptr EnumValue -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "enumGetValueByName" Ptr EnumValue result EnumValue result' <- ((ManagedPtr EnumValue -> EnumValue) -> Ptr EnumValue -> IO EnumValue forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr EnumValue -> EnumValue GObject.EnumValue.EnumValue) Ptr EnumValue result EnumClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr EnumClass enumClass CString -> IO () forall a. Ptr a -> IO () freeMem CString name' EnumValue -> IO EnumValue forall (m :: * -> *) a. Monad m => a -> m a return EnumValue result' -- function g_enum_get_value -- Args: [ Arg -- { argCName = "enum_class" -- , argType = -- TInterface Name { namespace = "GObject" , name = "EnumClass" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a #GEnumClass" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the value to look up" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "GObject" , name = "EnumValue" }) -- throws : False -- Skip return : False foreign import ccall "g_enum_get_value" g_enum_get_value :: Ptr GObject.EnumClass.EnumClass -> -- enum_class : TInterface (Name {namespace = "GObject", name = "EnumClass"}) Int32 -> -- value : TBasicType TInt IO (Ptr GObject.EnumValue.EnumValue) -- | Returns the t'GI.GObject.Structs.EnumValue.EnumValue' for a value. enumGetValue :: (B.CallStack.HasCallStack, MonadIO m) => GObject.EnumClass.EnumClass -- ^ /@enumClass@/: a t'GI.GObject.Structs.EnumClass.EnumClass' -> Int32 -- ^ /@value@/: the value to look up -> m GObject.EnumValue.EnumValue -- ^ __Returns:__ the t'GI.GObject.Structs.EnumValue.EnumValue' for /@value@/, or 'P.Nothing' -- if /@value@/ is not a member of the enumeration enumGetValue :: EnumClass -> Int32 -> m EnumValue enumGetValue enumClass :: EnumClass enumClass value :: Int32 value = IO EnumValue -> m EnumValue forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO EnumValue -> m EnumValue) -> IO EnumValue -> m EnumValue forall a b. (a -> b) -> a -> b $ do Ptr EnumClass enumClass' <- EnumClass -> IO (Ptr EnumClass) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr EnumClass enumClass Ptr EnumValue result <- Ptr EnumClass -> Int32 -> IO (Ptr EnumValue) g_enum_get_value Ptr EnumClass enumClass' Int32 value Text -> Ptr EnumValue -> IO () forall a. HasCallStack => Text -> Ptr a -> IO () checkUnexpectedReturnNULL "enumGetValue" Ptr EnumValue result EnumValue result' <- ((ManagedPtr EnumValue -> EnumValue) -> Ptr EnumValue -> IO EnumValue forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a newPtr ManagedPtr EnumValue -> EnumValue GObject.EnumValue.EnumValue) Ptr EnumValue result EnumClass -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr EnumClass enumClass EnumValue -> IO EnumValue forall (m :: * -> *) a. Monad m => a -> m a return EnumValue result' -- function g_enum_complete_type_info -- Args: [ Arg -- { argCName = "g_enum_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "the type identifier of the type being completed" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "info" -- , argType = -- TInterface Name { namespace = "GObject" , name = "TypeInfo" } -- , direction = DirectionOut -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the #GTypeInfo struct to be filled in" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferEverything -- } -- , Arg -- { argCName = "const_values" -- , argType = -- TInterface Name { namespace = "GObject" , name = "EnumValue" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "An array of #GEnumValue structs for the possible\n enumeration values. The array is terminated by a struct with all\n members being 0." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_enum_complete_type_info" g_enum_complete_type_info :: CGType -> -- g_enum_type : TBasicType TGType Ptr (Ptr GObject.TypeInfo.TypeInfo) -> -- info : TInterface (Name {namespace = "GObject", name = "TypeInfo"}) Ptr GObject.EnumValue.EnumValue -> -- const_values : TInterface (Name {namespace = "GObject", name = "EnumValue"}) IO () -- | This function is meant to be called from the @complete_type_info@ -- function of a t'GI.GObject.Interfaces.TypePlugin.TypePlugin' implementation, as in the following -- example: -- -- -- === /C code/ -- > -- >static void -- >my_enum_complete_type_info (GTypePlugin *plugin, -- > GType g_type, -- > GTypeInfo *info, -- > GTypeValueTable *value_table) -- >{ -- > static const GEnumValue values[] = { -- > { MY_ENUM_FOO, "MY_ENUM_FOO", "foo" }, -- > { MY_ENUM_BAR, "MY_ENUM_BAR", "bar" }, -- > { 0, NULL, NULL } -- > }; -- > -- > g_enum_complete_type_info (type, info, values); -- >} enumCompleteTypeInfo :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@gEnumType@/: the type identifier of the type being completed -> GObject.EnumValue.EnumValue -- ^ /@constValues@/: An array of t'GI.GObject.Structs.EnumValue.EnumValue' structs for the possible -- enumeration values. The array is terminated by a struct with all -- members being 0. -> m (GObject.TypeInfo.TypeInfo) enumCompleteTypeInfo :: GType -> EnumValue -> m TypeInfo enumCompleteTypeInfo gEnumType :: GType gEnumType constValues :: EnumValue constValues = IO TypeInfo -> m TypeInfo forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO TypeInfo -> m TypeInfo) -> IO TypeInfo -> m TypeInfo forall a b. (a -> b) -> a -> b $ do let gEnumType' :: CGType gEnumType' = GType -> CGType gtypeToCGType GType gEnumType Ptr (Ptr TypeInfo) info <- IO (Ptr (Ptr TypeInfo)) forall a. Storable a => IO (Ptr a) allocMem :: IO (Ptr (Ptr GObject.TypeInfo.TypeInfo)) Ptr EnumValue constValues' <- EnumValue -> IO (Ptr EnumValue) forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a) unsafeManagedPtrGetPtr EnumValue constValues CGType -> Ptr (Ptr TypeInfo) -> Ptr EnumValue -> IO () g_enum_complete_type_info CGType gEnumType' Ptr (Ptr TypeInfo) info Ptr EnumValue constValues' Ptr TypeInfo info' <- Ptr (Ptr TypeInfo) -> IO (Ptr TypeInfo) forall a. Storable a => Ptr a -> IO a peek Ptr (Ptr TypeInfo) info TypeInfo info'' <- ((ManagedPtr TypeInfo -> TypeInfo) -> Ptr TypeInfo -> IO TypeInfo forall a. (HasCallStack, WrappedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a wrapPtr ManagedPtr TypeInfo -> TypeInfo GObject.TypeInfo.TypeInfo) Ptr TypeInfo info' EnumValue -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr EnumValue constValues Ptr (Ptr TypeInfo) -> IO () forall a. Ptr a -> IO () freeMem Ptr (Ptr TypeInfo) info TypeInfo -> IO TypeInfo forall (m :: * -> *) a. Monad m => a -> m a return TypeInfo info'' -- function g_boxed_free -- Args: [ Arg -- { argCName = "boxed_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The type of @boxed." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "boxed" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The boxed structure to be freed." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "g_boxed_free" g_boxed_free :: CGType -> -- boxed_type : TBasicType TGType Ptr () -> -- boxed : TBasicType TPtr IO () -- | Free the boxed structure /@boxed@/ which is of type /@boxedType@/. boxedFree :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@boxedType@/: The type of /@boxed@/. -> Ptr () -- ^ /@boxed@/: The boxed structure to be freed. -> m () boxedFree :: GType -> Ptr () -> m () boxedFree boxedType :: GType boxedType boxed :: Ptr () boxed = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do let boxedType' :: CGType boxedType' = GType -> CGType gtypeToCGType GType boxedType CGType -> Ptr () -> IO () g_boxed_free CGType boxedType' Ptr () boxed () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () -- function g_boxed_copy -- Args: [ Arg -- { argCName = "boxed_type" -- , argType = TBasicType TGType -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The type of @src_boxed." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "src_boxed" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "The boxed structure to be copied." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TPtr) -- throws : False -- Skip return : False foreign import ccall "g_boxed_copy" g_boxed_copy :: CGType -> -- boxed_type : TBasicType TGType Ptr () -> -- src_boxed : TBasicType TPtr IO (Ptr ()) -- | Provide a copy of a boxed structure /@srcBoxed@/ which is of type /@boxedType@/. boxedCopy :: (B.CallStack.HasCallStack, MonadIO m) => GType -- ^ /@boxedType@/: The type of /@srcBoxed@/. -> Ptr () -- ^ /@srcBoxed@/: The boxed structure to be copied. -> m (Ptr ()) -- ^ __Returns:__ The newly created copy of the boxed -- structure. boxedCopy :: GType -> Ptr () -> m (Ptr ()) boxedCopy boxedType :: GType boxedType srcBoxed :: Ptr () srcBoxed = 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 $ do let boxedType' :: CGType boxedType' = GType -> CGType gtypeToCGType GType boxedType Ptr () result <- CGType -> Ptr () -> IO (Ptr ()) g_boxed_copy CGType boxedType' Ptr () srcBoxed Ptr () -> IO (Ptr ()) forall (m :: * -> *) a. Monad m => a -> m a return Ptr () result