reflex-0.4.0.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Class

Synopsis

Documentation

class (MonadHold t (PushM t), MonadSample t (PullM t), MonadFix (PushM t), Functor (Event t), Functor (Behavior t)) => Reflex t where Source #

Minimal complete definition

never, constant, push, pull, merge, fan, switch, coincidence

Associated Types

data Behavior t :: * -> * Source #

A container for a value that can change over time. Behaviors can be sampled at will, but it is not possible to be notified when they change

data Event t :: * -> * Source #

A stream of occurrences. During any given frame, an Event is either occurring or not occurring; if it is occurring, it will contain a value of the given type (its "occurrence type")

type PushM t :: * -> * Source #

A monad for doing complex push-based calculations efficiently

type PullM t :: * -> * Source #

A monad for doing complex pull-based calculations efficiently

Methods

never :: Event t a Source #

An Event with no occurrences

constant :: a -> Behavior t a Source #

Create a Behavior that always has the given value

push :: (a -> PushM t (Maybe b)) -> Event t a -> Event t b Source #

Create an Event from another Event; the provided function can sample Behaviors and hold Events, and use the results to produce a occurring (Just) or non-occurring (Nothing) result

pull :: PullM t a -> Behavior t a Source #

Create a Behavior by reading from other Behaviors; the result will be recomputed whenever any of the read Behaviors changes

merge :: GCompare k => DMap k (Event t) -> Event t (DMap k Identity) Source #

Merge a collection of events; the resulting Event will only occur if at least one input event is occuring, and will contain all of the input keys that are occurring simultaneously

fan :: GCompare k => Event t (DMap k Identity) -> EventSelector t k Source #

Efficiently fan-out an event to many destinations. This function should be partially applied, and then the result applied repeatedly to create child events

switch :: Behavior t (Event t a) -> Event t a Source #

Create an Event that will occur whenever the currently-selected input Event occurs

coincidence :: Event t (Event t a) -> Event t a Source #

Create an Event that will occur whenever the input event is occurring and its occurrence value, another Event, is also occurring

class (Applicative m, Monad m) => MonadSample t m | m -> t where Source #

Minimal complete definition

sample

Methods

sample :: Behavior t a -> m a Source #

Get the current value in the Behavior

class MonadSample t m => MonadHold t m where Source #

Minimal complete definition

hold

Methods

hold :: a -> Event t a -> m (Behavior t a) Source #

Create a new Behavior whose value will initially be equal to the given value and will be updated whenever the given Event occurs. The update takes effect immediately after the Event occurs; if the occurrence that sets the Behavior (or one that is simultaneous with it) is used to sample the Behavior, it will see the *old* value of the Behavior, not the new one.

Instances

MonadHold Spider ReadPhase Source # 

Methods

hold :: a -> Event Spider a -> ReadPhase (Behavior Spider a) Source #

MonadHold Spider SpiderHostFrame Source # 
MonadHold Spider SpiderHost Source # 

Methods

hold :: a -> Event Spider a -> SpiderHost (Behavior Spider a) Source #

MonadHold Spider EventM Source # 

Methods

hold :: a -> Event Spider a -> EventM (Behavior Spider a) Source #

MonadHold t m => MonadHold t (ExceptT e m) Source # 

Methods

hold :: a -> Event t a -> ExceptT e m (Behavior t a) Source #

MonadHold t m => MonadHold t (StateT s m) Source # 

Methods

hold :: a -> Event t a -> StateT s m (Behavior t a) Source #

(MonadHold t m, Monoid r) => MonadHold t (WriterT r m) Source # 

Methods

hold :: a -> Event t a -> WriterT r m (Behavior t a) Source #

MonadHold t m => MonadHold t (ContT * r m) Source # 

Methods

hold :: a -> Event t a -> ContT * r m (Behavior t a) Source #

MonadHold t m => MonadHold t (ReaderT * r m) Source # 

Methods

hold :: a -> Event t a -> ReaderT * r m (Behavior t a) Source #

(MonadHold t m, Monoid w) => MonadHold t (RWST r w s m) Source # 

Methods

hold :: a -> Event t a -> RWST r w s m (Behavior t a) Source #

newtype EventSelector t k Source #

Constructors

EventSelector 

Fields

pushAlways :: Reflex t => (a -> PushM t b) -> Event t a -> Event t b Source #

Create an Event from another Event. The provided function can sample Behaviors and hold Events.

ffor :: Functor f => f a -> (a -> b) -> f b Source #

Flipped version of fmap.

class FunctorMaybe f where Source #

A class for values that combines filtering and mapping using Maybe.

Minimal complete definition

fmapMaybe

Methods

fmapMaybe :: (a -> Maybe b) -> f a -> f b Source #

Combined mapping and filtering function.

Instances

Reflex t => FunctorMaybe (Event t) Source # 

Methods

fmapMaybe :: (a -> Maybe b) -> Event t a -> Event t b Source #

fforMaybe :: FunctorMaybe f => f a -> (a -> Maybe b) -> f b Source #

Flipped version of fmapMaybe.

