Copyright | Sven Bartscher 2020 |
---|---|
License | MPL-2.0 |
Maintainer | sven.bartscher@weltraumschlangen.de |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- sink :: MonadGtkSink t m => object -> [ReactiveAttrOp t object 'AttrSet] -> m ()
- sink1 :: 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
- class Functor s => Sinkable t s | s -> t where
- sinkPostBuild :: PostBuild t m => s a -> m (Event t (Maybe a))
- sinkUpdates :: Reflex t => s a -> Event t a
- toSinkEvent :: PostBuild t m => s a -> m (Event t a)
- type MonadGtkSink t m = (PerformEvent t m, PostBuild t m, MonadRunGtk (Performable m))
Documentation
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.
sink1 :: MonadGtkSink t m => object -> ReactiveAttrOp t object 'AttrSet -> m () Source #
Arranges that a given attribute is kept in sync with a reactive value on a given object, i.e.
sink1 labelWidget $
#label :== reactiveLabelText
will arrange that the attribute #label
on
labelWidget
will always be updated to the value of
reactiveLabelText
.
Essentially the single value case of sink
.
Alos see the note on sink
for updated from more than one source
to the targeted attribute.
data ReactiveAttrOp t obj (tag :: AttrOpTag) where Source #
Reactive pendant to AttrOp
.
class Functor s => Sinkable t s | s -> t where Source #
This is a typeclass for reactive values that that can give notifications about updates and thus be used to trigger actions in the real world based on those updates.
sinkPostBuild :: PostBuild t m => s a -> m (Event t (Maybe a)) Source #
Turn the reactive value into an event that fires at post build
time Just
the current value or Nothing
if no value is
available at post build time.
sinkUpdates :: Reflex t => s a -> Event t a Source #
Turn the reactive value into an event that fires the new value
whenever it is changed. This should not include sinkPostBuild
itself, though it may coincide with it, when the value changes at
post build time.
toSinkEvent :: PostBuild t m => s a -> m (Event t a) Source #
Turn the reactive value into an event that fires when the
available for the first time (possibly at post build time) and
whenever the value is replaced afterwards. This can be thought of
as a combination of sinkPostBuild
and sinkUpdates
.
Instances
Functor (Dynamic t) => Sinkable t (Dynamic t) Source # | A dynamic has a value at post build time and can be updated later. |
Defined in Reflex.GI.Gtk.Output | |
Reflex t => Sinkable t (Event t) Source # | An Event has no value available at post build time, but is updated whenever it fires. |
Defined in Reflex.GI.Gtk.Output |
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
.