reflex-0.1.0: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Class

Synopsis

Documentation

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

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 (WrapArg (Event t) k) -> Event t (DMap k) 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) -> 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

Instances

class Monad m => MonadSample t m | m -> t where Source

Methods

sample :: Behavior t a -> m a Source

Get the current value in the Behavior

class MonadSample t m => MonadHold t m where Source

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

newtype EventSelector t k Source

Constructors

EventSelector 

Fields

select :: forall a. k a -> Event t a
 

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

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

class FunctorMaybe f where Source

Methods

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

Instances

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

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

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

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

Replace the occurrence value of the Event with the value of the Behavior at the time of the occurrence

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

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

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

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

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

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

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

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

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

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

data EitherTag l r a where Source

Constructors

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

Instances

GCompare * (EitherTag l r) 
GEq * (EitherTag l r) 
(Show l, Show r) => ShowTag (EitherTag l r) 
GShow (EitherTag l r) 

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

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

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

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

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

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

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

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