Safe Haskell | None |
---|---|
Language | Haskell98 |
- class (MonadHold t (PushM t), MonadSample t (PullM t), Functor (Event t), Functor (Behavior t)) => Reflex t where
- data Behavior t :: * -> *
- data Event t :: * -> *
- type PushM t :: * -> *
- type PullM t :: * -> *
- never :: Event t a
- constant :: a -> Behavior t a
- push :: (a -> PushM t (Maybe b)) -> Event t a -> Event t b
- pull :: PullM t a -> Behavior t a
- merge :: GCompare k => DMap (WrapArg (Event t) k) -> Event t (DMap k)
- fan :: GCompare k => Event t (DMap k) -> EventSelector t k
- switch :: Behavior t (Event t a) -> Event t a
- coincidence :: Event t (Event t a) -> Event t a
- class Monad m => MonadSample t m | m -> t where
- class MonadSample t m => MonadHold t m where
- newtype EventSelector t k = EventSelector {}
- pushAlways :: Reflex t => (a -> PushM t b) -> Event t a -> Event t b
- ffor :: Functor f => f a -> (a -> b) -> f b
- class FunctorMaybe f where
- fforMaybe :: FunctorMaybe f => f a -> (a -> Maybe b) -> f b
- ffilter :: FunctorMaybe f => (a -> Bool) -> f a -> f a
- zipListWithEvent :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> c) -> [a] -> Event t b -> m (Event t c)
- tag :: Reflex t => Behavior t b -> Event t a -> Event t b
- attachWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Behavior t a -> Event t b -> Event t c
- attachWith :: Reflex t => (a -> b -> c) -> Behavior t a -> Event t b -> Event t c
- attach :: Reflex t => Behavior t a -> Event t b -> Event t (a, b)
- onceE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
- headE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
- tailE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
- headTailE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a, Event t a)
- splitE :: Reflex t => Event t (a, b) -> (Event t a, Event t b)
- traceEvent :: (Reflex t, Show a) => String -> Event t a -> Event t a
- traceEventWith :: Reflex t => (a -> String) -> Event t a -> Event t a
- data EitherTag l r a where
- eitherToDSum :: Either a b -> DSum (EitherTag a b)
- dsumToEither :: DSum (EitherTag a b) -> Either a b
- dmapToThese :: DMap (EitherTag a b) -> Maybe (These a b)
- appendEvents :: (Reflex t, Monoid a) => Event t a -> Event t a -> Event t a
- sequenceThese :: Monad m => These (m a) (m b) -> m (These a b)
- mergeWith :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a
- leftmost :: Reflex t => [Event t a] -> Event t a
- mergeList :: Reflex t => [Event t a] -> Event t (NonEmpty a)
- mergeMap :: (Reflex t, Ord k) => Map k (Event t a) -> Event t (Map k a)
- fanMap :: (Reflex t, Ord k) => Event t (Map k a) -> EventSelector t (Const2 k a)
- switchPromptly :: forall t m a. (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
- gate :: Reflex t => Behavior t Bool -> Event t a -> Event t a
Documentation
class (MonadHold t (PushM t), MonadSample t (PullM t), Functor (Event t), Functor (Behavior t)) => Reflex t where Source
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
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")
A monad for doing complex push-based calculations efficiently
A monad for doing complex pull-based calculations efficiently
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
class Monad m => MonadSample t m | m -> t where Source
class MonadSample t m => MonadHold t m where Source
newtype EventSelector t k Source
class FunctorMaybe f where Source
Reflex t => FunctorMaybe (Event t) |
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
eitherToDSum :: Either a b -> DSum (EitherTag a b) Source
dsumToEither :: DSum (EitherTag a b) -> Either a b Source
sequenceThese :: Monad m => These (m a) (m b) -> m (These a b) Source