Old-reactive
Abstract
Note: I have retired the old version of Reactive on darcs.haskell.org. Please use the new Reactive.
Reactive is a simple foundation for programming reactive systems functionally. Like Fran/FRP, it has a notions of (reactive) behaviors and events. Like DataDriven, Reactive has an efficient, data-driven implementation. The main difference between Reactive and DataDriven are
- Reactive provides and builds on "functional futures", which in turn build on Concurrent Haskell threads, while DataDriven builds on continuation-based computations; and
- The algebras of events and reactive values (called events and sources in DataDriven) are purely functional. I couldn't figure out how to accomplish that in DataDriven.
- Reactive manages (I hope) to get the efficiency of data-driven computation with a (sort-of) demand-driven architecture. For that reason, Reactive is garbage-collector-friendly, while DataDriven depends on weak references (because GC favors demand-driven computation.)
- Reactive elegantly and efficiently caches values.
- Reactive uses the term "reactive values" (
Reactive
), where DataDriven uses "sources" (Source
).
The inspiration for Reactive was Mike Sperber's Lula implementation of FRP. Mike used blocking threads, which I had never considered for FRP before a conversation with him at ICFP 2007. While playing with the idea, I realized that I could give a very elegant and efficient solution to caching, which DataDriven doesn't do. (For an application f <*> a
of a varying function to a varying argument, caching remembers the latest function to apply to a new argument and the latest argument to which to apply a new function.)
As with DataDriven, Reactive provides instances for Monoid
, Functor
, Applicative
, and Monad
.
Besides this wiki page, here are more ways to find out about Reactive:
- Read the Haddock docs.
- Get the code repository: darcs get http://darcs.haskell.org/packages/old-reactive/. (Old version, to be replaced in September 08.)
- Install from Hackage.
- See the version history.
Also, the paper Simply Efficient Functional Reactivity, and its blog post with discussion, describe a (not-yet-released) successor to Reactive that solves the determinacy problem mentioned below.
Modules
Data.Future
A future is a value that will become knowable only later. Primitive futures can be things like "the value of the next key you press", or "the value of LambdaPix stock at noon next Monday". The term "promise" might be more fitting.
Composition is via standard type classes: Functor
, Applicative
, Monad
, and Monoid
.
Monoid
:mempty
is a future that never becomes knowable.a `mappend` b
is whichever ofa
andb
is knowable first.Functor
: apply a function to a future. The result is knowable when the given future is knowable.Applicative
:pure
gives value knowable since the beginning of time.(<*>)
applies a future function to a future argument. Result available when both are available, i.e., it becomes knowable when the later of the two futures becomes knowable.- Monad:
return
is the same aspure
(as always).(>>=)
cascades futures.join
resolves a future future value into a future value.
The current implementation is nondeterministic in mappend
for futures that become knowable at the same time or nearly the same time. I want to make a deterministic implementation.
Garbage collection of futures
Baker & Hewitt's 1977 paper The Incremental Garbage Collection of Processes discusses using garbage collection to prevent the useless threads from consuming resources. In particular, consider Future
's mappend
(sometimes called "parallel or"). Once one thread completes, the other threads are then useless, and some might consume resources forever. My current implementation kill the losing threads. Baker & Hewitt suggest instead using garbage collection. I'm stumped about how to GC non-winning threads in a race between futures ("parallel or"). The winner-kills-loser approach seems to work fine, though is potentially dangerous w.r.t locked resources. Still, the elegance of a GC-based solution appeals to me.
Concurrent Haskell vs STM
Futures are implemented using Concurrent Haskell's MVar
s. I first tried using STM and TVar
s, simply using orElse
to implement mappend
for futures. However, I didn't see how to avoid nesting atomically
, which yielded a run-time error.
Data.SFuture
A target denotational semantics for Data.Future -- simple, precise, and deterministic, in terms of time/value pairs.
Data.Reactive
This module defines events and reactive values. An event is stream of future values in order of availability. 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.
data Reactive a = a `Stepper` Event a
newtype Event a = Event (Future (Reactive a))
This Reactive
representation can be thought of a reactive weak head normal form, to which arbitrary reactive expressions may be rewritten. The rewrite rules and their justification in terms of simple denotational semantics will be described in an upcoming paper.
Many of the operations on events and reactive values are packaged as instances of standard classes, as described below. See the module documentation for the other operations.
Instances for Event
:Monoid
mempty
is the event that never occurs, ande `mappend` e'
is the event that combines occurrences frome
ande'
. (Fran'sneverE
and(.|.)
.) :Functor
fmap f e
is the event that occurs whenevere
occurs, and whose occurrence values come from applyingf
to the values frome
. (Fran's(==>)
.) :Applicative
pure a
is an event with a single occurrence, available from the beginning of time.ef <*> ex
is an event whose occurrences are made from the product of the occurrences ofef
andex
. For every occurrencef
at timetf
ofef
and occurrencex
at timetx
ofex
,ef <*> ex
has an occurrencef x
at timemax tf tx
. :Monad
return a
is the same aspure a
(as always). Ine >>= f
, each occurrence ofe
leads, 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".
Instances for Reactive
The instances for Reactive
can be understood in terms of (a) a simple semantics of reactive values as functions of time, and (b) the corresponding instances for functions. The semantics is given by the function at :: Reactive a -> (Time -> a)
.
: a typical lifted monoid. IfMonoid
o
is a monoid, thenReactive o
is a monoid, withmempty = pure mempty
, andmappend = liftA2 mappend
. In other words,mempty `at` t == mempty
, and(r `mappend` s) `at` t == (r `at` t) `mappend` (s `at` t).
:Functor
fmap f r `at` t == f (r `at` t)
. :Applicative
pure a `at` t == a
, and(s <*> r) `at` t == (s `at` t) (r `at` t)
. :Monad
return a `at` t == a
, andjoin rr `at` t == (rr `at` t) `at` t
. As always,(r >>= f) == join (fmap f r)
.
Continuous reactive behaviors
Although the basic Reactive
type describes discretely-changing values, continuously-changing are defined simply by composing Reactive
and a simple type functions of time (see below).
type Time = Double
type ReactiveB = Reactive :. Fun Time
Because the combination of Reactive
and Fun Time
is wrapped in a type composition, we get Functor
and Applicative
instances for free.
The exact packaging of discrete vs continuous will probably change with more experience. Perhaps I'll fold Fun Time a
into the Reactive
type, making a dynamic rather than static distinction.
Data.Fun
This module defines a type of functions optimized for the constant case, together with instances of Functor
, Applicative
, Monad
, and Arrow
.