Safe Haskell | None |
---|---|
Language | Haskell2010 |
Convenience header for basic GObject-Introspection modules
See the documentation for each individual module for a description and usage help.
Synopsis
- data AttrOp obj (tag :: AttrOpTag) where
- (:=) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy (attr :: Symbol) -> b -> AttrOp obj tag
- (:=>) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy (attr :: Symbol) -> IO b -> AttrOp obj tag
- (:~) :: (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 :: Symbol) -> (a -> b) -> AttrOp obj tag
- (:~>) :: (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 :: Symbol) -> (a -> IO b) -> AttrOp obj tag
- (:&=) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrTransferTypeConstraint info b, AttrSetTypeConstraint info (AttrTransferType info)) => AttrLabelProxy (attr :: Symbol) -> b -> AttrOp obj tag
- set :: forall o m. MonadIO m => o -> [AttrOp o 'AttrSet] -> m ()
- get :: forall info attr obj result m. (AttrGetC info obj attr result, MonadIO m) => obj -> AttrLabelProxy (attr :: Symbol) -> m result
- 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
- class IsGValue a where
- newtype GValue = GValue (ManagedPtr GValue)
- module Data.GI.Base.GVariant
- module Data.GI.Base.ManagedPtr
- data SignalProxy (object :: *) (info :: *) where
- (:::) :: forall o info. SignalProxy o info -> Text -> SignalProxy o info
- PropertyNotify :: (info ~ ResolveAttribute propName o, AttrInfo info, pl ~ AttrLabel info, KnownSymbol pl) => AttrLabelProxy propName -> SignalProxy o GObjectNotifySignalInfo
- on :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> HaskellCallbackType info -> m SignalHandlerId
- after :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> HaskellCallbackType info -> m SignalHandlerId
- asA :: (ManagedPtrNewtype a, ManagedPtrNewtype b, HasParentTypes b, IsDescendantOf a b) => b -> (ManagedPtr a -> a) -> a
Documentation
data AttrOp obj (tag :: AttrOpTag) where Source #
Constructors for the different operations allowed on an attribute.
(:=) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy (attr :: Symbol) -> b -> AttrOp obj tag infixr 0 | Assign a value to an attribute |
(:=>) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info b) => AttrLabelProxy (attr :: Symbol) -> IO b -> AttrOp obj tag infixr 0 | Assign the result of an IO action to an attribute |
(:~) :: (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 :: Symbol) -> (a -> b) -> AttrOp obj tag infixr 0 | Apply an update function to an attribute |
(:~>) :: (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 :: Symbol) -> (a -> IO b) -> AttrOp obj tag infixr 0 | Apply an IO update function to an attribute |
(:&=) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrTransferTypeConstraint info b, AttrSetTypeConstraint info (AttrTransferType info)) => AttrLabelProxy (attr :: Symbol) -> 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 |
set :: forall o m. MonadIO m => o -> [AttrOp o 'AttrSet] -> m () Source #
Set a number of properties for some object.
get :: forall info attr obj result m. (AttrGetC info obj attr result, MonadIO m) => obj -> AttrLabelProxy (attr :: Symbol) -> m result Source #
Get the value of an attribute for an object.
module Data.GI.Base.BasicTypes
The basic type. This corresponds to a wrapped GClosure
on the C
side, which is a boxed object.
Instances
HasParentTypes (GClosure a) Source # | |
Defined in Data.GI.Base.GClosure | |
GBoxed (GClosure a) Source # |
|
Defined in Data.GI.Base.GClosure | |
TypedObject (GClosure a) Source # | Find the associated |
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
class IsGValue a where Source #
A convenience class for marshaling back and forth between Haskell
values and GValue
s.
Instances
IsGValue Bool Source # | |
IsGValue Double Source # | |
IsGValue Float Source # | |
IsGValue Int32 Source # | |
IsGValue Int64 Source # | |
IsGValue Word32 Source # | |
IsGValue Word64 Source # | |
IsGValue CInt Source # | |
IsGValue CLong Source # | |
IsGValue CUInt Source # | |
IsGValue CULong Source # | |
IsGValue GType Source # | |
IsGValue (Maybe String) Source # | |
IsGValue (Maybe Text) Source # | |
IsGValue (StablePtr a) Source # | |
IsGValue (Ptr a) Source # | |
Haskell-side representation of a GValue
.
Instances
HasParentTypes GValue Source # | |
Defined in Data.GI.Base.GValue | |
GBoxed GValue Source # |
|
Defined in Data.GI.Base.GValue | |
TypedObject GValue Source # | |
type ParentTypes GValue Source # | There are no types in the bindings that a |
Defined in Data.GI.Base.GValue |
module Data.GI.Base.GVariant
module Data.GI.Base.ManagedPtr
data SignalProxy (object :: *) (info :: *) where Source #
Support for overloaded signal connectors.
(:::) :: forall o info. SignalProxy o info -> Text -> SignalProxy o info | A signal connector annotated with a detail. |
PropertyNotify :: (info ~ ResolveAttribute propName o, AttrInfo info, pl ~ AttrLabel info, KnownSymbol pl) => AttrLabelProxy propName -> SignalProxy o 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 fromLabel :: SignalProxy object info |
on :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> 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 -> HaskellCallbackType info -> m SignalHandlerId Source #
Connect a signal to a handler, running the handler after the default one.
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