| Copyright | Will Thompson and Iñaki García Etxebarria | 
|---|---|
| License | LGPL-2.1 | 
| Maintainer | Iñaki García Etxebarria | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
GI.GObject.Functions
Contents
- Methods- boxedCopy
- boxedFree
- boxedTypeRegisterStatic
- clearSignalHandler
- enumCompleteTypeInfo
- enumGetValue
- enumGetValueByName
- enumGetValueByNick
- enumRegisterStatic
- enumToString
- flagsCompleteTypeInfo
- flagsGetFirstValue
- flagsGetValueByName
- flagsGetValueByNick
- flagsRegisterStatic
- flagsToString
- gtypeGetType
- paramSpecBoolean
- paramSpecBoxed
- paramSpecChar
- paramSpecDouble
- paramSpecEnum
- paramSpecFlags
- paramSpecFloat
- paramSpecGtype
- paramSpecInt
- paramSpecInt64
- paramSpecLong
- paramSpecObject
- paramSpecParam
- paramSpecPointer
- paramSpecString
- paramSpecUchar
- paramSpecUint
- paramSpecUint64
- paramSpecUlong
- paramSpecUnichar
- paramSpecVariant
- paramTypeRegisterStatic
- paramValueConvert
- paramValueDefaults
- paramValueIsValid
- paramValueSetDefault
- paramValueValidate
- paramValuesCmp
- pointerTypeRegisterStatic
- signalAccumulatorFirstWins
- signalAccumulatorTrueHandled
- signalAddEmissionHook
- signalChainFromOverridden
- signalConnectClosure
- signalConnectClosureById
- signalEmitv
- signalGetInvocationHint
- signalHandlerBlock
- signalHandlerDisconnect
- signalHandlerFind
- signalHandlerIsConnected
- signalHandlerUnblock
- signalHandlersBlockMatched
- signalHandlersDestroy
- signalHandlersDisconnectMatched
- signalHandlersUnblockMatched
- signalHasHandlerPending
- signalIsValidName
- signalListIds
- signalLookup
- signalName
- signalNewv
- signalOverrideClassClosure
- signalOverrideClassHandler
- signalParseName
- signalQuery
- signalRemoveEmissionHook
- signalStopEmission
- signalStopEmissionByName
- signalTypeCclosureNew
- strdupValueContents
- typeAddClassPrivate
- typeAddInstancePrivate
- typeAddInterfaceDynamic
- typeAddInterfaceStatic
- typeCheckClassIsA
- typeCheckInstance
- typeCheckInstanceIsA
- typeCheckInstanceIsFundamentallyA
- typeCheckIsValueType
- typeCheckValue
- typeCheckValueHolds
- typeChildren
- typeDefaultInterfacePeek
- typeDefaultInterfaceRef
- typeDefaultInterfaceUnref
- typeDepth
- typeEnsure
- typeFreeInstance
- typeFromName
- typeFundamental
- typeFundamentalNext
- typeGetInstanceCount
- typeGetPlugin
- typeGetQdata
- typeGetTypeRegistrationSerial
- typeInit
- typeInitWithDebugFlags
- typeInterfaces
- typeIsA
- typeName
- typeNameFromClass
- typeNameFromInstance
- typeNextBase
- typeParent
- typeQname
- typeQuery
- typeRegisterDynamic
- typeRegisterFundamental
- typeRegisterStatic
- typeSetQdata
- typeTestFlags
- variantGetGtype
 
