reflex-0.5.0.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Dynamic

Contents

Description

This module contains various functions for working with Dynamic values. Dynamic and its primitives have been moved to the Reflex class.

Synopsis

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
Reflex t => Accumulator (t :: k) (Dynamic t) Source # 
Instance details

Defined in Reflex.Class

Methods

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

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

accumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> Maybe a) -> a -> Event t b -> m (Dynamic t a) Source #

accumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a)) -> a -> Event t b -> m (Dynamic t a) Source #

mapAccum :: (MonadHold t m, MonadFix m) => (a -> b -> (a, c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

mapAccumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (a, c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

mapAccumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> (Maybe a, Maybe c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

mapAccumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

Monad (Dynamic (Pure t)) Source # 
Instance details

Defined in Reflex.Pure

Methods

(>>=) :: Dynamic (Pure t) a -> (a -> Dynamic (Pure t) b) -> Dynamic (Pure t) b #

(>>) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) b #

return :: a -> Dynamic (Pure t) a #

fail :: String -> Dynamic (Pure t) a #

Monad (Dynamic t) => Monad (Dynamic (ProfiledTimeline t)) Source # 
Instance details

Defined in Reflex.Profiled

HasSpiderTimeline x => Monad (Dynamic (SpiderTimeline x)) Source # 
Instance details

Defined in Reflex.Spider.Internal

Functor (Dynamic (Pure t)) Source # 
Instance details

Defined in Reflex.Pure

Methods

fmap :: (a -> b) -> Dynamic (Pure t) a -> Dynamic (Pure t) b #

(<$) :: a -> Dynamic (Pure t) b -> Dynamic (Pure t) a #

Functor (Dynamic t) => Functor (Dynamic (ProfiledTimeline t)) Source # 
Instance details

Defined in Reflex.Profiled

Methods

fmap :: (a -> b) -> Dynamic (ProfiledTimeline t) a -> Dynamic (ProfiledTimeline t) b #

(<$) :: a -> Dynamic (ProfiledTimeline t) b -> Dynamic (ProfiledTimeline t) a #

HasSpiderTimeline x => Functor (Dynamic (SpiderTimeline x)) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

fmap :: (a -> b) -> Dynamic (SpiderTimeline x) a -> Dynamic (SpiderTimeline x) b #

(<$) :: a -> Dynamic (SpiderTimeline x) b -> Dynamic (SpiderTimeline x) a #

Applicative (Dynamic (Pure t)) Source # 
Instance details

Defined in Reflex.Pure

Methods

pure :: a -> Dynamic (Pure t) a #

(<*>) :: Dynamic (Pure t) (a -> b) -> Dynamic (Pure t) a -> Dynamic (Pure t) b #

liftA2 :: (a -> b -> c) -> Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) c #

(*>) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) b #

(<*) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) a #

Applicative (Dynamic t) => Applicative (Dynamic (ProfiledTimeline t)) Source # 
Instance details

Defined in Reflex.Profiled

HasSpiderTimeline x => Applicative (Dynamic (SpiderTimeline x)) Source # 
Instance details

Defined in Reflex.Spider.Internal

