Safe Haskell | None |
---|---|
Language | Haskell98 |
Basic types used in the bindings.
- newtype GType = GType {}
- type CGType = Word64
- gtypeName :: GType -> IO String
- gtypeString :: GType
- gtypePointer :: GType
- gtypeInt :: GType
- gtypeUInt :: GType
- gtypeLong :: GType
- gtypeULong :: GType
- gtypeInt64 :: GType
- gtypeUInt64 :: GType
- gtypeFloat :: GType
- gtypeDouble :: GType
- gtypeBoolean :: GType
- gtypeGType :: GType
- gtypeStrv :: GType
- gtypeBoxed :: GType
- gtypeObject :: GType
- gtypeVariant :: GType
- gtypeByteArray :: GType
- gtypeInvalid :: GType
- type ForeignPtrNewtype a = Coercible a (ForeignPtr ())
- class ForeignPtrNewtype a => BoxedObject a where
- class BoxedEnum a where
- boxedEnumType :: a -> IO GType
- class BoxedFlags a where
- boxedFlagsType :: Proxy a -> IO GType
- class ForeignPtrNewtype a => GObject a where
- gobjectIsInitiallyUnowned :: a -> Bool
- gobjectType :: a -> IO GType
- class ForeignPtrNewtype a => WrappedPtr a where
- wrappedPtrCalloc :: IO (Ptr a)
- wrappedPtrCopy :: Ptr a -> IO (Ptr a)
- wrappedPtrFree :: Maybe (FunPtr (Ptr a -> IO ()))
- data UnexpectedNullPointerReturn = UnexpectedNullPointerReturn {}
- class NullToNothing a where
- nullToNothing :: MonadIO m => IO a -> m (Maybe (UnMaybe a))
- newtype GVariant = GVariant (ForeignPtr GVariant)
- newtype GParamSpec = GParamSpec (ForeignPtr GParamSpec)
- data GArray a = GArray (Ptr (GArray a))
- data GPtrArray a = GPtrArray (Ptr (GPtrArray a))
- data GByteArray = GByteArray (Ptr GByteArray)
- data GHashTable a b = GHashTable (Ptr (GHashTable a b))
- data GList a = GList (Ptr (GList a))
- g_list_free :: Ptr (GList a) -> IO ()
- data GSList a = GSList (Ptr (GSList a))
- g_slist_free :: Ptr (GSList a) -> IO ()
- class Enum a => IsGFlag a
- newtype PtrWrapped a = PtrWrapped {}
- type GDestroyNotify a = FunPtr (Ptr a -> IO ())
GType related
A newtype for use on the haskell side.
A type identifier in the GLib type system. This is the low-level
type associated with the representation in memory, when using this
on the Haskell side use GType
below.
- Note: compile-time vs run-time GTypes
Notice that there are two types of GType's: the fundamental ones,
which are created with G_TYPE_MAKE_FUNDAMENTAL(n) and always have the
same runtime representation, and the ones that are registered in the
GObject type system at runtime, and whose CGType
may change for each
program run (and generally does).
For the first type it is safe to use hsc to read the numerical values of the CGType at compile type, but for the second type it is essential to call the corresponding _get_type() function at runtime, and not use the value of the corresponding "constant" at compile time via hsc.
GType
of strings.
GType
of pointers.
GType
for gulong
.
GType
for signed 64 bit integers.
GType
for unsigned 64 bit integers.
GType
for floating point values.
GType
for gdouble.
GType
corresponding to gboolean.
GType
corresponding to a BoxedObject
.
gtypeByteArray :: GType Source
GType
for a boxed type holding a GByteArray
.
Memory management
type ForeignPtrNewtype a = Coercible a (ForeignPtr ()) Source
A constraint ensuring that the given type is coercible to a ForeignPtr. It will hold for newtypes of the form
newtype Foo = Foo (ForeignPtr Foo)
which is the typical shape of wrapped GObject
s.
class ForeignPtrNewtype a => BoxedObject a where Source
Wrapped boxed structures, identified by their GType
.
class BoxedFlags a where Source
Flags with an associated GType
.
boxedFlagsType :: Proxy a -> IO GType Source
class ForeignPtrNewtype a => GObject a where Source
A wrapped GObject
.
gobjectIsInitiallyUnowned :: a -> Bool Source
Whether the GObject
is a descendent of GInitiallyUnowned.
gobjectType :: a -> IO GType Source
The GType
for this object.
class ForeignPtrNewtype a => WrappedPtr a where Source
Pointers to structs/unions without an associated GType
.
wrappedPtrCalloc :: IO (Ptr a) Source
Allocate a zero-initialized block of memory for the given type.
wrappedPtrCopy :: Ptr a -> IO (Ptr a) Source
Make a copy of the given pointer.
wrappedPtrFree :: Maybe (FunPtr (Ptr a -> IO ())) Source
A pointer to a function for freeing the given pointer, or
Nothing
is the memory associated to the pointer does not need
to be freed.
data UnexpectedNullPointerReturn Source
A common omission in the introspection data is missing (nullable) annotations for return types, when they clearly are nullable. (A common idiom is "Returns: valid value, or %NULL if something went wrong.")
Haskell wrappers will raise this exception if the return value is
an unexpected nullPtr
.
class NullToNothing a where Source
nullToNothing :: MonadIO m => IO a -> m (Maybe (UnMaybe a)) Source
Some functions are not marked as having a nullable return type in the introspection data. The result is that they currently do not return a Maybe type. This functions lets you work around this in a way that will not break when the introspection data is fixed.
When you want to call a someHaskellGIFunction
that may return null
wrap the call like this.
nullToNothing (someHaskellGIFunction x y)
The result will be a Maybe type even if the introspection data has
not been fixed for someHaskellGIFunction
yet.
(~) * a (UnMaybe a) => NullToNothing a | |
NullToNothing (Maybe a) |
Basic GLib / GObject types
A GVariant. See Data.GI.Base.GVariant for further methods.
newtype GParamSpec Source
A GParamSpec. See Data.GI.Base.GParamSpec for further methods.
A GArray. Marshalling for this type is done in Data.GI.Base.BasicConversions, it is mapped to a list on the Haskell side.
A GPtrArray. Marshalling for this type is done in Data.GI.Base.BasicConversions, it is mapped to a list on the Haskell side.
data GByteArray Source
A GByteArray. Marshalling for this type is done in Data.GI.Base.BasicConversions, it is packed to a ByteString
on the Haskell side.
data GHashTable a b Source
A GHashTable. It is mapped to a Map
on the Haskell side.
GHashTable (Ptr (GHashTable a b)) |
A GList, mapped to a list on the Haskell side. Marshalling is done in Data.GI.Base.BasicConversions.
A GSList, mapped to a list on the Haskell side. Marshalling is done in Data.GI.Base.BasicConversions.
newtype PtrWrapped a Source
Some APIs, such as GHashTable
, pass around scalar types
wrapped into a pointer. We encode such a type as follows.
type GDestroyNotify a = FunPtr (Ptr a -> IO ()) Source
Destroy the memory associated with a given pointer.