| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.GI.Base.Signals
Description
Routines for connecting GObjects to signals. There are two
 basic variants, on and after, which correspond to
 g_signal_connect and g_signal_connect_after, respectively.
Basic usage is
 on widget #signalName $ do ...or
 after widget #signalName $ do ...Note that in the Haskell bindings we represent the signal name in camelCase, so a signal like script-message-received in the original API becomes scriptMessageReceived in the bindings.
There are two variants of note. If you want to provide a detail
 when connecting the signal you can use :::, as follows:
onwidget (#scriptMessageReceived:::"handlerName") $ do ...
On the other hand, if you want to connect to the "notify" signal for a property of a widget, it is recommended to use instead PropertyNotify, as follows:
onwidget (PropertyNotify#propertyName) $ do ...
which has the advantage that it will be checked at compile time
 that the widget does indeed have the property "propertyName".
Synopsis
- 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
- data SignalProxy (object :: *) (info :: *) where- SignalProxy :: SignalProxy o info
- (:::) :: 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
 
- data SignalConnectMode
- connectSignalFunPtr :: GObject o => o -> Text -> FunPtr a -> SignalConnectMode -> Maybe Text -> IO SignalHandlerId
- disconnectSignalHandler :: GObject o => o -> SignalHandlerId -> IO ()
- type SignalHandlerId = CULong
- class SignalInfo (info :: *) where- type HaskellCallbackType info :: *
- connectSignal :: GObject o => o -> HaskellCallbackType info -> SignalConnectMode -> Maybe Text -> IO SignalHandlerId
 
- data GObjectNotifySignalInfo
- type family SignalCodeGenError (signalName :: Symbol) :: * where ...
Documentation
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.
data SignalProxy (object :: *) (info :: *) where Source #
Support for overloaded signal connectors.
Constructors
| SignalProxy :: SignalProxy o info | A basic signal name connector. | 
| (:::) :: 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 Methods fromLabel :: SignalProxy object info | |
data SignalConnectMode Source #
Whether to connect a handler to a signal with connectSignal so
 that it runs before/after the default handler for the given signal.
Constructors
| SignalConnectBefore | Run before the default handler. | 
| SignalConnectAfter | Run after the default handler. | 
connectSignalFunPtr :: GObject o => o -> Text -> FunPtr a -> SignalConnectMode -> Maybe Text -> IO SignalHandlerId Source #
Connect a signal to a handler, given as a FunPtr.
disconnectSignalHandler :: GObject o => o -> SignalHandlerId -> IO () Source #
Disconnect a previously connected signal.
type SignalHandlerId = CULong Source #
Type of a GObject signal handler id.
class SignalInfo (info :: *) where Source #
Information about an overloaded signal.
Methods
connectSignal :: GObject o => o -> HaskellCallbackType info -> SignalConnectMode -> Maybe Text -> IO SignalHandlerId Source #
Connect a Haskell function to a signal of the given
 GObject, specifying whether the handler will be called before
 or after the default handler.
Instances
| SignalInfo GObjectNotifySignalInfo Source # | |
| Defined in Data.GI.Base.Signals Associated Types Methods connectSignal :: GObject o => o -> HaskellCallbackType GObjectNotifySignalInfo -> SignalConnectMode -> Maybe Text -> IO SignalHandlerId Source # | |
data GObjectNotifySignalInfo Source #
Connection information for a "notify" signal indicating that a
 specific property changed (see PropertyNotify for the relevant
 constructor).
Instances
| SignalInfo GObjectNotifySignalInfo Source # | |
| Defined in Data.GI.Base.Signals Associated Types Methods connectSignal :: GObject o => o -> HaskellCallbackType GObjectNotifySignalInfo -> SignalConnectMode -> Maybe Text -> IO SignalHandlerId Source # | |
| type HaskellCallbackType GObjectNotifySignalInfo Source # | |
| Defined in Data.GI.Base.Signals | |
type family SignalCodeGenError (signalName :: Symbol) :: * where ... Source #
Generate an informative type error whenever one tries to use a signal for which code generation has failed.
Equations
| SignalCodeGenError signalName = TypeError ((('Text "The signal \8216" :<>: 'Text signalName) :<>: 'Text "\8217 is not supported, because haskell-gi failed to generate appropriate bindings.") :$$: 'Text "Please file an issue at https://github.com/haskell-gi/haskell-gi/issues.") |