reflex-gi-gtk-0.2.0.0: Helper functions to use reflex with gi-gtk
CopyrightSven Bartscher 2020
LicenseMPL-2.0
Maintainersven.bartscher@weltraumschlangen.de
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Reflex.GI.Gtk.Input

Description

This module provides helpers for constructing input Events, Behaviors, and Dynamics from GLib signals and attributes.

Synopsis

Obtaining input from GI signals

as Events

class (MonadRunGtk m, TriggerEvent t m) => MonadGtkSource t m where Source #

This class provides the creation of reactive inputs from GLib signals.

Methods

eventFromSignalWith Source #

Arguments

:: (GObject object, SignalInfo info) 
=> Registerer object info

A function to register a handler for a GLib signal. Usually on or after.

-> 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 fire that emits the constructed event with the passed value. Is also responsible for handling the arguments provided by the signal and returning an appropriate value expected by the signal.

-> m (Event t a)

An Event that is emitted whenever the GLib signal occurs — or rather whenever the passed helper function calls fire.

Turns a GLib signal into a reactive Event.

Instances

Instances details
(ReflexHost t, MonadIO (HostFrame t), MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO) => MonadGtkSource t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

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 Behaviors

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 Source #

Arguments

:: (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 :: (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 #

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 :: (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 #

as Dynamics

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 :: (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 #

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 :: (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 #

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 Source #

Arguments

:: (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 on or after.

-> 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 :: (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 :: (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.

data FireAsync Source #

A sum type to select between synchronous and asynchronous event propagation.

Constructors

FireAsync

Specify asynchronous event propagation

FireSync

Specify synchronous event propagation

Instances

Instances details
Eq FireAsync Source # 
Instance details

Defined in Reflex.GI.Gtk.Input

Read FireAsync Source # 
Instance details

Defined in Reflex.GI.Gtk.Input

Show FireAsync Source # 
Instance details

Defined in Reflex.GI.Gtk.Input

Miscellanous

type Registerer object info = object -> SignalProxy object info -> HaskellCallbackType info -> IO SignalHandlerId Source #

A shorthand for the types of on and after as required by the helpers in this module.