Description
Synopsis
- boxedCopy :: (HasCallStack, MonadIO m) => GType -> Ptr () -> m (Ptr ())
- boxedFree :: (HasCallStack, MonadIO m) => GType -> Ptr () -> m ()
- boxedTypeRegisterStatic :: (HasCallStack, MonadIO m) => Text -> BoxedCopyFunc -> BoxedFreeFunc -> m GType
- clearSignalHandler :: (HasCallStack, MonadIO m, IsObject a) => CULong -> a -> m ()
- enumCompleteTypeInfo :: (HasCallStack, MonadIO m) => GType -> EnumValue -> m TypeInfo
- enumGetValue :: (HasCallStack, MonadIO m) => EnumClass -> Int32 -> m (Maybe EnumValue)
- enumGetValueByName :: (HasCallStack, MonadIO m) => EnumClass -> Text -> m (Maybe EnumValue)
- enumGetValueByNick :: (HasCallStack, MonadIO m) => EnumClass -> Text -> m (Maybe EnumValue)
- enumRegisterStatic :: (HasCallStack, MonadIO m) => Text -> EnumValue -> m GType
- enumToString :: (HasCallStack, MonadIO m) => GType -> Int32 -> m Text
- flagsCompleteTypeInfo :: (HasCallStack, MonadIO m) => GType -> FlagsValue -> m TypeInfo
- flagsGetFirstValue :: (HasCallStack, MonadIO m) => FlagsClass -> Word32 -> m (Maybe FlagsValue)
- flagsGetValueByName :: (HasCallStack, MonadIO m) => FlagsClass -> Text -> m (Maybe FlagsValue)
- flagsGetValueByNick :: (HasCallStack, MonadIO m) => FlagsClass -> Text -> m (Maybe FlagsValue)
- flagsRegisterStatic :: (HasCallStack, MonadIO m) => Text -> FlagsValue -> m GType
- flagsToString :: (HasCallStack, MonadIO m) => GType -> Word32 -> m Text
- gtypeGetType :: (HasCallStack, MonadIO m) => m GType
- paramSpecBoolean :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Bool -> [ParamFlags] -> m GParamSpec
- paramSpecBoxed :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> GType -> [ParamFlags] -> m GParamSpec
- paramSpecChar :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Int8 -> Int8 -> Int8 -> [ParamFlags] -> m GParamSpec
- paramSpecDouble :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Double -> Double -> Double -> [ParamFlags] -> m GParamSpec
- paramSpecEnum :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> GType -> Int32 -> [ParamFlags] -> m GParamSpec
- paramSpecFlags :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> GType -> Word32 -> [ParamFlags] -> m GParamSpec
- paramSpecFloat :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Float -> Float -> Float -> [ParamFlags] -> m GParamSpec
- paramSpecGtype :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> GType -> [ParamFlags] -> m GParamSpec
- paramSpecInt :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Int32 -> Int32 -> Int32 -> [ParamFlags] -> m GParamSpec
- paramSpecInt64 :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Int64 -> Int64 -> Int64 -> [ParamFlags] -> m GParamSpec
- paramSpecLong :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> CLong -> CLong -> CLong -> [ParamFlags] -> m GParamSpec
- paramSpecObject :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> GType -> [ParamFlags] -> m GParamSpec
- paramSpecParam :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> GType -> [ParamFlags] -> m GParamSpec
- paramSpecPointer :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> [ParamFlags] -> m GParamSpec
- paramSpecString :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Maybe Text -> [ParamFlags] -> m GParamSpec
- paramSpecUchar :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Word8 -> Word8 -> Word8 -> [ParamFlags] -> m GParamSpec
- paramSpecUint :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Word32 -> Word32 -> Word32 -> [ParamFlags] -> m GParamSpec
- paramSpecUint64 :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Word64 -> Word64 -> Word64 -> [ParamFlags] -> m GParamSpec
- paramSpecUlong :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> CULong -> CULong -> CULong -> [ParamFlags] -> m GParamSpec
- paramSpecUnichar :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> Char -> [ParamFlags] -> m GParamSpec
- paramSpecVariant :: (HasCallStack, MonadIO m) => Text -> Maybe Text -> Maybe Text -> VariantType -> Maybe GVariant -> [ParamFlags] -> m GParamSpec
- paramTypeRegisterStatic :: (HasCallStack, MonadIO m) => Text -> ParamSpecTypeInfo -> m GType
- paramValueConvert :: (HasCallStack, MonadIO m) => GParamSpec -> GValue -> GValue -> Bool -> m Bool
- paramValueDefaults :: (HasCallStack, MonadIO m) => GParamSpec -> GValue -> m Bool
- paramValueIsValid :: (HasCallStack, MonadIO m) => GParamSpec -> GValue -> m Bool
- paramValueSetDefault :: (HasCallStack, MonadIO m) => GParamSpec -> GValue -> m ()
- paramValueValidate :: (HasCallStack, MonadIO m) => GParamSpec -> GValue -> m Bool
- paramValuesCmp :: (HasCallStack, MonadIO m) => GParamSpec -> GValue -> GValue -> m Int32
- pointerTypeRegisterStatic :: (HasCallStack, MonadIO m) => Text -> m GType
- signalAccumulatorFirstWins :: (HasCallStack, MonadIO m) => SignalInvocationHint -> GValue -> GValue -> Ptr () -> m Bool
- signalAccumulatorTrueHandled :: (HasCallStack, MonadIO m) => SignalInvocationHint -> GValue -> GValue -> Ptr () -> m Bool
- signalAddEmissionHook :: (HasCallStack, MonadIO m) => Word32 -> Word32 -> SignalEmissionHook -> m CULong
- signalChainFromOverridden :: (HasCallStack, MonadIO m) => [GValue] -> GValue -> m ()
- signalConnectClosure :: (HasCallStack, MonadIO m, IsObject a) => a -> Text -> GClosure b -> Bool -> m CULong
- signalConnectClosureById :: (HasCallStack, MonadIO m, IsObject a) => a -> Word32 -> Word32 -> GClosure b -> Bool -> m CULong
- signalEmitv :: (HasCallStack, MonadIO m) => [GValue] -> Word32 -> Word32 -> m GValue
- signalGetInvocationHint :: (HasCallStack, MonadIO m, IsObject a) => a -> m (Maybe SignalInvocationHint)
- signalHandlerBlock :: (HasCallStack, MonadIO m, IsObject a) => a -> CULong -> m ()
- signalHandlerDisconnect :: (HasCallStack, MonadIO m, IsObject a) => a -> CULong -> m ()
- signalHandlerFind :: (HasCallStack, MonadIO m, IsObject a) => a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m CULong
- signalHandlerIsConnected :: (HasCallStack, MonadIO m, IsObject a) => a -> CULong -> m Bool
- signalHandlerUnblock :: (HasCallStack, MonadIO m, IsObject a) => a -> CULong -> m ()
- signalHandlersBlockMatched :: (HasCallStack, MonadIO m, IsObject a) => a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m Word32
- signalHandlersDestroy :: (HasCallStack, MonadIO m, IsObject a) => a -> m ()
- signalHandlersDisconnectMatched :: (HasCallStack, MonadIO m, IsObject a) => a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m Word32
- signalHandlersUnblockMatched :: (HasCallStack, MonadIO m, IsObject a) => a -> [SignalMatchType] -> Word32 -> Word32 -> Maybe (GClosure b) -> Ptr () -> Ptr () -> m Word32
- signalHasHandlerPending :: (HasCallStack, MonadIO m, IsObject a) => a -> Word32 -> Word32 -> Bool -> m Bool
- signalIsValidName :: (HasCallStack, MonadIO m) => Text -> m Bool
- signalListIds :: (HasCallStack, MonadIO m) => GType -> m [Word32]
- signalLookup :: (HasCallStack, MonadIO m) => Text -> GType -> m Word32
- signalName :: (HasCallStack, MonadIO m) => Word32 -> m (Maybe Text)
- signalNewv :: (HasCallStack, MonadIO m) => Text -> GType -> [SignalFlags] -> Maybe (GClosure a) -> Maybe SignalAccumulator -> Maybe ClosureMarshal -> GType -> Maybe [GType] -> m Word32
- signalOverrideClassClosure :: (HasCallStack, MonadIO m) => Word32 -> GType -> GClosure a -> m ()
- signalOverrideClassHandler :: (HasCallStack, MonadIO m) => Text -> GType -> Callback -> m ()
- signalParseName :: (HasCallStack, MonadIO m) => Text -> GType -> Bool -> m (Bool, Word32, Word32)
- signalQuery :: (HasCallStack, MonadIO m) => Word32 -> m SignalQuery
- signalRemoveEmissionHook :: (HasCallStack, MonadIO m) => Word32 -> CULong -> m ()
- signalStopEmission :: (HasCallStack, MonadIO m, IsObject a) => a -> Word32 -> Word32 -> m ()
- signalStopEmissionByName :: (HasCallStack, MonadIO m, IsObject a) => a -> Text -> m ()
- signalTypeCclosureNew :: (HasCallStack, MonadIO m) => GType -> Word32 -> m (GClosure a)
- strdupValueContents :: (HasCallStack, MonadIO m) => GValue -> m Text
- typeAddClassPrivate :: (HasCallStack, MonadIO m) => GType -> CSize -> m ()
- typeAddInstancePrivate :: (HasCallStack, MonadIO m) => GType -> CSize -> m Int32
- typeAddInterfaceDynamic :: (HasCallStack, MonadIO m, IsTypePlugin a) => GType -> GType -> a -> m ()
- typeAddInterfaceStatic :: (HasCallStack, MonadIO m) => GType -> GType -> InterfaceInfo -> m ()
- typeCheckClassIsA :: (HasCallStack, MonadIO m) => TypeClass -> GType -> m Bool
- typeCheckInstance :: (HasCallStack, MonadIO m) => TypeInstance -> m Bool
- typeCheckInstanceIsA :: (HasCallStack, MonadIO m) => TypeInstance -> GType -> m Bool
- typeCheckInstanceIsFundamentallyA :: (HasCallStack, MonadIO m) => TypeInstance -> GType -> m Bool
- typeCheckIsValueType :: (HasCallStack, MonadIO m) => GType -> m Bool
- typeCheckValue :: (HasCallStack, MonadIO m) => GValue -> m Bool
- typeCheckValueHolds :: (HasCallStack, MonadIO m) => GValue -> GType -> m Bool
- typeChildren :: (HasCallStack, MonadIO m) => GType -> m [GType]
- typeDefaultInterfacePeek :: (HasCallStack, MonadIO m) => GType -> m TypeInterface
- typeDefaultInterfaceRef :: (HasCallStack, MonadIO m) => GType -> m TypeInterface
- typeDefaultInterfaceUnref :: (HasCallStack, MonadIO m) => TypeInterface -> m ()
- typeDepth :: (HasCallStack, MonadIO m) => GType -> m Word32
- typeEnsure :: (HasCallStack, MonadIO m) => GType -> m ()
- typeFreeInstance :: (HasCallStack, MonadIO m) => TypeInstance -> m ()
- typeFromName :: (HasCallStack, MonadIO m) => Text -> m GType
- typeFundamental :: (HasCallStack, MonadIO m) => GType -> m GType
- typeFundamentalNext :: (HasCallStack, MonadIO m) => m GType
- typeGetInstanceCount :: (HasCallStack, MonadIO m) => GType -> m Int32
- typeGetPlugin :: (HasCallStack, MonadIO m) => GType -> m TypePlugin
- typeGetQdata :: (HasCallStack, MonadIO m) => GType -> Word32 -> m (Ptr ())
- typeGetTypeRegistrationSerial :: (HasCallStack, MonadIO m) => m Word32
- typeInit :: (HasCallStack, MonadIO m) => m ()
- typeInitWithDebugFlags :: (HasCallStack, MonadIO m) => [TypeDebugFlags] -> m ()
- typeInterfaces :: (HasCallStack, MonadIO m) => GType -> m [GType]
- typeIsA :: (HasCallStack, MonadIO m) => GType -> GType -> m Bool
- typeName :: (HasCallStack, MonadIO m) => GType -> m (Maybe Text)
- typeNameFromClass :: (HasCallStack, MonadIO m) => TypeClass -> m Text
- typeNameFromInstance :: (HasCallStack, MonadIO m) => TypeInstance -> m Text
- typeNextBase :: (HasCallStack, MonadIO m) => GType -> GType -> m GType
- typeParent :: (HasCallStack, MonadIO m) => GType -> m GType
- typeQname :: (HasCallStack, MonadIO m) => GType -> m Word32
- typeQuery :: (HasCallStack, MonadIO m) => GType -> m TypeQuery
- typeRegisterDynamic :: (HasCallStack, MonadIO m, IsTypePlugin a) => GType -> Text -> a -> [TypeFlags] -> m GType
- typeRegisterFundamental :: (HasCallStack, MonadIO m) => GType -> Text -> TypeInfo -> TypeFundamentalInfo -> [TypeFlags] -> m GType
- typeRegisterStatic :: (HasCallStack, MonadIO m) => GType -> Text -> TypeInfo -> [TypeFlags] -> m GType
- typeSetQdata :: (HasCallStack, MonadIO m) => GType -> Word32 -> Ptr () -> m ()
- typeTestFlags :: (HasCallStack, MonadIO m) => GType -> Word32 -> m Bool
- variantGetGtype :: (HasCallStack, MonadIO m) => m GType
Methods
boxedCopy
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Ptr () | 
 | 