(Reflex t, IsString a) => IsString (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

fromString :: String -> Dynamic t a #

(Reflex t, Semigroup a) => Semigroup (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(<>) :: Dynamic t a -> Dynamic t a -> Dynamic t a #

sconcat :: NonEmpty (Dynamic t a) -> Dynamic t a #

stimes :: Integral b => b -> Dynamic t a -> Dynamic t a #

(Reflex t, Monoid a) => Monoid (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

mempty :: Dynamic t a #

mappend :: Dynamic t a -> Dynamic t a -> Dynamic t a #

mconcat :: [Dynamic t a] -> Dynamic t a #

(Reflex t, Default a) => Default (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

def :: Dynamic t a #

newtype Dynamic (Pure t :: Type) a Source # 
Instance details

Defined in Reflex.Pure

newtype Dynamic (Pure t :: Type) a = Dynamic {}
newtype Dynamic (ProfiledTimeline t :: Type) a Source # 
Instance details

Defined in Reflex.Profiled

newtype Dynamic (SpiderTimeline x :: Type) a Source # 
Instance details

Defined in Reflex.Spider.Internal

current :: Reflex t => Dynamic t a -> Behavior t a Source #

Extract the Behavior of a Dynamic.

updated :: Reflex t => Dynamic t a -> Event t a Source #

Extract the Event of the Dynamic.

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

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

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

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

Construct a Dynamic value that never changes

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 occurrences 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.

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 #

Create a Dynamic that accumulates values from another Dynamic. This function does not force its input Dynamic until the output Dynamic is forced.

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 #

Create a new Dynamic that changes only when the underlying Dynamic changes and the given function returns False when given both the old and the new values.

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 #

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 #

Like foldDyn, but the combining function is a PushM action, so it can sample existing Behaviors and hold new ones.

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 #

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 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.

splitDynPure :: Reflex t => Dynamic t (a, b) -> (Dynamic t a, Dynamic t b) Source #

Split a Dynamic pair into a pair of Dynamics

distributeMapOverDynPure :: (Reflex t, Ord k) => Map k (Dynamic t v) -> Dynamic t (Map k v) Source #

Convert a Map with Dynamic elements into a Dynamic of a Map with non-Dynamic elements.

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 Dynamics 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 #

Convert a list with Dynamic elements into a Dynamic of a list with non-Dynamic elements, preserving the order of the elements.

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,

demuxed (demux d) k === fmap (== k) d

However, the when getDemuxed is used multiple times, the complexity is only O(log(n)), rather than O(n) for fmap.

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.

demuxed :: (Reflex t, Eq k) => Demux t k -> k -> 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.

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.

Constructors

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

data FHList f l where Source #

Like HList, but with a functor wrapping each element.

Constructors

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

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 #

Convert a datastructure whose constituent parts are all Dynamics into a single Dynamic whose value represents all the current values of the input's consitutent Dynamics.

class RebuildSortedHList l where Source #

This class allows HLists and FHlists to be built from regular lists; they must be contiguous and sorted.

Instances
RebuildSortedHList ([] :: [Type]) Source # 
Instance details

Defined in Reflex.Dynamic

RebuildSortedHList t => RebuildSortedHList (h ': t) Source # 
Instance details

Defined in Reflex.Dynamic

Methods

rebuildSortedFHList :: [DSum (HListPtr (h ': t)) f] -> FHList f (h ': t) Source #

rebuildSortedHList :: [DSum (HListPtr (h ': t)) Identity] -> HList (h ': t) Source #

class IsHList a where Source #

Poor man's Generics for product types only.

Associated Types

type HListElems a :: [*] Source #

Instances
IsHList (a, b) Source # 
Instance details

Defined in Reflex.Dynamic

Associated Types

type HListElems (a, b) :: [Type] Source #

Methods

toHList :: (a, b) -> HList (HListElems (a, b)) Source #

fromHList :: HList (HListElems (a, b)) -> (a, b) Source #

IsHList (a, b, c, d) Source # 
Instance details

Defined in Reflex.Dynamic

Associated Types

type HListElems (a, b, c, d) :: [Type] Source #

Methods

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 # 
Instance details

Defined in Reflex.Dynamic

Associated Types

type HListElems (a, b, c, d, e, f) :: [Type] Source #

Methods

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.

Associated Types

type FunctorList f l :: [*] Source #

Instances
AllAreFunctors (f :: a -> Type) ([] :: [a]) Source # 
Instance details

Defined in Reflex.Dynamic

Associated Types

type FunctorList f [] :: [Type] Source #

Methods

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 # 
Instance details

Defined in Reflex.Dynamic

Associated Types

type FunctorList f (h ': t) :: [Type] Source #

Methods

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.

Constructors

HHeadPtr :: HListPtr (h ': t) h 
HTailPtr :: HListPtr t a -> HListPtr (h ': t) a 
Instances
GCompare (HListPtr l :: k -> Type) Source # 
Instance details

Defined in Reflex.Dynamic

Methods

gcompare :: HListPtr l a -> HListPtr l b -> GOrdering a b #

GEq (HListPtr l :: k -> Type) Source # 
Instance details

Defined in Reflex.Dynamic

Methods

geq :: HListPtr l a -> HListPtr l b -> Maybe (a := b) #

Eq (HListPtr l a2) Source # 
Instance details

Defined in Reflex.Dynamic

Methods

(==) :: HListPtr l a2 -> HListPtr l a2 -> Bool #

(/=) :: HListPtr l a2 -> HListPtr l a2 -> Bool #

Ord (HListPtr l a2) Source # 
Instance details

Defined in Reflex.Dynamic

Methods

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 #

max :: HListPtr l a2 -> HListPtr l a2 -> HListPtr l a2 #

min :: HListPtr l a2 -> HListPtr l a2 -> HListPtr l a2 #

distributeFHListOverDynPure :: (Reflex t, RebuildSortedHList l) => FHList (Dynamic t) l -> Dynamic t (HList l) Source #

Collect a hetereogeneous list whose elements are all Dynamics into a single Dynamic whose value represents the current values of all of the input Dynamics.

Unsafe

unsafeDynamic :: Reflex t => Behavior t a -> Event t a -> Dynamic t a Source #

Construct a Dynamic from a Behavior and an Event. The Behavior must change when and only when the Event fires, such that the Behavior's value is always equal to the most recent firing of the Event; if this is not the case, the resulting Dynamic will behave nondeterministically.

Deprecated functions

apDyn :: forall t m a b. (Reflex t, Monad m) => m (Dynamic t (a -> b)) -> Dynamic t a -> m (Dynamic t b) Source #

Deprecated: Use 'ffor m (* a)' instead of 'apDyn m a'; consider eliminating monadic style, since Dynamics are now Applicative and can be used with applicative style directly

A psuedo applicative version of ap for Dynamic. Example useage:

do
   person <- Person `mapDyn` dynFirstName
                    `apDyn` dynListName
                    `apDyn` dynAge
                    `apDyn` dynAddress

attachDyn :: Reflex t => Dynamic t a -> Event t b -> Event t (a, b) Source #

Deprecated: Use attachPromptlyDyn instead

This function has been renamed to attachPromptlyDyn to clarify its semantics.

attachDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Event t b -> Event t c Source #

Deprecated: Use attachPromptlyDynWith instead

This function has been renamed to attachPromptlyDynWith to clarify its semantics.

attachDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c Source #

Deprecated: Use attachPromptlyDynWithMaybe instead

This function has been renamed to attachPromptlyDynWithMaybe to clarify its semantics.

collectDyn :: (RebuildSortedHList (HListElems b), IsHList a, IsHList b, AllAreFunctors (Dynamic t) (HListElems b), Reflex t, Monad m, HListElems a ~ FunctorList (Dynamic t) (HListElems b)) => a -> m (Dynamic t b) Source #

Deprecated: Use 'return . collectDynPure' instead; consider eliminating monadic style

This function no longer needs to be monadic, so it has been replaced by collectDynPure, which is pure.

combineDyn :: forall t m a b c. (Reflex t, Monad m) => (a -> b -> c) -> Dynamic t a -> Dynamic t b -> m (Dynamic t c) Source #

Deprecated: Use 'return (zipDynWith f a b)' instead of 'combineDyn f a b'; consider eliminating monadic style

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.

distributeDMapOverDyn :: (Reflex t, Monad m, GCompare k) => DMap k (Dynamic t) -> m (Dynamic t (DMap k Identity)) Source #

Deprecated: Use 'return . distributeDMapOverDynPure' instead; consider eliminating monadic style

This function no longer needs to be monadic; see distributeMapOverDynPure.

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

Deprecated: Use 'return . distributeFHListOverDynPure' instead; consider eliminating monadic style

This function no longer needs to be monadic, so it has been replaced by distributeFHListOverDynPure, which is pure.

forDyn :: (Reflex t, Monad m) => Dynamic t a -> (a -> b) -> m (Dynamic t b) Source #

Deprecated: Use 'return . ffor a' instead of 'forDyn a'; consider eliminating monadic style

Flipped version of mapDyn.

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

Deprecated: Use 'return . demuxed d' instead of 'getDemuxed d'; consider eliminating monadic style

This function no longer needs to be monadic, so it has been replaced by demuxed, which is pure.

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

Deprecated: Use join instead

Combine an inner and outer Dynamic such that the resulting Dynamic's current value will always be equal to the current value's current value, and will change whenever either the inner or the outer (or both) values change.

mapDyn :: (Reflex t, Monad m) => (a -> b) -> Dynamic t a -> m (Dynamic t b) Source #

Deprecated: Use 'return . fmap f' instead of 'mapDyn f'; consider eliminating monadic style

Map a function over a Dynamic.

mconcatDyn :: forall t m a. (Reflex t, Monad m, Monoid a) => [Dynamic t a] -> m (Dynamic t a) Source #

Deprecated: Use 'return . mconcat' instead; consider eliminating monadic style

Merge the Dynamic values using their Monoid instance.

nubDyn :: (Reflex t, Eq a) => Dynamic t a -> Dynamic t a Source #

Deprecated: Use holdUniqDyn instead; note that it returns a MonadHold action rather than a pure Dynamic

WARNING: This function is only pure if a's Eq instance tests representational equality. Use holdUniqDyn instead, which is pure in all circumstances. Also, note that, unlike nub, this function does not prevent all recurrences of a value, only consecutive recurrences.

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

Deprecated: Use 'return . splitDynPure' instead; consider eliminating monadic style

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

tagDyn :: Reflex t => Dynamic t a -> Event t b -> Event t a Source #

Deprecated: Use tagPromptlyDyn instead

This function has been renamed to tagPromptlyDyn to clarify its semantics.

uniqDyn :: (Reflex t, Eq a) => Dynamic t a -> Dynamic t a Source #

Deprecated: Use holdUniqDyn instead; note that it returns a MonadHold action rather than a pure Dynamic

WARNING: This function is only pure if a's Eq instance tests representational equality. Use holdUniqDyn instead, which is pure in all circumstances.

uniqDynBy :: Reflex t => (a -> a -> Bool) -> Dynamic t a -> Dynamic t a Source #

Deprecated: Use holdUniqDynBy instead; note that it returns a MonadHold action rather than a pure Dynamic

WARNING: This function is impure. Use holdUniqDynBy instead.