| Copyright | Sven Bartscher 2020 |
|---|---|
| License | MPL-2.0 |
| Maintainer | sven.bartscher@weltraumschlangen.de |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Reflex.GI.Gtk
Description
This module provides the most important functions to create reactive interfaces using reflex and gi-gtk.
runReflexGtk provides a reflex host, i.e. the top level entry point
to start constructing your reactive network. It relies on the User
providing a Application to run. Running a GTK application
using the older init and main is currently not
supported.
Warning: While runReflexGtk provides access to
MonadIO you should be careful not to execute
GTK-related functions using liftIO. GTK
functions expect to be called from the same OS thread that GTK was
initialized in. runReflexGtk internally starts mutliple threads and
any code you write might not be run in the correct thread to execute
GTK functions. To make sure that your GTK function calls are performed
in the correct thread, use runGtk which has the same type as
liftIO and always makes sure that the lifted
IO action is run in the correct context to properly call GTK
functions.
Reactive inputs can be obtained with the help of eventOnSignal0 and
similar helpers defined in Reflex.GI.Gtk.Input. Reactive values can
be rendered as properties of widgets using sink. The submodules of
Reflex.GI.Gtk.Widget also provide specific helpers for specific
widgets, such as sinkBox or sinkBin to render dynamic widgets into
Boxes or Bins respectively.
Synopsis
- runReflexGtk :: Application -> Maybe [String] -> (forall x. HasSpiderTimeline x => ReflexGtk x ()) -> IO Int32
- type ReflexGtk x = ReflexGtkT (SpiderTimeline x) (SpiderHost x)
- type MonadReflexGtk t m = (MonadIO m, MonadFix m, MonadRunGtk m, ReflexHost t, MonadHold t m, MonadGtkSource t m, NotReady t m, TriggerEvent t m, PostBuild t m, Adjustable t m, PerformEvent t m, MonadIO (Performable m), MonadRunGtk (Performable m), MonadFix (Performable m), MonadHold t (Performable m))
- runGtk :: MonadRunGtk m => IO a -> m a
- runGtk_ :: MonadRunGtk m => IO a -> m ()
- runGtkPromise :: MonadRunGtk m => IO a -> m (m a)
- module Reflex.GI.Gtk.Input
- type MonadGtkSink t m = (PerformEvent t m, PostBuild t m, MonadRunGtk (Performable m))
- sink :: MonadGtkSink t m => object -> [ReactiveAttrOp t object 'AttrSet] -> m ()
- data ReactiveAttrOp t obj (tag :: AttrOpTag) where
- (:==) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info a, Sinkable t s) => AttrLabelProxy (attr :: Symbol) -> s a -> ReactiveAttrOp t obj tag
- (:==>) :: (HasAttributeList obj, info ~ ResolveAttribute attr obj, AttrInfo info, AttrBaseTypeConstraint info obj, AttrOpAllowed tag info obj, AttrSetTypeConstraint info a, Sinkable t s) => AttrLabelProxy (attr :: Symbol) -> s (IO a) -> ReactiveAttrOp t 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 a, a ~ AttrGetType info, Sinkable t s) => AttrLabelProxy (attr :: Symbol) -> s (a -> a) -> ReactiveAttrOp t 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 a, a ~ AttrGetType info, Sinkable t s) => AttrLabelProxy (attr :: Symbol) -> s (a -> IO a) -> ReactiveAttrOp t obj tag
- module Reflex.GI.Gtk.Widget
Running
Arguments
| :: Application | The application to run the GTK mainloop on. |
| -> Maybe [String] | The arguments to provide to |
| -> (forall x. HasSpiderTimeline x => ReflexGtk x ()) | The user-provided monadic action to set up your reactive network. |
| -> IO Int32 | The exit code as returned by |
The top-level entry point for reactive GTK applications.
You have to provide an existing Application which will run the
GTK application. applicationRun should not be called on
the Application manually, as this function expects to start the
mainloop by itself. However, apart from that, you may use the
Application as you wish, for example by setting appropriate
ApplicationFlags, binding to its signals, assigning
Windows to it or changing its attributes.
type ReflexGtk x = ReflexGtkT (SpiderTimeline x) (SpiderHost x) Source #
This is the monad that reactive GTK code is run in. Notably this
type implements MonadReflexGtk when run with
runReflexGtk.
type MonadReflexGtk t m = (MonadIO m, MonadFix m, MonadRunGtk m, ReflexHost t, MonadHold t m, MonadGtkSource t m, NotReady t m, TriggerEvent t m, PostBuild t m, Adjustable t m, PerformEvent t m, MonadIO (Performable m), MonadRunGtk (Performable m), MonadFix (Performable m), MonadHold t (Performable m)) Source #
This class declares the interface provided for use in monadic
code for constructing reactive networks. The most notable
implementation is ReflexGtk.
Executing IO in GTK context
runGtk :: MonadRunGtk m => IO a -> m a Source #
Execute the given IO action in the correct context for
calling GTK actions. This might mean executing the action in a
different thread if the current thread is not the GTK thread, but
it might also mean executing the action in the current thread if
the current thread is the GTK thread.
runGtk_ :: MonadRunGtk m => IO a -> m () Source #
Like runGtk but does not return the result of the executed
action and will not wait for the action to finish executing if it
is run in a different thread.
Note that it is not precisely specified under which circumstances
will be executed asynchronously in a different thread or
synchronously in the current thread, so you should either account
for both possibilities or use runGtk to always wait
synchronously wait for the action to finish.
runGtkPromise :: MonadRunGtk m => IO a -> m (m a) Source #
Like runGtk but does not wait for the IO action to finish
executing. Instead it returns another monadic action that waits
for the action to finish and returns its result.
Note that just as with runGtk_ it is not exactly specified
under which circumstances the action will be run asynchronously
or synchronously. You should either account for both cases or use
runGtk to always wait for the action to finish.
Obtaining input from GTK sources
module Reflex.GI.Gtk.Input
Outputting reactive values to GTK widgets
type MonadGtkSink t m = (PerformEvent t m, PostBuild t m, MonadRunGtk (Performable m)) Source #
This constraint is necessary for output operations to GTK
widgets. Note that it is a subclass of
MonadReflexGtk and implemented by
ReflexGtk.
sink :: MonadGtkSink t m => object -> [ReactiveAttrOp t object 'AttrSet] -> m () Source #
A reactive version of set.
For example
sink object [attr2 :== attr2Event]
Will arrange that #attr1 is updated to the current value of
attr1Dynamic whenever it is updated, just as #attr2 will always
be updated to the value of attr2Event whenever it fires.
When a single attribute is changed by multiple sources, (such as
different calls to sink, sink1, specifying the same attribute
multiple times in the same call to sink, or manual updates
through set) the most recent update wins (until a newer update
occurs). However, you should generally not rely on this and instead
make sure that at most one call to sink or sink1 targets the
same attribute.
data ReactiveAttrOp t obj (tag :: AttrOpTag) where Source #
Reactive pendant to AttrOp.
Constructors
Helpers for specific widgets
module Reflex.GI.Gtk.Widget