| -> m (Ptr ()) | Returns: The newly created copy of the boxed structure. | 
Provide a copy of a boxed structure srcBoxed which is of type boxedType.
boxedFree
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Free the boxed structure boxed which is of type boxedType.
boxedTypeRegisterStatic
boxedTypeRegisterStatic Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> BoxedCopyFunc | 
 | 
| -> BoxedFreeFunc | 
 | 
| -> m GType | Returns: New  | 
This function creates a new G_TYPE_BOXED derived type id for a new
 boxed type with name name.
Boxed type handling functions have to be provided to copy and free opaque boxed structures of this type.
For the general case, it is recommended to use G_DEFINE_BOXED_TYPE()
 instead of calling boxedTypeRegisterStatic directly. The macro
 will create the appropriate *_get_type() function for the boxed type.
clearSignalHandler
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => CULong | 
 | 
| -> a | 
 | 
| -> m () | 
Disconnects a handler from instance so it will not be called during
 any future or currently ongoing emissions of the signal it has been
 connected to. The handlerIdPtr is then set to zero, which is never a valid handler ID value (see g_signal_connect()).
If the handler ID is 0 then this function does nothing.
There is also a macro version of this function so that the code will be inlined.
Since: 2.62
enumCompleteTypeInfo
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> EnumValue | 
 | 