ffilter :: FunctorMaybe f => (a -> Bool) -> f a -> f a Source #

Filter 'f a' using the provided predicate. Relies on fforMaybe.

zipListWithEvent :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> c) -> [a] -> Event t b -> m (Event t c) Source #

Create a new Event by combining each occurence with the next value of the list using the supplied function. If the list runs out of items, all subsequent Event occurrences will be ignored.

tag :: Reflex t => Behavior t b -> Event t a -> Event t b Source #

Replace each occurrence value of the Event with the value of the Behavior at the time of that occurrence.

attach :: Reflex t => Behavior t a -> Event t b -> Event t (a, b) Source #

Create a new Event that combines occurences of supplied Event with the current value of the Behavior.

attachWith :: Reflex t => (a -> b -> c) -> Behavior t a -> Event t b -> Event t c Source #

Create a new Event that occurs when the supplied Event occurs by combining it with the current value of the Behavior.

attachWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Behavior t a -> Event t b -> Event t c Source #

Create a new Event by combining each occurence with the current value of the Behavior. The occurrence is discarded if the combining function returns Nothing

onceE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a) Source #

Alias for headE

headE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a) Source #

Create a new Event that only occurs on the first occurence of the supplied Event.

tailE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a) Source #

Create a new Event that occurs on all but the first occurence of the supplied Event.

headTailE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a, Event t a) Source #

Create a tuple of two Events with the first one occuring only the first time the supplied Event occurs and the second occuring on all but the first occurence.

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

Split the supplied Event into two individual Events occuring at the same time with the respective values from the tuple.

traceEvent :: (Reflex t, Show a) => String -> Event t a -> Event t a Source #

Print the supplied String and the value of the Event on each occurence. This should only be used for debugging.

Note: As with Debug.Trace.trace, the message will only be printed if the Event is actually used.

traceEventWith :: Reflex t => (a -> String) -> Event t a -> Event t a Source #

Print the output of the supplied function on each occurence of the Event. This should only be used for debugging.

Note: As with Debug.Trace.trace, the message will only be printed if the Event is actually used.

data EitherTag l r a where Source #

Tag type for Either to use it as a DSum.

Constructors

LeftTag :: EitherTag l r l 
RightTag :: EitherTag l r r 

Instances

GCompare * (EitherTag l r) Source # 

Methods

gcompare :: f a -> f b -> GOrdering (EitherTag l r) a b #

GEq * (EitherTag l r) Source # 

Methods

geq :: f a -> f b -> Maybe ((EitherTag l r := a) b) #

GShow * (EitherTag l r) Source # 

Methods

gshowsPrec :: Int -> t a -> ShowS #

(Show l, Show r) => ShowTag * (EitherTag l r) Identity Source # 

Methods

showTaggedPrec :: Identity a -> Int -> f a -> ShowS #

eitherToDSum :: Either a b -> DSum (EitherTag a b) Identity Source #

Convert Either to a DSum. Inverse of dsumToEither.

dsumToEither :: DSum (EitherTag a b) Identity -> Either a b Source #

Convert DSum to Either. Inverse of eitherToDSum.

dmapToThese :: DMap (EitherTag a b) Identity -> Maybe (These a b) Source #

Extract the values of a DMap of EitherTags.

appendEvents :: (Reflex t, Monoid a) => Event t a -> Event t a -> Event t a Source #

Create a new Event that occurs if at least one of the supplied Events occurs. If both occur at the same time they are combined using mappend.

sequenceThese :: Monad m => These (m a) (m b) -> m (These a b) Source #

Deprecated: Use bisequenceA or bisequence from the bifunctors package instead

mergeWith :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a Source #

Create a new Event that occurs if at least one of the Events in the list occurs. If multiple occur at the same time they are folded from the left with the given function.

leftmost :: Reflex t => [Event t a] -> Event t a Source #

Create a new Event that occurs if at least one of the Events in the list occurs. If multiple occur at the same time the value is the value of the leftmost event.

mergeList :: Reflex t => [Event t a] -> Event t (NonEmpty a) Source #

Create a new Event that occurs if at least one of the Events in the list occurs and has a list of the values of all Events occuring at that time.

mergeMap :: (Reflex t, Ord k) => Map k (Event t a) -> Event t (Map k a) Source #

Create a new Event combining the map of Events into an Event that occurs if at least one of them occurs and has a map of values of all Events occuring at that time.

fanMap :: (Reflex t, Ord k) => Event t (Map k a) -> EventSelector t (Const2 k a) Source #

Split the event into an EventSelector that allows efficient selection of the individual Events.

switchPromptly :: forall t m a. (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a) Source #

Switches to the new event whenever it receives one; the new event is used immediately, on the same frame that it is switched to

gate :: Reflex t => Behavior t Bool -> Event t a -> Event t a Source #

Create a new Event that only occurs if the supplied Event occurs and the Behavior is true at the time of occurence.

switcher :: (Reflex t, MonadHold t m) => Behavior t a -> Event t (Behavior t a) -> m (Behavior t a) Source #

Create a new behavior given a starting behavior and switch to a the behvior carried by the event when it fires.