Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data family Dynamic t :: * -> *
- current :: Reflex t => Dynamic t a -> Behavior t a
- updated :: Reflex t => Dynamic t a -> Event t a
- holdDyn :: MonadHold t m => a -> Event t a -> m (Dynamic t a)
- mapDynM :: forall t m a b. (Reflex t, MonadHold t m) => (forall m'. MonadSample t m' => a -> m' b) -> Dynamic t a -> m (Dynamic t b)
- forDynM :: forall t m a b. (Reflex t, MonadHold t m) => Dynamic t a -> (forall m'. MonadSample t m' => a -> m' b) -> m (Dynamic t b)
- constDyn :: Reflex t => a -> Dynamic t a
- count :: (Reflex t, MonadHold t m, MonadFix m, Num b) => Event t a -> m (Dynamic t b)
- toggle :: (Reflex t, MonadHold t m, MonadFix m) => Bool -> Event t a -> m (Dynamic t Bool)
- switchDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a
- switchPromptlyDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a
- tagPromptlyDyn :: Reflex t => Dynamic t a -> Event t b -> Event t a
- attachPromptlyDyn :: Reflex t => Dynamic t a -> Event t b -> Event t (a, b)
- attachPromptlyDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Event t b -> Event t c
- attachPromptlyDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c
- maybeDyn :: forall t a m. (Reflex t, MonadFix m, MonadHold t m) => Dynamic t (Maybe a) -> m (Dynamic t (Maybe (Dynamic t a)))
- eitherDyn :: forall t a b m. (Reflex t, MonadFix m, MonadHold t m) => Dynamic t (Either a b) -> m (Dynamic t (Either (Dynamic t a) (Dynamic t b)))
- factorDyn :: forall t m k v. (Reflex t, MonadHold t m, GEq k) => Dynamic t (DSum k v) -> m (Dynamic t (DSum k (Compose (Dynamic t) v)))
- scanDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b) -> (a -> b -> b) -> Dynamic t a -> m (Dynamic t b)
- scanDynMaybe :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b) -> (a -> b -> Maybe b) -> Dynamic t a -> m (Dynamic t b)
- holdUniqDyn :: (Reflex t, MonadHold t m, MonadFix m, Eq a) => Dynamic t a -> m (Dynamic t a)
- holdUniqDynBy :: (Reflex t, MonadHold t m, MonadFix m) => (a -> a -> Bool) -> Dynamic t a -> m (Dynamic t a)
- improvingMaybe :: (Reflex t, MonadHold t m, MonadFix m) => Dynamic t (Maybe a) -> m (Dynamic t (Maybe a))
- foldDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> b) -> b -> Event t a -> m (Dynamic t b)
- foldDynM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t b) -> b -> Event t a -> m (Dynamic t b)
- foldDynMaybe :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> Maybe b) -> b -> Event t a -> m (Dynamic t b)
- foldDynMaybeM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe b)) -> b -> Event t a -> m (Dynamic t b)
- joinDynThroughMap :: forall t k a. (Reflex t, Ord k) => Dynamic t (Map k (Dynamic t a)) -> Dynamic t (Map k a)
- traceDyn :: (Reflex t, Show a) => String -> Dynamic t a -> Dynamic t a
- traceDynWith :: Reflex t => (a -> String) -> Dynamic t a -> Dynamic t a
- splitDynPure :: Reflex t => Dynamic t (a, b) -> (Dynamic t a, Dynamic t b)
- distributeMapOverDynPure :: (Reflex t, Ord k) => Map k (Dynamic t v) -> Dynamic t (Map k v)
- distributeDMapOverDynPure :: forall t k. (Reflex t, GCompare k) => DMap k (Dynamic t) -> Dynamic t (DMap k Identity)
- distributeListOverDynPure :: Reflex t => [Dynamic t v] -> Dynamic t [v]
- data Demux t k
- demux :: (Reflex t, Ord k) => Dynamic t k -> Demux t k
- demuxed :: (Reflex t, Eq k) => Demux t k -> k -> Dynamic t Bool
- data HList (l :: [*]) where
- data FHList f l where
- collectDynPure :: (RebuildSortedHList (HListElems b), IsHList a, IsHList b, AllAreFunctors (Dynamic t) (HListElems b), Reflex t, HListElems a ~ FunctorList (Dynamic t) (HListElems b)) => a -> Dynamic t b
- class RebuildSortedHList l where
- rebuildSortedFHList :: [DSum (HListPtr l) f] -> FHList f l
- rebuildSortedHList :: [DSum (HListPtr l) Identity] -> HList l
- class IsHList a where
- type HListElems a :: [*]
- toHList :: a -> HList (HListElems a)
- fromHList :: HList (HListElems a) -> a
- class AllAreFunctors (f :: a -> *) (l :: [a]) where
- type FunctorList f l :: [*]
- toFHList :: HList (FunctorList f l) -> FHList f l
- fromFHList :: FHList f l -> HList (FunctorList f l)
- data HListPtr l a where
- distributeFHListOverDynPure :: (Reflex t, RebuildSortedHList l) => FHList (Dynamic t) l -> Dynamic t (HList l)
- unsafeDynamic :: Reflex t => Behavior t a -> Event t a -> Dynamic t a
Basics
data family Dynamic t :: * -> * Source #
A container for a value that can change over time and allows
notifications on changes. Basically a combination of a Behavior
and an
Event
, with a rule that the Behavior
will change if and only if the
Event
fires.
Instances
mapDynM :: forall t m a b. (Reflex t, MonadHold t m) => (forall m'. MonadSample t m' => a -> m' b) -> Dynamic t a -> m (Dynamic t b) Source #
Map a sampling function over a Dynamic
.
forDynM :: forall t m a b. (Reflex t, MonadHold t m) => Dynamic t a -> (forall m'. MonadSample t m' => a -> m' b) -> m (Dynamic t b) Source #
Flipped version of mapDynM
switchDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a Source #
Switches to the new Event
whenever it receives one. Only the old event is
considered the moment a new one is switched in; the output event will fire at
that moment if only if the old event does.
Prefer this to switchPromptlyDyn
where possible. The lack of doing double
work when the outer and (new) inner fires means this imposes fewer "timing
requirements" and thus is far more easy to use without introducing fresh
failure cases. switchDyn
is also more performant.
switchPromptlyDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a Source #
Switches to the new Event
whenever it receives one. Switching occurs
before the inner Event
fires - so if the Dynamic
changes and both the
old and new inner Events fire simultaneously, the output will fire with the
value of the new Event
.
Prefer switchDyn
to this where possible. The timing requirements that
switching before imposes are likely to bring down your app unless you are
very careful. switchDyn
is also more performant.
tagPromptlyDyn :: Reflex t => Dynamic t a -> Event t b -> Event t a Source #
Replace the value of the Event
with the current value of the Dynamic
each time the Event
occurs.
Note: tagPromptlyDyn d e
differs from tag (current d) e
in the case that e
is firing
at the same time that d
is changing. With tagPromptlyDyn d e
, the new value of d
will replace the value of e
, whereas with tag (current d) e
, the old value
will be used, since the Behavior
won't be updated until the end of the frame.
Additionally, this means that the output Event
may not be used to directly change
the input Dynamic
, because that would mean its value depends on itself. When creating
cyclic data flows, generally tag (current d) e
is preferred.
attachPromptlyDyn :: Reflex t => Dynamic t a -> Event t b -> Event t (a, b) Source #
Attach the current value of the Dynamic
to the value of the
Event
each time it occurs.
Note: attachPromptlyDyn d
is not the same as attach (current d)
. See tagPromptlyDyn
for details.
attachPromptlyDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Event t b -> Event t c Source #
Combine the current value of the Dynamic
with the value of the
Event
each time it occurs.
Note: attachPromptlyDynWith f d
is not the same as attachWith f (current d)
. See tagPromptlyDyn
for details.
attachPromptlyDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c Source #
Create a new Event
by combining the value at each occurrence with the
current value of the Dynamic
value and possibly filtering if the combining
function returns Nothing
.
Note: attachPromptlyDynWithMaybe f d
is not the same as attachWithMaybe f (current d)
. See tagPromptlyDyn
for details.
maybeDyn :: forall t a m. (Reflex t, MonadFix m, MonadHold t m) => Dynamic t (Maybe a) -> m (Dynamic t (Maybe (Dynamic t a))) Source #
Factor a Dynamic t (Maybe a)
into a Dynamic t (Maybe (Dynamic t a))
,
such that the outer Dynamic
is updated only when the Maybe's constructor
chages from Nothing
to Just
or vice-versa. Whenever the constructor
becomes Just
, an inner Dynamic
will be provided, whose value will track
the a
inside the Just
; when the constructor becomes Nothing
, the
existing inner Dynamic
will become constant, and will not change when the
outer constructor changes back to Nothing
.
eitherDyn :: forall t a b m. (Reflex t, MonadFix m, MonadHold t m) => Dynamic t (Either a b) -> m (Dynamic t (Either (Dynamic t a) (Dynamic t b))) Source #
factorDyn :: forall t m k v. (Reflex t, MonadHold t m, GEq k) => Dynamic t (DSum k v) -> m (Dynamic t (DSum k (Compose (Dynamic t) v))) Source #
scanDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b) -> (a -> b -> b) -> Dynamic t a -> m (Dynamic t b) Source #
scanDynMaybe :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b) -> (a -> b -> Maybe b) -> Dynamic t a -> m (Dynamic t b) Source #
Like scanDyn
, but the the accumulator function may decline to update the
result Dynamic'
s value.
holdUniqDyn :: (Reflex t, MonadHold t m, MonadFix m, Eq a) => Dynamic t a -> m (Dynamic t a) Source #
Create a new Dynamic
that only signals changes if the values actually
changed.
holdUniqDynBy :: (Reflex t, MonadHold t m, MonadFix m) => (a -> a -> Bool) -> Dynamic t a -> m (Dynamic t a) Source #
improvingMaybe :: (Reflex t, MonadHold t m, MonadFix m) => Dynamic t (Maybe a) -> m (Dynamic t (Maybe a)) Source #
Dynamic Maybe
that can only update from Nothing
to Just
or Just
to Just
(i.e., cannot revert to Nothing
)
foldDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> b) -> b -> Event t a -> m (Dynamic t b) Source #
foldDynM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t b) -> b -> Event t a -> m (Dynamic t b) Source #
foldDynMaybe :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> Maybe b) -> b -> Event t a -> m (Dynamic t b) Source #
Create a Dynamic
using the provided initial value and change it each time
the provided Event
occurs, using a function to combine the old value with
the Event'
s value. If the function returns Nothing
, the value is not
changed; this is distinct from returning Just
the old value, since the
Dynamic'
s updated
Event
will fire in the Just
case, and will not fire
in the Nothing
case.
foldDynMaybeM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe b)) -> b -> Event t a -> m (Dynamic t b) Source #
Like foldDynMaybe
, but the combining function is a PushM
action, so it
can sample
existing Behaviors
and hold
new ones.
joinDynThroughMap :: forall t k a. (Reflex t, Ord k) => Dynamic t (Map k (Dynamic t a)) -> Dynamic t (Map k a) Source #
traceDyn :: (Reflex t, Show a) => String -> Dynamic t a -> Dynamic t a Source #
Print the value of the Dynamic
when it is first read and on each
subsequent change that is observed (as traceEvent
), prefixed with the
provided string. This should only be used for debugging.
Note: Just like Debug.Trace.trace, the value will only be shown if something else in the system is depending on it.
traceDynWith :: Reflex t => (a -> String) -> Dynamic t a -> Dynamic t a Source #
Print the result of applying the provided function to the value
of the Dynamic
when it is first read and on each subsequent change
that is observed (as traceEvent
). This should only be used for
debugging.
Note: Just like Debug.Trace.trace, the value will only be shown if something else in the system is depending on it.
distributeMapOverDynPure :: (Reflex t, Ord k) => Map k (Dynamic t v) -> Dynamic t (Map k v) Source #
distributeDMapOverDynPure :: forall t k. (Reflex t, GCompare k) => DMap k (Dynamic t) -> Dynamic t (DMap k Identity) Source #
This function converts a DMap
whose elements are Dynamic
s into a
Dynamic
DMap
. Its implementation is more efficient than doing the same
through the use of multiple uses of zipDynWith
or Applicative
operators.
distributeListOverDynPure :: Reflex t => [Dynamic t v] -> Dynamic t [v] Source #
Deprecated: Use distributeListOverDyn
instead
Convert a list with Dynamic
elements into a Dynamic
of a list with
non-Dynamic
elements, preserving the order of the elements.
Represents a time changing value together with an EventSelector
that can
efficiently detect when the underlying Dynamic
has a particular value.
This is useful for representing data like the current selection of a long
list.
Semantically,
demuxed (demux d) k === fmap (== k) d
However, when getDemuxed is used multiple times, the complexity is only O(log(n)), rather than O(n) for fmap.
Miscellaneous
data HList (l :: [*]) where Source #
A heterogeneous list whose type and length are fixed statically. This is
reproduced from the HList
package due to integration issues, and because
very little other functionality from that library is needed.
collectDynPure :: (RebuildSortedHList (HListElems b), IsHList a, IsHList b, AllAreFunctors (Dynamic t) (HListElems b), Reflex t, HListElems a ~ FunctorList (Dynamic t) (HListElems b)) => a -> Dynamic t b Source #
class RebuildSortedHList l where Source #
This class allows HList
s and FHlist
s to be built from regular lists;
they must be contiguous and sorted.
rebuildSortedFHList :: [DSum (HListPtr l) f] -> FHList f l Source #
rebuildSortedHList :: [DSum (HListPtr l) Identity] -> HList l Source #
Instances
RebuildSortedHList ([] :: [Type]) Source # | |
Defined in Reflex.Dynamic | |
RebuildSortedHList t => RebuildSortedHList (h ': t) Source # | |
Defined in Reflex.Dynamic |
class IsHList a where Source #
Poor man's Generic
s for product types only.
type HListElems a :: [*] Source #
toHList :: a -> HList (HListElems a) Source #
fromHList :: HList (HListElems a) -> a Source #
Instances
IsHList (a, b) Source # | |
Defined in Reflex.Dynamic type HListElems (a, b) :: [Type] Source # toHList :: (a, b) -> HList (HListElems (a, b)) Source # fromHList :: HList (HListElems (a, b)) -> (a, b) Source # | |
IsHList (a, b, c, d) Source # | |
Defined in Reflex.Dynamic type HListElems (a, b, c, d) :: [Type] Source # toHList :: (a, b, c, d) -> HList (HListElems (a, b, c, d)) Source # fromHList :: HList (HListElems (a, b, c, d)) -> (a, b, c, d) Source # | |
IsHList (a, b, c, d, e, f) Source # | |
Defined in Reflex.Dynamic type HListElems (a, b, c, d, e, f) :: [Type] Source # toHList :: (a, b, c, d, e, f) -> HList (HListElems (a, b, c, d, e, f)) Source # fromHList :: HList (HListElems (a, b, c, d, e, f)) -> (a, b, c, d, e, f) Source # |
class AllAreFunctors (f :: a -> *) (l :: [a]) where Source #
Indicates that all elements in a type-level list are applications of the same functor.
type FunctorList f l :: [*] Source #
toFHList :: HList (FunctorList f l) -> FHList f l Source #
fromFHList :: FHList f l -> HList (FunctorList f l) Source #
Instances
AllAreFunctors (f :: a -> Type) ([] :: [a]) Source # | |
Defined in Reflex.Dynamic type FunctorList f [] :: [Type] Source # toFHList :: HList (FunctorList f []) -> FHList f [] Source # fromFHList :: FHList f [] -> HList (FunctorList f []) Source # | |
AllAreFunctors f t => AllAreFunctors (f :: a -> Type) (h ': t :: [a]) Source # | |
Defined in Reflex.Dynamic type FunctorList f (h ': t) :: [Type] Source # toFHList :: HList (FunctorList f (h ': t)) -> FHList f (h ': t) Source # fromFHList :: FHList f (h ': t) -> HList (FunctorList f (h ': t)) Source # |
data HListPtr l a where Source #
A typed index into a typed heterogeneous list.
Instances
GCompare (HListPtr l :: k -> Type) Source # | |
GEq (HListPtr l :: k -> Type) Source # | |
Eq (HListPtr l a2) Source # | |
Ord (HListPtr l a2) Source # | |
Defined in Reflex.Dynamic compare :: HListPtr l a2 -> HListPtr l a2 -> Ordering # (<) :: HListPtr l a2 -> HListPtr l a2 -> Bool # (<=) :: HListPtr l a2 -> HListPtr l a2 -> Bool # (>) :: HListPtr l a2 -> HListPtr l a2 -> Bool # (>=) :: HListPtr l a2 -> HListPtr l a2 -> Bool # |
distributeFHListOverDynPure :: (Reflex t, RebuildSortedHList l) => FHList (Dynamic t) l -> Dynamic t (HList l) Source #