| -> m TypeInfo | 
This function is meant to be called from the complete_type_info
 function of a 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);
}enumGetValue
Arguments
| :: (HasCallStack, MonadIO m) | |
| => EnumClass | 
 | 
| -> Int32 | 
 | 
| -> m (Maybe EnumValue) | Returns: the  | 
Returns the EnumValue for a value.
enumGetValueByName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => EnumClass | 
 | 
| -> Text | 
 | 
| -> m (Maybe EnumValue) | Returns: the  | 
Looks up a EnumValue by name.
enumGetValueByNick
Arguments
| :: (HasCallStack, MonadIO m) | |
| => EnumClass | 
 | 
| -> Text | 
 | 
| -> m (Maybe EnumValue) | Returns: the  | 
Looks up a EnumValue by nickname.
enumRegisterStatic
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> EnumValue | 
 | 
| -> m GType | Returns: The new type identifier. | 
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 enumRegisterStatic.
enumToString
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Int32 | 
 | 
| -> m Text | Returns: a newly-allocated text string | 
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
flagsCompleteTypeInfo
flagsCompleteTypeInfo Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> FlagsValue | 
 | 
| -> m TypeInfo | 
This function is meant to be called from the complete_type_info()
 function of a TypePlugin implementation, see the example for
 enumCompleteTypeInfo above.
flagsGetFirstValue
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FlagsClass | 
 | 
| -> Word32 | 
 | 
| -> m (Maybe FlagsValue) | Returns: the first  | 
Returns the first FlagsValue which is set in value.
flagsGetValueByName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FlagsClass | 
 | 
| -> Text | 
 | 
| -> m (Maybe FlagsValue) | Returns: the  | 
Looks up a FlagsValue by name.
flagsGetValueByNick
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FlagsClass | 
 | 
| -> Text | 
 | 
| -> m (Maybe FlagsValue) | Returns: the  | 
Looks up a FlagsValue by nickname.
flagsRegisterStatic
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> FlagsValue | 
 | 
| -> m GType | Returns: The new type identifier. | 
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 flagsRegisterStatic.
flagsToString
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Word32 | 
 | 
| -> m Text | Returns: a newly-allocated text string | 
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
gtypeGetType
gtypeGetType :: (HasCallStack, MonadIO m) => m GType Source #
No description available in the introspection data.
paramSpecBoolean
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Bool | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecBoolean instance specifying a G_TYPE_BOOLEAN
 property. In many cases, it may be more appropriate to use an enum with
 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.
paramSpecBoxed
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> GType | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecBoxed instance specifying a G_TYPE_BOXED
 derived property.
See g_param_spec_internal() for details on property names.
paramSpecChar
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Int8 | 
 | 
| -> Int8 | 
 | 
| -> Int8 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecChar instance specifying a G_TYPE_CHAR property.
paramSpecDouble
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Double | 
 | 
| -> Double | 
 | 
| -> Double | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecDouble instance specifying a G_TYPE_DOUBLE
 property.
See g_param_spec_internal() for details on property names.
paramSpecEnum
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> GType | 
 | 
| -> Int32 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecEnum instance specifying a G_TYPE_ENUM
 property.
See g_param_spec_internal() for details on property names.
paramSpecFlags
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> GType | 
 | 
| -> Word32 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecFlags instance specifying a G_TYPE_FLAGS
 property.
See g_param_spec_internal() for details on property names.
paramSpecFloat
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Float | 
 | 
| -> Float | 
 | 
| -> Float | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecFloat instance specifying a G_TYPE_FLOAT property.
See g_param_spec_internal() for details on property names.
paramSpecGtype
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> GType | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecGType instance specifying a
 G_TYPE_GTYPE property.
See g_param_spec_internal() for details on property names.
Since: 2.10
paramSpecInt
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Int32 | 
 | 
