| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
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
- 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
 
- 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
- module Data.GI.Base.Closure
- new :: (Constructible a tag, MonadIO m) => (ManagedPtr a -> a) -> [AttrOp a tag] -> m a
- module Data.GI.Base.GError
- module Data.GI.Base.GHashTable
- new' :: (MonadIO m, GObject o) => (ManagedPtr o -> o) -> [IO (GValueConstruct o)] -> m o
- class IsGValue a where
- newtype GValue = GValue (ManagedPtr GValue)
- module Data.GI.Base.GVariant
- module Data.GI.Base.ManagedPtr
- data SignalProxy (object :: *) (info :: *) where- PropertyNotify :: (info ~ ResolveAttribute propName o, AttrInfo info, pl ~ AttrLabel info) => AttrLabelProxy propName -> SignalProxy o (GObjectNotifySignalInfo pl)
 
- 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
Documentation
data AttrOp obj (tag :: AttrOpTag) where Source #
Constructors for the different operations allowed on an attribute.
Constructors
| (:=) :: (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 | 
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
module Data.GI.Base.Closure
new :: (Constructible a tag, MonadIO m) => (ManagedPtr a -> a) -> [AttrOp a tag] -> m a Source #
module Data.GI.Base.GError
module Data.GI.Base.GHashTable
new' :: (MonadIO m, GObject o) => (ManagedPtr o -> o) -> [IO (GValueConstruct o)] -> m o Source #
class IsGValue a where Source #
A convenience class for marshaling back and forth between Haskell
 values and GValues.
Instances
Constructors
| GValue (ManagedPtr GValue) | 
module Data.GI.Base.GVariant
module Data.GI.Base.ManagedPtr
data SignalProxy (object :: *) (info :: *) where Source #
Support for overloaded signal connectors.
Constructors
| PropertyNotify :: (info ~ ResolveAttribute propName o, AttrInfo info, pl ~ AttrLabel info) => AttrLabelProxy propName -> SignalProxy o (GObjectNotifySignalInfo pl) | 
Instances
| info ~ ResolveSignal slot object => IsLabel slot (SignalProxy object info) Source # | |
| Defined in Data.GI.Base.Signals Methods fromLabel :: SignalProxy object info # | |
| info ~ ResolveSignal slot object => IsLabelProxy slot (SignalProxy object info) Source # | Support for overloaded labels. | 
| Defined in Data.GI.Base.Signals Methods fromLabelProxy :: Proxy slot -> SignalProxy object info Source # | |
on :: forall object info m. (GObject object, MonadIO m, SignalInfo info) => object -> SignalProxy object info -> HaskellCallbackType info -> m SignalHandlerId Source #
Same as connectSignal, specifying from the beginning that the
 handler is to be run before the default handler.
on object signal handler = liftIO $ connectSignal signal object handler SignalConnectBefore
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.
after object signal handler = liftIO $ connectSignal signal object handler SignalConnectAfter