Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.GI.Base
Description
Convenience header for basic GObject-Introspection modules
See the documentation for each individual module for a description and usage help.
Synopsis
- get :: forall info (attr :: Symbol) obj result m. (AttrGetC info obj attr result, MonadIO m) => obj -> AttrLabelProxy attr -> m result
- set :: forall o m. MonadIO m => o -> [AttrOp o 'AttrSet] -> m ()
- data AttrOp obj (tag :: AttrOpTag) where
- (:=) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy attr -> b -> AttrOp obj tag
- (:=>) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy attr -> IO b -> AttrOp obj tag
- (:~) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b a. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, tag ~ 'AttrSet, AttrOpAllowed 'AttrSet info obj, AttrOpAllowed 'AttrGet info obj, AttrSetTypeConstraint info b, a ~ AttrGetType info) => AttrLabelProxy attr -> (a -> b) -> AttrOp obj tag
- (:~>) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b a. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, tag ~ 'AttrSet, AttrOpAllowed 'AttrSet info obj, AttrOpAllowed 'AttrGet info obj, AttrSetTypeConstraint info b, a ~ AttrGetType info) => AttrLabelProxy attr -> (a -> IO b) -> AttrOp obj tag
- (:&=) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrTransferTypeConstraint info b, AttrSetTypeConstraint info (AttrTransferType info)) => AttrLabelProxy attr -> b -> AttrOp obj tag
- On :: forall obj info (tag :: AttrOpTag). (GObject obj, SignalInfo info) => SignalProxy obj info -> ((?self :: obj) => HaskellCallbackType info) -> AttrOp obj tag
- After :: forall obj info (tag :: AttrOpTag). (GObject obj, SignalInfo info) => SignalProxy obj info -> ((?self :: obj) => HaskellCallbackType info) -> AttrOp obj tag
- module Data.GI.Base.BasicConversions
- module Data.GI.Base.BasicTypes
- data GClosure a
- new :: (Constructible a tag, MonadIO m) => (ManagedPtr a -> a) -> [AttrOp a tag] -> m a
- module Data.GI.Base.GError
- module Data.GI.Base.GHashTable
- newtype GValue = GValue (ManagedPtr GValue)
- fromGValue :: (IsGValue a, MonadIO m) => GValue -> m a
- toGValue :: (IsGValue a, MonadIO m) => a -> m GValue
- class IsGValue a where
- gvalueGType_ :: IO GType
- gvalueSet_ :: Ptr GValue -> a -> IO ()
- gvalueGet_ :: Ptr GValue -> IO a
- module Data.GI.Base.GVariant
- module Data.GI.Base.ManagedPtr
- on :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> ((?self :: object) => HaskellCallbackType info) -> m SignalHandlerId
- after :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> ((?self :: object) => HaskellCallbackType info) -> m SignalHandlerId
- data SignalProxy object info where
- (:::) :: forall object info. SignalProxy object info -> Text -> SignalProxy object info
- PropertyNotify :: forall info1 (propName :: Symbol) object (pl :: Symbol). (info1 ~ ResolveAttribute propName object, AttrInfo info1, pl ~ AttrLabel info1, KnownSymbol pl) => AttrLabelProxy propName -> SignalProxy object GObjectNotifySignalInfo
- asA :: (ManagedPtrNewtype a, ManagedPtrNewtype b, HasParentTypes b, IsDescendantOf a b) => b -> (ManagedPtr a -> a) -> a
Documentation
get :: forall info (attr :: Symbol) obj result m. (AttrGetC info obj attr result, MonadIO m) => obj -> AttrLabelProxy attr -> m result Source #
Get the value of an attribute for an object.
set :: forall o m. MonadIO m => o -> [AttrOp o 'AttrSet] -> m () Source #
Set a number of properties for some object.
data AttrOp obj (tag :: AttrOpTag) where Source #
Constructors for the different operations allowed on an attribute.
Constructors
(:=) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy attr -> b -> AttrOp obj tag infixr 0 | Assign a value to an attribute |
(:=>) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy attr -> IO b -> AttrOp obj tag infixr 0 | Assign the result of an IO action to an attribute |
(:~) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b a. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, tag ~ 'AttrSet, AttrOpAllowed 'AttrSet info obj, AttrOpAllowed 'AttrGet info obj, AttrSetTypeConstraint info b, a ~ AttrGetType info) => AttrLabelProxy attr -> (a -> b) -> AttrOp obj tag infixr 0 | Apply an update function to an attribute |
(:~>) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b a. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, tag ~ 'AttrSet, AttrOpAllowed 'AttrSet info obj, AttrOpAllowed 'AttrGet info obj, AttrSetTypeConstraint info b, a ~ AttrGetType info) => AttrLabelProxy attr -> (a -> IO b) -> AttrOp obj tag infixr 0 | Apply an IO update function to an attribute |
(:&=) :: forall obj info (attr :: Symbol) (tag :: AttrOpTag) b. (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrTransferTypeConstraint info b, AttrSetTypeConstraint info (AttrTransferType info)) => AttrLabelProxy attr -> b -> AttrOp obj tag | Assign a value to an attribute, allocating any necessary
memory for representing the Haskell value as a C value. Note
that it is the responsibility of the caller to make sure that
the memory is freed when no longer used, otherwise there will
be a memory leak. In the majority of cases you probably want to
use |
On :: forall obj info (tag :: AttrOpTag). (GObject obj, SignalInfo info) => SignalProxy obj info -> ((?self :: obj) => HaskellCallbackType info) -> AttrOp obj tag | Connect the given signal to a signal handler. |
After :: forall obj info (tag :: AttrOpTag). (GObject obj, SignalInfo info) => SignalProxy obj info -> ((?self :: obj) => HaskellCallbackType info) -> AttrOp obj tag | Like |
module Data.GI.Base.BasicTypes
The basic type. This corresponds to a wrapped GClosure
on the C
side, which is a boxed object.
Instances
GBoxed (GClosure a) Source # |
|
Defined in Data.GI.Base.GClosure | |
TypedObject (GClosure a) Source # | Find the associated |
HasParentTypes (GClosure a) Source # | |
Defined in Data.GI.Base.GClosure | |
type ParentTypes (GClosure a) Source # | There are no types in the bindings that a closure can be safely cast to. |
Defined in Data.GI.Base.GClosure |
new :: (Constructible a tag, MonadIO m) => (ManagedPtr a -> a) -> [AttrOp a tag] -> m a Source #
Allocate a new instance of the given type, with the given attributes.
module Data.GI.Base.GError
module Data.GI.Base.GHashTable
Haskell-side representation of a GValue
.
Constructors
GValue (ManagedPtr GValue) |
Instances
GBoxed GValue Source # |
|
Defined in Data.GI.Base.GValue | |
TypedObject GValue Source # | |
HasParentTypes GValue Source # | |
Defined in Data.GI.Base.GValue | |
type ParentTypes GValue Source # | There are no types in the bindings that a |
Defined in Data.GI.Base.GValue |
fromGValue :: (IsGValue a, MonadIO m) => GValue -> m a Source #
Create a Haskell object out of the given GValue
.
toGValue :: (IsGValue a, MonadIO m) => a -> m GValue Source #
Create a GValue
from the given Haskell value.
class IsGValue a where Source #
Class for types that can be marshaled back and forth between
Haskell values and GValue
s. These are low-level methods, you
might want to use toGValue
and fromGValue
instead for a higher
level interface.
Methods
Instances
module Data.GI.Base.GVariant
module Data.GI.Base.ManagedPtr
on :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> ((?self :: object) => HaskellCallbackType info) -> m SignalHandlerId Source #
Connect a signal to a signal handler.
after :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> ((?self :: object) => HaskellCallbackType info) -> m SignalHandlerId Source #
Connect a signal to a handler, running the handler after the default one.
data SignalProxy object info where Source #
Support for overloaded signal connectors.
Constructors
(:::) :: forall object info. SignalProxy object info -> Text -> SignalProxy object info | A signal connector annotated with a detail. |
PropertyNotify :: forall info1 (propName :: Symbol) object (pl :: Symbol). (info1 ~ ResolveAttribute propName object, AttrInfo info1, pl ~ AttrLabel info1, KnownSymbol pl) => AttrLabelProxy propName -> SignalProxy object GObjectNotifySignalInfo | A signal connector for the |
Instances
info ~ ResolveSignal slot object => IsLabel slot (SignalProxy object info) Source # | Support for overloaded labels. |
Defined in Data.GI.Base.Signals Methods fromLabel :: SignalProxy object info # |
asA :: (ManagedPtrNewtype a, ManagedPtrNewtype b, HasParentTypes b, IsDescendantOf a b) => b -> (ManagedPtr a -> a) -> a Source #
Safe coercions to a parent class. For instance:
#show $ label `asA` Gtk.Widget