| -> Int32 | 
 | 
| -> Int32 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecInt instance specifying a G_TYPE_INT property.
See g_param_spec_internal() for details on property names.
paramSpecInt64
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Int64 | 
 | 
| -> Int64 | 
 | 
| -> Int64 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecInt64 instance specifying a G_TYPE_INT64 property.
See g_param_spec_internal() for details on property names.
paramSpecLong
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> CLong | 
 | 
| -> CLong | 
 | 
| -> CLong | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecLong instance specifying a G_TYPE_LONG property.
See g_param_spec_internal() for details on property names.
paramSpecObject
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> GType | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecBoxed instance specifying a G_TYPE_OBJECT
 derived property.
See g_param_spec_internal() for details on property names.
paramSpecParam
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> GType | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecParam instance specifying a G_TYPE_PARAM
 property.
See g_param_spec_internal() for details on property names.
paramSpecPointer
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecPointer instance specifying a pointer property.
 Where possible, it is better to use paramSpecObject or
 paramSpecBoxed to expose memory management information.
See g_param_spec_internal() for details on property names.
paramSpecString
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecString instance.
See g_param_spec_internal() for details on property names.
paramSpecUchar
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Word8 | 
 | 
| -> Word8 | 
 | 
| -> Word8 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecUChar instance specifying a G_TYPE_UCHAR property.
paramSpecUint
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecUInt instance specifying a G_TYPE_UINT property.
See g_param_spec_internal() for details on property names.
paramSpecUint64
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Word64 | 
 | 
| -> Word64 | 
 | 
| -> Word64 | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecUInt64 instance specifying a G_TYPE_UINT64
 property.
See g_param_spec_internal() for details on property names.
paramSpecUlong
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> CULong | 
 | 
| -> CULong | 
 | 
| -> CULong | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecULong instance specifying a G_TYPE_ULONG
 property.
See g_param_spec_internal() for details on property names.
paramSpecUnichar
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> Char | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: a newly created parameter specification | 
Creates a new ParamSpecUnichar instance specifying a G_TYPE_UINT
 property. Value structures for this property can be accessed with
 valueSetUint and valueGetUint.
See g_param_spec_internal() for details on property names.
paramSpecVariant
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> Maybe Text | 
 | 
| -> Maybe Text | 
 | 
| -> VariantType | 
 | 
| -> Maybe GVariant | 
 | 
| -> [ParamFlags] | 
 | 
| -> m GParamSpec | Returns: the newly created  | 
Creates a new ParamSpecVariant instance specifying a GVariant
 property.
If defaultValue is floating, it is consumed.
See g_param_spec_internal() for details on property names.
Since: 2.26
paramTypeRegisterStatic
paramTypeRegisterStatic Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> ParamSpecTypeInfo | 
 | 
| -> m GType | Returns: The new type identifier. | 
Registers name as the name of a new static type derived
 from G_TYPE_PARAM.
The type system uses the information contained in the ParamSpecTypeInfo
 structure pointed to by info to manage the ParamSpec type and its
 instances.
paramValueConvert
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GParamSpec | 
 | 
| -> GValue | 
 | 
| -> GValue | 
 | 
| -> Bool | 
 | 
| -> m Bool | Returns:  | 
Transforms srcValue into destValue if possible, and then
 validates destValue, in order for it to conform to pspec.  If
 strictValidation is True this function will only succeed if the
 transformed destValue complied to pspec without modifications.
See also valueTypeTransformable, valueTransform and
 paramValueValidate.
paramValueDefaults
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GParamSpec | 
 | 
| -> GValue | 
 | 
| -> m Bool | Returns: whether  | 
Checks whether value contains the default value as specified in pspec.
paramValueIsValid
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GParamSpec | 
 | 
| -> GValue | 
 | 
| -> m Bool | Returns: whether the contents of  | 
Return whether the contents of value comply with the specifications
 set out by pspec.
Since: 2.74
paramValueSetDefault
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GParamSpec | 
 | 
| -> GValue | 
 | 
| -> m () | 
Sets value to its default value as specified in pspec.
paramValueValidate
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GParamSpec | 
 | 
| -> GValue | 
 | 
| -> m Bool | Returns: whether modifying  | 
Ensures that the contents of value comply with the specifications
 set out by pspec. For example, a 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.
paramValuesCmp
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GParamSpec | 
 | 
| -> GValue | 
 | 
| -> GValue | 
 | 
| -> m Int32 | Returns: -1, 0 or +1, for a less than, equal to or greater than result | 
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.
pointerTypeRegisterStatic
pointerTypeRegisterStatic Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> m GType | Returns: a new  | 
Creates a new G_TYPE_POINTER derived type id for a new
 pointer type with name name.
signalAccumulatorFirstWins
signalAccumulatorFirstWins Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => SignalInvocationHint | 
 | 
| -> GValue | 
 | 
| -> GValue | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns: standard  | 
A predefined 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
signalAccumulatorTrueHandled
signalAccumulatorTrueHandled Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => SignalInvocationHint | 
 | 
| -> GValue | 
 | 
| -> GValue | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns: standard  | 
A predefined SignalAccumulator for signals that return a
 boolean values. The behavior that this accumulator gives is
 that a return of True stops the signal emission: no further
 callbacks will be invoked, while a return of False allows
 the emission to continue. The idea here is that a True return
 indicates that the callback handled the signal, and no further
 handling is needed.
Since: 2.4
signalAddEmissionHook
signalAddEmissionHook Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
 | 
| -> Word32 | 
 | 
| -> SignalEmissionHook | 
 | 
