Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Dynamic t a
- current :: Dynamic t a -> Behavior t a
- updated :: Dynamic t a -> Event t a
- constDyn :: Reflex t => a -> Dynamic t a
- holdDyn :: MonadHold t m => a -> Event t a -> m (Dynamic t a)
- nubDyn :: (Reflex t, Eq a) => Dynamic 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)
- switchPromptlyDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a
- tagDyn :: Reflex t => Dynamic t a -> Event t b -> Event t a
- attachDyn :: Reflex t => Dynamic t a -> Event t b -> Event t (a, b)
- attachDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Event t b -> Event t c
- attachDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c
- mapDyn :: (Reflex t, MonadHold t m) => (a -> b) -> Dynamic t a -> m (Dynamic t b)
- forDyn :: (Reflex t, MonadHold t m) => Dynamic t a -> (a -> b) -> m (Dynamic t b)
- 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)
- 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)
- combineDyn :: forall t m a b c. (Reflex t, MonadHold t m) => (a -> b -> c) -> Dynamic t a -> Dynamic t b -> m (Dynamic t c)
- collectDyn :: (RebuildSortedHList (HListElems b), IsHList a, IsHList b, AllAreFunctors (Dynamic t) (HListElems b), Reflex t, MonadHold t m, HListElems a ~ FunctorList (Dynamic t) (HListElems b)) => a -> m (Dynamic t b)
- mconcatDyn :: forall t m a. (Reflex t, MonadHold t m, Monoid a) => [Dynamic t a] -> m (Dynamic t a)
- distributeDMapOverDyn :: forall t m k. (Reflex t, MonadHold t m, GCompare k) => DMap (WrapArg (Dynamic t) k) -> m (Dynamic t (DMap k))
- joinDyn :: forall t a. Reflex t => Dynamic t (Dynamic t a) -> Dynamic t a
- 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
- splitDyn :: (Reflex t, MonadHold t m) => Dynamic t (a, b) -> m (Dynamic t a, Dynamic t b)
- data Demux t k
- demux :: (Reflex t, Ord k) => Dynamic t k -> Demux t k
- getDemuxed :: (Reflex t, MonadHold t m, Eq k) => Demux t k -> k -> m (Dynamic t Bool)
- data HList l where
- data FHList f l where
- distributeFHListOverDyn :: forall t m l. (Reflex t, MonadHold t m, RebuildSortedHList l) => FHList (Dynamic t) l -> m (Dynamic t (HList l))
- unsafeDynamic :: Behavior t a -> Event t a -> Dynamic t a
Documentation
nubDyn :: (Reflex t, Eq a) => Dynamic t a -> Dynamic t a Source
Create a new Dynamic
that only signals changes if the values
actually changed.
tagDyn :: 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: `tagDyn d e` differs from `tag (current d) e` in the case that e
is firing
at the same time that d
is changing. With `tagDyn 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.
attachDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c Source
mapDyn :: (Reflex t, MonadHold t m) => (a -> b) -> Dynamic t a -> m (Dynamic t b) Source
Map a function over a Dynamic
.
forDyn :: (Reflex t, MonadHold t m) => Dynamic t a -> (a -> b) -> m (Dynamic t b) Source
Flipped version of mapDyn
.
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
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
foldDynMaybeM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe b)) -> b -> Event t a -> m (Dynamic t b) Source
combineDyn :: forall t m a b c. (Reflex t, MonadHold t m) => (a -> b -> c) -> Dynamic t a -> Dynamic t b -> m (Dynamic t c) Source
collectDyn :: (RebuildSortedHList (HListElems b), IsHList a, IsHList b, AllAreFunctors (Dynamic t) (HListElems b), Reflex t, MonadHold t m, HListElems a ~ FunctorList (Dynamic t) (HListElems b)) => a -> m (Dynamic t b) Source
mconcatDyn :: forall t m a. (Reflex t, MonadHold t m, Monoid a) => [Dynamic t a] -> m (Dynamic t a) Source
distributeDMapOverDyn :: forall t m k. (Reflex t, MonadHold t m, GCompare k) => DMap (WrapArg (Dynamic t) k) -> m (Dynamic t (DMap k)) Source
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
on each change and prefix it
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
on each change. 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.
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, > getDemuxed (demux d) k === mapDyn (== k) d However, the when getDemuxed is used multiple times, the complexity is only O(log(n)), rather than O(n) for mapDyn.
distributeFHListOverDyn :: forall t m l. (Reflex t, MonadHold t m, RebuildSortedHList l) => FHList (Dynamic t) l -> m (Dynamic t (HList l)) Source
unsafeDynamic :: Behavior t a -> Event t a -> Dynamic t a Source