reflex-0.3.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Dynamic

Synopsis

Documentation

data Dynamic t a 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.

current :: Dynamic t a -> Behavior t a Source

Extract the Behavior of a Dynamic.

updated :: Dynamic t a -> Event t a Source

Extract the Event of the Dynamic.

constDyn :: Reflex t => a -> Dynamic t a Source

Dynamic with the constant supplied value.

holdDyn :: MonadHold t m => a -> Event t a -> m (Dynamic t a) Source

Create a Dynamic using the initial value that changes every time the Event occurs.

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.

count :: (Reflex t, MonadHold t m, MonadFix m, Num b) => Event t a -> m (Dynamic t b) Source

Create a new Dynamic that counts the occurences of the Event.

toggle :: (Reflex t, MonadHold t m, MonadFix m) => Bool -> Event t a -> m (Dynamic t Bool) Source

Create a new Dynamic using the initial value that flips its value every time the Event occurs.

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.

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.

attachDyn :: 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: `attachDyn d` is not the same as `attach (current d)`. See tagDyn for details.

attachDynWith :: 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: `attachDynWith f d` is not the same as `attachWith f (current d)`. See tagDyn for details.

attachDynWithMaybe :: 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 occurence with the current value of the Dynamic value and possibly filtering if the combining function returns Nothing.

Note: `attachDynWithMaybe f d` is not the same as `attachWithMaybe f (current d)`. See tagDyn for details.

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

Map a monadic function over a Dynamic. The only monadic action that the given function can perform is sample.

foldDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> b) -> b -> Event t a -> m (Dynamic t b) Source

Create a Dynamic using the initial value and change it each time the Event occurs using a folding function on the previous value and the value of the Event.

foldDynM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t b) -> b -> Event t a -> m (Dynamic t b) Source

Create a Dynamic using the initial value and change it each time the Event occurs using a monadic folding function on the previous value and the value of the Event.

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

Merge two Dynamics into a new one using the provided function. The new Dynamic changes its value each time one of the original Dynamics changes its value.

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

Merge the Dynamic values using their Monoid instance.

distributeDMapOverDyn :: forall t m k. (Reflex t, MonadHold t m, GCompare k) => DMap (WrapArg (Dynamic t) k) -> m (Dynamic t (DMap k)) Source

Create a Dynamic with a DMap of values out of a DMap of Dynamic values.

joinDyn :: forall t a. Reflex t => Dynamic t (Dynamic t a) -> Dynamic t a Source

Join a nested Dynamic into a new Dynamic that has the value of the inner Dynamic.

joinDynThroughMap :: forall t k a. (Reflex t, Ord k) => Dynamic t (Map k (Dynamic t a)) -> Dynamic t (Map k a) Source

Combine a Dynamic of a Map of Dynamics into a Dynamic with the current values of the Dynamics in a map.

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.

splitDyn :: (Reflex t, MonadHold t m) => Dynamic t (a, b) -> m (Dynamic t a, Dynamic t b) Source

Split the Dynamic into two Dynamics, each taking the respective value of the tuple.

data Demux t k Source

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.

demux :: (Reflex t, Ord k) => Dynamic t k -> Demux t k Source

Demultiplex an input value to a Demux with many outputs. At any given time, whichever output is indicated by the given Dynamic will be True.

getDemuxed :: (Reflex t, MonadHold t m, Eq k) => Demux t k -> k -> m (Dynamic t Bool) Source

Select a particular output of the Demux; this is equivalent to (but much faster than) mapping over the original Dynamic and checking whether it is equal to the given key.

data HList l where Source

Constructors

HNil :: HList `[]` 
HCons :: e -> HList l -> HList (e : l) infixr 2 

data FHList f l where Source

Constructors

FHNil :: FHList f `[]` 
FHCons :: f e -> FHList f l -> FHList f (e : l) 

distributeFHListOverDyn :: forall t m l. (Reflex t, MonadHold t m, RebuildSortedHList l) => FHList (Dynamic t) l -> m (Dynamic t (HList l)) Source