| -> m CULong | Returns: the hook id, for later use with  | 
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 SignalFlagsNoHooks flag set.
signalChainFromOverridden
signalChainFromOverridden Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [GValue] | 
 | 
| -> GValue | 
 | 
| -> m () | 
Calls the original class closure of a signal. This function should only
 be called from an overridden class closure; see
 signalOverrideClassClosure and
 signalOverrideClassHandler.
signalConnectClosure
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> Text | 
 | 
| -> GClosure b | 
 | 
| -> Bool | 
 | 
| -> m CULong | Returns: the handler ID (always greater than 0) | 
Connects a closure to a signal for a particular object.
If closure is a floating reference (see closureSink), this function
 takes ownership of closure.
This function cannot fail. If the given signal doesn’t exist, a critical warning is emitted.
signalConnectClosureById
signalConnectClosureById Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> GClosure b | 
 | 
| -> Bool | 
 | 
| -> m CULong | Returns: the handler ID (always greater than 0) | 
Connects a closure to a signal for a particular object.
If closure is a floating reference (see closureSink), this function
 takes ownership of closure.
This function cannot fail. If the given signal doesn’t exist, a critical warning is emitted.
signalEmitv
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [GValue] | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> m GValue | 
Emits a signal. Signal emission is done synchronously. The method will only return control after all handlers are called or signal emission was stopped.
Note that signalEmitv doesn't change returnValue if no handlers are
 connected, in contrast to g_signal_emit() and g_signal_emit_valist().
signalGetInvocationHint
signalGetInvocationHint Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> m (Maybe SignalInvocationHint) | Returns: the invocation hint of the innermost
     signal emission, or  | 
Returns the invocation hint of the innermost signal emission of instance.
signalHandlerBlock
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> CULong | 
 | 
| -> m () | 
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 deactivate 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.
signalHandlerDisconnect
signalHandlerDisconnect Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> CULong | 
 | 
| -> m () | 
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.
signalHandlerFind
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> [SignalMatchType] | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> Maybe (GClosure b) | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m CULong | Returns: A valid non-0 signal handler id for a successful match. | 
Finds the first signal handler that matches certain selection criteria.
 The criteria mask is passed as an OR-ed combination of 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.
signalHandlerIsConnected
signalHandlerIsConnected Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> CULong | 
 | 
| -> m Bool | Returns: whether  | 
Returns whether handlerId is the ID of a handler connected to instance.
signalHandlerUnblock
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> CULong | 
 | 
| -> m () | 
Undoes the effect of a previous 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.
signalHandlersBlockMatched
signalHandlersBlockMatched Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> [SignalMatchType] | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> Maybe (GClosure b) | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Word32 | Returns: The number of handlers that matched. | 
Blocks all handlers on an instance that match a certain selection criteria.
The criteria mask is passed as a combination of SignalMatchType flags, and
 the criteria values are passed as arguments. A handler must match on all
 flags set in mask to be blocked (i.e. the match is conjunctive).
Passing at least one of the SignalMatchTypeId, SignalMatchTypeClosure,
 SignalMatchTypeFunc
 or SignalMatchTypeData match flags is required for successful matches.
 If no handlers were found, 0 is returned, the number of blocked handlers
 otherwise.
Support for SignalMatchTypeId was added in GLib 2.78.
signalHandlersDestroy
signalHandlersDestroy Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> m () | 
Destroy all signal handlers of a type instance. This function is
 an implementation detail of the Object dispose implementation,
 and should not be used outside of the type system.
signalHandlersDisconnectMatched
signalHandlersDisconnectMatched Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> [SignalMatchType] | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> Maybe (GClosure b) | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Word32 | Returns: The number of handlers that matched. | 
Disconnects all handlers on an instance that match a certain selection criteria.
The criteria mask is passed as a combination of SignalMatchType flags, and
 the criteria values are passed as arguments. A handler must match on all
 flags set in mask to be disconnected (i.e. the match is conjunctive).
Passing at least one of the SignalMatchTypeId, SignalMatchTypeClosure,
 SignalMatchTypeFunc or
 SignalMatchTypeData match flags is required for successful
 matches.  If no handlers were found, 0 is returned, the number of
 disconnected handlers otherwise.
Support for SignalMatchTypeId was added in GLib 2.78.
signalHandlersUnblockMatched
signalHandlersUnblockMatched Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> [SignalMatchType] | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> Maybe (GClosure b) | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Word32 | Returns: The number of handlers that matched. | 
Unblocks all handlers on an instance that match a certain selection criteria.
The criteria mask is passed as a combination of SignalMatchType flags, and
 the criteria values are passed as arguments. A handler must match on all
 flags set in mask to be unblocked (i.e. the match is conjunctive).
Passing at least one of the SignalMatchTypeId, SignalMatchTypeClosure,
 SignalMatchTypeFunc
 or 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.
Support for SignalMatchTypeId was added in GLib 2.78.
signalHasHandlerPending
signalHasHandlerPending Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> Bool | 
 | 
| -> m Bool | Returns:  | 
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.
signalIsValidName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> m Bool | Returns:  | 
Validate a signal name. This can be useful for dynamically-generated signals which need to be validated at run-time before actually trying to create them.
See [canonical parameter names][canonical-parameter-names] for details of the rules for valid names. The rules for signal names are the same as those for property names.
Since: 2.66
signalListIds
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m [Word32] | Returns: Newly allocated array of signal IDs. | 
Lists the signals by id that a certain instance or interface type
 created. Further information about the signals can be acquired through
 signalQuery.
signalLookup
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> GType | 
 | 
