| Stability | experimental |
|---|---|
| Maintainer | conal@conal.net |
Data.Reactive
Contents
Description
Functional events and reactive values. An Event is stream of
future values in time order. A Reactive value is a discretly
time-varying value. These two types are closely linked: a reactive
value is defined by an initial value and an event that yields future
values; while an event is simply a future reactive value.
Many of the operations on events and reactive values are packaged as
instances of the standard type classes Monoid, Functor,
Applicative, and Monad.
Although the basic Reactive type describes discretely-changing
values, continuously-changing values are modeled simply as reactive
functions. For convenience, this module defines ReactiveB as a type
composition of Reactive and a constant-optimized representation of
functions of time.
The exact packaging of discrete vs continuous will probably change with more experience.
- newtype Event a = Event {}
- data Reactive a = Stepper {}
- type Source = Reactive
- inEvent :: (Future (Reactive a) -> Future (Reactive b)) -> Event a -> Event b
- inEvent2 :: (Future (Reactive a) -> Future (Reactive b) -> Future (Reactive c)) -> Event a -> Event b -> Event c
- stepper :: a -> Event a -> Reactive a
- switcher :: Reactive a -> Event (Reactive a) -> Reactive a
- mkEvent :: IO (Event a, Sink a)
- mkEventTrace :: (a -> String) -> IO (Event a, Sink a)
- mkEventShow :: Show a => String -> IO (Event a, Sink a)
- runE :: Event (IO b) -> IO a
- forkE :: Event (IO b) -> IO ThreadId
- subscribe :: Event a -> Sink a -> IO ThreadId
- forkR :: Reactive (IO b) -> IO ThreadId
- accumE :: a -> Event (a -> a) -> Event a
- scanlE :: (a -> b -> a) -> a -> Event b -> Event a
- monoidE :: Monoid o => Event o -> Event o
- withPrevE :: Event a -> Event (a, a)
- countE :: Num n => Event b -> Event (b, n)
- countE_ :: Num n => Event b -> Event n
- diffE :: Num n => Event n -> Event n
- snapshot :: Event a -> Reactive b -> Event (a, b)
- snapshot_ :: Event a -> Reactive b -> Event b
- whenE :: Event a -> Reactive Bool -> Event a
- once :: Event a -> Event a
- traceE :: (a -> String) -> Unop (Event a)
- eventX :: IO (Event a, Sink (Event a))
- mkReactive :: a -> IO (Reactive a, Sink a)
- accumR :: a -> Event (a -> a) -> Reactive a
- scanlR :: (a -> b -> a) -> a -> Event b -> Reactive a
- monoidR :: Monoid a => Event a -> Reactive a
- maybeR :: Event a -> Event b -> Reactive (Maybe a)
- flipFlop :: Event a -> Event b -> Reactive Bool
- countR :: Num n => Event a -> Reactive n
- traceR :: (a -> String) -> Unop (Reactive a)
- type Time = Double
- type ReactiveB = Reactive :. Fun Time
- replace :: Functor f => b -> f a -> f b
- forget :: Functor f => f a -> f ()
- type Action = IO ()
- type Sink a = a -> Action
- joinMaybes :: MonadPlus m => m (Maybe a) -> m a
- filterMP :: MonadPlus m => (a -> Bool) -> m a -> m a
Events and reactive values
Event, i.e., a stream of future values. Instances:
-
Monoid:memptyis the event that never occurs, andeis the event that combines occurrences frommappende'eande'. (Fran'sneverEand(.|.).) -
Functor:fmap f eis the event that occurs whenevereoccurs, and whose occurrence values come from applyingfto the values frome. (Fran's(==>).) -
Applicative:pure ais an event with a single occurrence, available from the beginning of time.ef <*> exis an event whose occurrences are made from the product of the occurrences ofefandex. For every occurrencefat timetfofefand occurrencexat timetxofex,ef <*> exhas an occurrencef xat timemax tf tx. -
Monad:return ais the same aspure a(as always). Ine >>= f, each occurrence ofeleads, throughf, to a new event. Similarly forjoin ee, which is somehow simpler for me to think about. The occurrences ofe >>= f(orjoin ee) correspond to the union of the occurrences of all such events. For example, suppose we're playing Asteroids and tracking collisions. Each collision can break an asteroid into more of them, each of which has to be tracked for more collisions. Another example: A chat room has an enter event, whose occurrences contain new events like speak. An especially useful monad-based function isjoinMaybes, which filters a Maybe-valued event.
Reactive value: a discretely changing value. Reactive values can be
understood in terms of (a) a simple denotational semantics of reactive
values as functions of time, and (b) the corresponding instances for
functions. The semantics is given by the function (%$) :: Reactive a
-> (Time -> a). A reactive value also has a current value and an
event (stream of future values).
Instances for Reactive
-
Monoid: a typical lifted monoid. Ifois a monoid, thenReactive ois a monoid, withmempty = pure mempty, andmappend = liftA2 mappend. In other words,mempty %$ t == mempty, and(rmappends) %$ t == (r %$ t)mappend(s %$ t). -
Functor:fmap f r %$ t == f (r %$ t). -
Applicative:pure a %$ t == a, and(s <*> r) %$ t == (s %$ t) (r %$ t). -
Monad:return a %$ t == a, andjoin rr %$ t == (rr %$ t) %$ t. As always,(r >>= f) == join (fmap f r).
inEvent :: (Future (Reactive a) -> Future (Reactive b)) -> Event a -> Event bSource
Apply a unary function inside an Event representation.
inEvent2 :: (Future (Reactive a) -> Future (Reactive b) -> Future (Reactive c)) -> Event a -> Event b -> Event cSource
Apply a unary function inside an Event representation.
stepper :: a -> Event a -> Reactive aSource
Reactive value from an initial value and a new-value event.
mkEvent :: IO (Event a, Sink a)Source
Make an event and a sink for feeding the event. Each value sent to the sink becomes an occurrence of the event.
mkEventShow :: Show a => String -> IO (Event a, Sink a)Source
Show specialization of mkEventTrace
forkR :: Reactive (IO b) -> IO ThreadIdSource
Run a reactive value in a new thread. The initial action happens in the current thread.
Event extras
accumE :: a -> Event (a -> a) -> Event aSource
Accumulating event, starting from an initial value and a
update-function event. See also accumR.
withPrevE :: Event a -> Event (a, a)Source
Pair each event value with the previous one, given an initial value.
countE :: Num n => Event b -> Event (b, n)Source
Count occurrences of an event, remembering the occurrence values.
See also countE_.
snapshot :: Event a -> Reactive b -> Event (a, b)Source
Snapshot a reactive value whenever an event occurs.
snapshot_ :: Event a -> Reactive b -> Event bSource
Like snapshot but discarding event data (often a is ()).
whenE :: Event a -> Reactive Bool -> Event aSource
Filter an event according to whether a boolean source is true.
eventX :: IO (Event a, Sink (Event a))Source
Make an extensible event. The returned sink is a way to add new
events to mix. You can often use '(>>=)' or join instead. Warning:
this function might be removed at some point.
Reactive extras
mkReactive :: a -> IO (Reactive a, Sink a)Source
accumR :: a -> Event (a -> a) -> Reactive aSource
Reactive value from an initial value and an updater event. See also
accumE.
flipFlop :: Event a -> Event b -> Reactive BoolSource
Flip-flopping source. Turns true when ea occurs and false when
eb occurs.
Reactive behaviors
type ReactiveB = Reactive :. Fun TimeSource
Reactive behaviors. Simply a reactive Function value. Wrapped in
a type composition to get Functor and Applicative for free.
To be moved elsewhere
joinMaybes :: MonadPlus m => m (Maybe a) -> m aSource
Pass through Just occurrences.