Copyright | Sven Bartscher 2020 |
---|---|
License | MPL-2.0 |
Maintainer | sven.bartscher@weltraumschlangen.de |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class (MonadRunGtk m, TriggerEvent t m) => MonadGtkSource t m where
- eventFromSignalWith :: (GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Event t a)
- eventOnSignal :: (MonadGtkSource t m, GObject object, SignalInfo info) => object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Event t a)
- eventOnSignal0 :: (MonadGtkSource t m, HaskellCallbackType info ~ IO (), GObject object, SignalInfo info) => object -> SignalProxy object info -> m (Event t ())
- eventFromSignalWith0 :: (MonadGtkSource t m, GObject object, SignalInfo info, HaskellCallbackType info ~ IO ()) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> m (Event t ())
- eventOnSignal1 :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => object -> SignalProxy object info -> m (Event t a)
- eventFromSignalWith1 :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> m (Event t a)
- eventOnSignal0R :: (MonadGtkSource t m, HaskellCallbackType info ~ IO b, GObject object, SignalInfo info) => object -> SignalProxy object info -> b -> m (Event t ())
- eventFromSignalWith0R :: (MonadGtkSource t m, HaskellCallbackType info ~ IO b, GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> b -> m (Event t ())
- eventOnSignal1R :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => object -> SignalProxy object info -> b -> m (Event t a)
- eventFromSignalWith1R :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> b -> m (Event t a)
- behaviorOnSignal :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Behavior t a)
- behaviorFromSignalWith :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Behavior t a)
- behaviorOnSignal1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> m (Behavior t a)
- behaviorFromSignalWith1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> m (Behavior t a)
- behaviorOnSignal1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> b -> m (Behavior t a)
- behaviorFromSignalWith1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> b -> m (Behavior t a)
- dynamicOnSignal :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Dynamic t a)
- dynamicFromSignalWith :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Dynamic t a)
- dynamicOnSignal1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> m (Dynamic t a)
- dynamicFromSignalWith1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> m (Dynamic t a)
- dynamicOnSignal1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> b -> m (Dynamic t a)
- dynamicFromSignalWith1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> b -> m (Dynamic t a)
- eventOnAttribute :: (MonadGtkSource t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => object -> AttrLabelProxy attr -> m (Event t value)
- eventFromAttributeWith :: (MonadGtkSource t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => Registerer object GObjectNotifySignalInfo -> FireAsync -> object -> AttrLabelProxy attr -> m (Event t value)
- behaviorOnAttribute :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => object -> AttrLabelProxy attr -> m (Behavior t value)
- behaviorFromAttributeWith :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => Registerer object GObjectNotifySignalInfo -> FireAsync -> object -> AttrLabelProxy attr -> m (Behavior t value)
- dynamicOnAttribute :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => object -> AttrLabelProxy attr -> m (Dynamic t value)
- dynamicFromAttributeWith :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => Registerer object GObjectNotifySignalInfo -> FireAsync -> object -> AttrLabelProxy attr -> m (Dynamic t value)
- data FireAsync
- type Registerer object info = object -> SignalProxy object info -> HaskellCallbackType info -> IO SignalHandlerId
Obtaining input from GI signals
as Event
s
class (MonadRunGtk m, TriggerEvent t m) => MonadGtkSource t m where Source #
This class provides the creation of reactive inputs from GLib signals.
:: (GObject object, SignalInfo info) | |
=> Registerer object info | A function to
register a handler for a GLib
signal. Usually |
-> FireAsync | Whether to fire the event synchronously or asynchronously. See Synchronous vs asynchronous event triggers for a more in-depth explanation. |
-> object | The object emitting the signal |
-> SignalProxy object info | The signal to bind to |
-> ((a -> IO ()) -> HaskellCallbackType info) | A helper function that is called in the
handler of the signal. It receives an
operation |
-> m (Event t a) | An |
Turns a GLib signal into a reactive Event
.
Instances
(ReflexHost t, MonadIO (HostFrame t), MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO) => MonadGtkSource t (ReflexGtkT t m) Source # | |
Defined in Reflex.GI.Gtk.Host eventFromSignalWith :: (GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> ReflexGtkT t m (Event t a) Source # |
eventOnSignal :: (MonadGtkSource t m, GObject object, SignalInfo info) => object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Event t a) Source #
eventFromSignalWith
pre-applied to on
and FireSync
eventOnSignal0 :: (MonadGtkSource t m, HaskellCallbackType info ~ IO (), GObject object, SignalInfo info) => object -> SignalProxy object info -> m (Event t ()) Source #
eventFromSignalWith0
pre-applied to on
and FireSync
eventFromSignalWith0 :: (MonadGtkSource t m, GObject object, SignalInfo info, HaskellCallbackType info ~ IO ()) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> m (Event t ()) Source #
A specialization of eventFromSignalWith
for signal handlers
without arguments or return types.
eventOnSignal1 :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => object -> SignalProxy object info -> m (Event t a) Source #
eventFromSignalWith1
pre-applied to on
and FireSync
eventFromSignalWith1 :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> m (Event t a) Source #
A specialization of eventFromSignalWith
for signal handlers
with exactly one argument and no return type. The argument is used
as a value for the emitted Event
.
eventOnSignal0R :: (MonadGtkSource t m, HaskellCallbackType info ~ IO b, GObject object, SignalInfo info) => object -> SignalProxy object info -> b -> m (Event t ()) Source #
eventFromSignalWith0R
pre-applied to on
and FireSync
eventFromSignalWith0R :: (MonadGtkSource t m, HaskellCallbackType info ~ IO b, GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> b -> m (Event t ()) Source #
A specialization of eventFromSignalWith
for signal handlers
with no arguments and an expected return type. The bound signal
handler will returns the supplied constant value.
eventOnSignal1R :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => object -> SignalProxy object info -> b -> m (Event t a) Source #
eventFromSignalWith1R
pre-applied to on
and FireSync
eventFromSignalWith1R :: (MonadGtkSource t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> b -> m (Event t a) Source #
A specialized version of eventFromSignalWith
for signal
handlers with exactly one argument and an expected return type. The
bound signal handler will always return the supplied constant value
and the argument will be used as a value for the emitted event.
as Behavior
s
behaviorOnSignal :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Behavior t a) Source #
behaviorFromSignalWith
pre-applied to on
and FireSync
behaviorFromSignalWith Source #
:: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) | |
=> Registerer object info | |
-> FireAsync | |
-> a | The initial value |
-> object | |
-> SignalProxy object info | |
-> ((a -> IO ()) -> HaskellCallbackType info) | |
-> m (Behavior t a) |
A shorthand to create an input event with eventFromSignalWith
and
hold
the resulting event using the provided initial value.
behaviorOnSignal1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> m (Behavior t a) Source #
behaviorFromSignalWith1
pre-applied to on
and FireSync
behaviorFromSignalWith1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> m (Behavior t a) Source #
behaviorFromSignalWith
but specialized like
eventFromSignalWith1
behaviorOnSignal1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> b -> m (Behavior t a) Source #
behaviorFromSignalWith1R
pre-applied to on
and FireSync
behaviorFromSignalWith1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> b -> m (Behavior t a) Source #
behaviorFromSignalWith
but specialized like
eventFromSignalWith1R
as Dynamic
s
dynamicOnSignal :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Dynamic t a) Source #
dynamicFromSignalWith
pre-applied to on
and FireSync
dynamicFromSignalWith :: (MonadGtkSource t m, MonadHold t m, GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> m (Dynamic t a) Source #
A shorthand to create an input event with eventFromSignalWith
and
holdDyn
the resulting event using the provided initial value.
dynamicOnSignal1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> m (Dynamic t a) Source #
dynamicFromSignalWith1
pre-applied to on
and FireSync
dynamicFromSignalWith1 :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO ()), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> m (Dynamic t a) Source #
dynamicFromSignalWith
but specialized like
eventFromSignalWith1
dynamicOnSignal1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => a -> object -> SignalProxy object info -> b -> m (Dynamic t a) Source #
dynamicFromSignalWith1R
pre-applied to on
and FireSync
dynamicFromSignalWith1R :: (MonadGtkSource t m, MonadHold t m, HaskellCallbackType info ~ (a -> IO b), GObject object, SignalInfo info) => Registerer object info -> FireAsync -> a -> object -> SignalProxy object info -> b -> m (Dynamic t a) Source #
dynamicFromSignalWith
but specialized like
eventFromSignalWith1R
Obtaining input from GI attributes
eventOnAttribute :: (MonadGtkSource t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => object -> AttrLabelProxy attr -> m (Event t value) Source #
eventFromAttributeWith
pre-applied to on
and FireSync
eventFromAttributeWith Source #
:: (MonadGtkSource t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) | |
=> Registerer object GObjectNotifySignalInfo | The function used to register the
signal handler, usually either |
-> FireAsync | synchronous or asynchronous signal emission |
-> object | The object the attribute belongs to |
-> AttrLabelProxy attr | The attribute to watch |
-> m (Event t value) | The signal that emits new values of the attribute |
Construct an input Event
that fires whenever a given attribute
changes.
behaviorOnAttribute :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => object -> AttrLabelProxy attr -> m (Behavior t value) Source #
behaviorFromAttributeWith
pre-applied to on
and FireSync
behaviorFromAttributeWith :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => Registerer object GObjectNotifySignalInfo -> FireAsync -> object -> AttrLabelProxy attr -> m (Behavior t value) Source #
A shorthand to construct an input Event
using
eventFromAttributeWith
and hold
it with the current value of
the attribute as the initial value.
This means that the constructed Behavior
always has the same
value as the attribute.
dynamicOnAttribute :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => object -> AttrLabelProxy attr -> m (Dynamic t value) Source #
dynamicFromAttributeWith
pre-applied to on
and FireSync
dynamicFromAttributeWith :: (MonadGtkSource t m, MonadHold t m, AttrGetC info object attr value, GObject object, KnownSymbol (AttrLabel info)) => Registerer object GObjectNotifySignalInfo -> FireAsync -> object -> AttrLabelProxy attr -> m (Dynamic t value) Source #
Like behaviorFromAttributeWith
but constructs a Dynamic
instead of a Behavior
Synchronous vs asynchronous event triggers
When a signal is emitted by GTK the main loop of GTK is not able to run until the handler(s) for the signal have returned. During this time, the GUI becomes unresponsive. This prevents the user from interacting with the GUI and may cause certain operating systems to display a warning to the user if the GUI stays unresponsive for too long.
This may or may or may not be desirable depending on the signal being handled and the actions taken in response to the signal. So depending on the circumstances it may be appropriate to carry out all actions triggered by a signal synchronously in the signal handler before it returns, while for other actions it may be more appropriate to trigger the effects of the action to be applied asynchronously (in another thread) and return from the signal handler as soon as possible.
Usually actions that can be carried out quickly and are expected to show an effect immediately by the user should be handled synchronously, because this provides a relatively intuitive indication to the user that work is still being done in the rare case that the action is not as immediate as intended. This indication usually comes in the form of the GUI being marked as unresponsive and for example the pressed button still displaying the pressed animation.
Actions that trigger long running processes on the other hand should usually be handled asynchronously, so the user is not left with an unresponsive GUI for an extended period of time. However, this is usually also more elaborate to implement, because the user should still have an indicator that there is still progress being made on the requested action.
The helpers defined in this module can be parametrized to bind
either synchronous signal handlers that wait for the event
propagation to fully complete or asynchronous handlers that just
mark the signal propagation to be handled later and return as soon
as possible. The shorthand versions *OnSignal*
bind synchronous
handlers, while the more general variants *FromSignalWith*
support both synchronous and asynchronous handlers.
A sum type to select between synchronous and asynchronous event propagation.
Miscellanous
type Registerer object info = object -> SignalProxy object info -> HaskellCallbackType info -> IO SignalHandlerId Source #