| -> m Word32 | Returns: the signal's identifying number, or 0 if no signal was found. | 
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.
The type class passed as itype must already have been instantiated (for
 example, using typeClassRef) for this function to work, as signals are
 always installed during class initialization.
See g_signal_new() for details on allowed signal names.
signalName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
 | 
| -> m (Maybe Text) | Returns: the signal name, or  | 
Given the signal's identifier, finds its name.
Two different signals may have the same name, if they have differing types.
signalNewv
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> GType | 
 | 
| -> [SignalFlags] | 
 | 
| -> Maybe (GClosure a) | 
 | 
| -> Maybe SignalAccumulator | 
 | 
| -> Maybe ClosureMarshal | 
 | 
| -> GType | 
 | 
| -> Maybe [GType] | 
 | 
| -> m Word32 | Returns: the signal id | 
Creates a new signal. (This is usually done in the class initializer.)
See g_signal_new() for details on allowed signal names.
If c_marshaller is Nothing, cclosureMarshalGeneric will be used as
 the marshaller for this signal.
signalOverrideClassClosure
signalOverrideClassClosure Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
 | 
| -> GType | 
 | 
| -> GClosure a | 
 | 
| -> m () | 
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 signalChainFromOverridden and
 g_signal_chain_from_overridden_handler() for how to chain up to the
 parent class closure from inside the overridden one.
signalOverrideClassHandler
signalOverrideClassHandler Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> GType | 
 | 
| -> Callback | 
 | 
| -> m () | 
Overrides the class closure (i.e. the default handler) for the
 given signal for emissions on instances of instanceType with
 callback classHandler. instanceType must be derived from the
 type to which the signal belongs.
See signalChainFromOverridden and
 g_signal_chain_from_overridden_handler() for how to chain up to the
 parent class closure from inside the overridden one.
Since: 2.18
signalParseName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> GType | 
 | 
| -> Bool | 
 | 
| -> m (Bool, Word32, Word32) | Returns: Whether the signal name could successfully be parsed and  | 
Internal function to parse a signal name into its signalId
 and detail quark.
signalQuery
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
 | 
| -> m SignalQuery | 
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 SignalQuery
 is 0. All members filled into the SignalQuery structure should
 be considered constant and have to be left untouched.
signalRemoveEmissionHook
signalRemoveEmissionHook Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
 | 
| -> CULong | 
 | 
| -> m () | 
Deletes an emission hook.
signalStopEmission
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> Word32 | 
 | 
| -> Word32 | 
 | 
| -> m () | 
Stops a signal's current emission.
This will prevent the default method from running, if the signal was
 SignalFlagsRunLast and you connected normally (i.e. without the "after"
 flag).
Prints a warning if used on a signal which isn't being emitted.
signalStopEmissionByName
signalStopEmissionByName Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
 | 
| -> Text | 
 | 
| -> m () | 
Stops a signal's current emission.
This is just like signalStopEmission except it will look up the
 signal id for you.
signalTypeCclosureNew
signalTypeCclosureNew Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Word32 | 
 | 
| -> m (GClosure a) | Returns: a floating reference to a new  | 
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.
strdupValueContents
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GValue | 
 | 
| -> m Text | Returns: Newly allocated string. | 
typeAddClassPrivate
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> CSize | 
 | 
| -> m () | 
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
typeAddInstancePrivate
typeAddInstancePrivate :: (HasCallStack, MonadIO m) => GType -> CSize -> m Int32 Source #
No description available in the introspection data.
typeAddInterfaceDynamic
typeAddInterfaceDynamic Source #
Arguments
| :: (HasCallStack, MonadIO m, IsTypePlugin a) | |
| => GType | 
 | 
| -> GType | 
 | 
| -> a | 
 | 
| -> m () | 
Adds interfaceType to the dynamic instanceType. The information
 contained in the TypePlugin structure pointed to by plugin
 is used to manage the relationship.
typeAddInterfaceStatic
typeAddInterfaceStatic Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> GType | 
 | 
| -> InterfaceInfo | 
 | 
| -> m () | 
Adds interfaceType to the static instanceType.
 The information contained in the InterfaceInfo structure
 pointed to by info is used to manage the relationship.
typeCheckClassIsA
typeCheckClassIsA :: (HasCallStack, MonadIO m) => TypeClass -> GType -> m Bool Source #
No description available in the introspection data.
typeCheckInstance
Arguments
| :: (HasCallStack, MonadIO m) | |
| => TypeInstance | 
 | 
| -> m Bool | 
Private helper function to aid implementation of the
 G_TYPE_CHECK_INSTANCE() macro.
typeCheckInstanceIsA
typeCheckInstanceIsA :: (HasCallStack, MonadIO m) => TypeInstance -> GType -> m Bool Source #
No description available in the introspection data.
typeCheckInstanceIsFundamentallyA
typeCheckInstanceIsFundamentallyA :: (HasCallStack, MonadIO m) => TypeInstance -> GType -> m Bool Source #
No description available in the introspection data.
typeCheckIsValueType
typeCheckIsValueType :: (HasCallStack, MonadIO m) => GType -> m Bool Source #
No description available in the introspection data.
typeCheckValue
typeCheckValue :: (HasCallStack, MonadIO m) => GValue -> m Bool Source #
No description available in the introspection data.
typeCheckValueHolds
typeCheckValueHolds :: (HasCallStack, MonadIO m) => GValue -> GType -> m Bool Source #
No description available in the introspection data.
typeChildren
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m [GType] | Returns: Newly allocated
     and 0-terminated array of child types, free with  | 
Return a newly allocated and 0-terminated array of type IDs, listing
 the child types of type.
typeDefaultInterfacePeek
typeDefaultInterfacePeek Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m TypeInterface | Returns: the default
     vtable for the interface, or  | 
If the interface type gType is currently in use, returns its
 default interface vtable.
Since: 2.4
typeDefaultInterfaceRef
typeDefaultInterfaceRef Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m TypeInterface | Returns: the default
     vtable for the interface; call  | 
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 initialized by calling
 the base interface init and default vtable init functions for
 the type (the baseInit and classInit members of TypeInfo).
 Calling typeDefaultInterfaceRef is useful when you
 want to make sure that signals and properties for an interface
 have been installed.
Since: 2.4
typeDefaultInterfaceUnref
typeDefaultInterfaceUnref Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => TypeInterface | 
 | 
| -> m () | 
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 TypeInfo) will be called.
Since: 2.4
typeDepth
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m Word32 | Returns: the depth of  | 
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.
typeEnsure
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m () | 
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 typeEnsure guarantees that the
 type's _get_type() method is called.
Since: 2.34
typeFreeInstance
Arguments
| :: (HasCallStack, MonadIO m) | |
| => TypeInstance | 
 | 
| -> m () | 
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.
typeFromName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
 | 
| -> m GType | Returns: corresponding type ID or 0 | 
Look up 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).
typeFundamental
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m GType | Returns: fundamental type ID | 
Internal function, used to extract the fundamental type ID portion.
 Use G_TYPE_FUNDAMENTAL() instead.
typeFundamentalNext
Arguments
| :: (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 | 
Returns the next free fundamental type id which can be used to
 register a new fundamental type with typeRegisterFundamental.
 The returned type ID represents the highest currently registered
 fundamental type identifier.
typeGetInstanceCount
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m Int32 | Returns: the number of instances allocated of the given type; if instance counts are not available, returns 0. | 
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
typeGetPlugin
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m TypePlugin | Returns: the corresponding plugin
     if  | 
Returns the TypePlugin structure for type.
typeGetQdata
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Word32 | 
 | 
| -> m (Ptr ()) | Returns: the data, or  | 
Obtains data which has previously been attached to type
 with typeSetQdata.
Note that this does not take subtyping into account; data
 attached to one type with typeSetQdata cannot
 be retrieved from a subtype using typeGetQdata.
typeGetTypeRegistrationSerial
typeGetTypeRegistrationSerial Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: An unsigned int, representing the state of type registrations | 
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
 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
typeInit
typeInit :: (HasCallStack, MonadIO m) => m () Source #
Deprecated: (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.
typeInitWithDebugFlags
typeInitWithDebugFlags Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [TypeDebugFlags] | 
 | 
| -> m () | 
Deprecated: (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.
typeInterfaces
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m [GType] | Returns: Newly allocated
     and 0-terminated array of interface types, free with  | 
Return a newly allocated and 0-terminated array of type IDs, listing
 the interface types that type conforms to.
typeIsA
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> GType | 
 | 
| -> m Bool | Returns:  | 
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.
typeName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m (Maybe Text) | Returns: static type name or  | 
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.
typeNameFromClass
typeNameFromClass :: (HasCallStack, MonadIO m) => TypeClass -> m Text Source #
No description available in the introspection data.
typeNameFromInstance
typeNameFromInstance :: (HasCallStack, MonadIO m) => TypeInstance -> m Text Source #
No description available in the introspection data.
typeNextBase
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> GType | 
 | 
| -> m GType | Returns: immediate child of  | 
Given a leafType and a rootType which is contained in its
 ancestry, 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.
typeParent
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m GType | Returns: the parent type | 
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.
typeQname
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m Word32 | Returns: the type names quark or 0 | 
Get the corresponding quark of the type IDs name.
typeQuery
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> m TypeQuery | 
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 GType is passed in, the
 type member of the TypeQuery is 0. All members filled into the
 TypeQuery structure should be considered constant and have to be
 left untouched.
Since GLib 2.78, this function allows queries on dynamic types. Previously it only supported static types.
typeRegisterDynamic
Arguments
| :: (HasCallStack, MonadIO m, IsTypePlugin a) | |
| => GType | 
 | 
| -> Text | 
 | 
| -> a | 
 | 
| -> [TypeFlags] | 
 | 
| -> m GType | Returns: the new type identifier or  | 
Registers typeName as the name of a new dynamic type derived from
 parentType.  The type system uses the information contained in the
 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.
typeRegisterFundamental
typeRegisterFundamental Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Text | 
 | 
| -> TypeInfo | 
 | 
| -> TypeFundamentalInfo | 
 | 
| -> [TypeFlags] | 
 | 
| -> m GType | Returns: the predefined type identifier | 
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 TypeInfo structure
 pointed to by info and the TypeFundamentalInfo structure pointed to by
 finfo to manage the type and its instances. The value of flags determines
 additional characteristics of the fundamental type.
typeRegisterStatic
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Text | 
 | 
| -> TypeInfo | 
 | 
| -> [TypeFlags] | 
 | 
| -> m GType | Returns: the new type identifier | 
Registers typeName as the name of a new static type derived from
 parentType. The type system uses the information contained in the
 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.
typeSetQdata
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GType | 
 | 
| -> Word32 | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Attaches arbitrary data to a type.
typeTestFlags
typeTestFlags :: (HasCallStack, MonadIO m) => GType -> Word32 -> m Bool Source #
No description available in the introspection data.
variantGetGtype
variantGetGtype :: (HasCallStack, MonadIO m) => m GType Source #
No description available in the introspection data.