Difference between revisions of "Old-reactive"

From HaskellWiki
Jump to navigation Jump to search
(→‎Data.Reactive: type class instances)
Line 52: Line 52:
   
 
This <hask>Reactive</hask> 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.
 
This <hask>Reactive</hask> 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 ====
  +
  +
* '''<hask>Monoid</hask>''': <hask>mempty</hask> is the event that never occurs, and <hask>e `mappend` e'</hask> is the event that combines occurrences from <hask>e</hask> and <hask>e'</hask>. (Fran's <hask>neverE</hask> and <hask>(.|.)</hask>.)
  +
* '''<hask>Functor</hask>''': <hask>fmap f e</hask> is the event that occurs whenever <hask>e</hask> occurs, and whose occurrence values come from applying <hask>f</hask> to the values from <hask>e</hask>. (Fran's <hask>(==>)</hask>.)
  +
* '''<hask>Applicative</hask>''': <hask>pure a</hask> is an event with a single occurrence, available from the beginning of time. <hask>ef <*> ex</hask> is an event whose occurrences are made from the ''product'' of the occurrences of <hask>ef</hask> and <hask>ex</hask>. For every occurrence <hask>f</hask> at time <hask>tf</hask> of <hask>ef</hask> and occurrence <hask>x</hask> at time <hask>tx</hask> of <hask>ex</hask>, <hask>ef <*> ex</hask> has an occurrence <hask>f x</hask> at time <hask>max tf tx</hask>.
  +
* '''<hask>Monad</hask>''': <hask>return a</hask> is the same as <hask>pure a</hask> (as always). In <hask>e >>= f</hask>, each occurrence of <hask>e</hask> leads, through <hask>f</hask>, to a new event. Similarly for <hask>join ee</hask>, which is somehow simpler for me to think about. The occurrences of <hask>e >>= f</hask> (or <hask>join ee</hask>) 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 <hask>Reactive</hask> 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 <hask>at :: Reactive a -> (Time -> a)</hask>.
  +
* '''<hask>Monoid</hask>''': a typical lifted monoid. If <hask>o</hask> is a monoid, then <hask>Reactive o</hask> is a monoid, with <hask>mempty = pure mempty</hask>, and <hask>mappend = liftA2 mappend</hask>. In other words, <hask>mempty `at` t == mempty</hask>, and <hask>(r `mappend` s) `at` t == (r `at` t) `mappend` (s `at` t).</hask>
  +
* '''<hask>Functor</hask>''': <hask>fmap f r `at` t == f (r `at` t)</hask>.
  +
* '''<hask>Applicative</hask>''': <hask>pure a `at` t == a</hask>, and <hask>(s <*> r) `at` t == (s `at` t) (r `at` t)</hask>.
  +
* '''<hask>Monad</hask>''': <hask>return a `at` t == a</hask>, and <hask>join rr `at` t == (rr `at` t) `at` t</hask>. As always, <hask>(r >>= f) == join (fmap f r)</hask>.
  +
  +
==== Continuous reactive behaviors ====
   
 
Although the basic <hask>Reactive</hask> type describes ''discretely''-changing values, ''continuously''-changing are defined simply by composing <hask>Reactive</hask> and a simple type functions of time (see below).
 
Although the basic <hask>Reactive</hask> type describes ''discretely''-changing values, ''continuously''-changing are defined simply by composing <hask>Reactive</hask> and a simple type functions of time (see below).

Revision as of 04:44, 20 December 2007


Abstract

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:

Please leave comments at the Talk page.

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".

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 of a and b 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 as pure (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.

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.

newtype Event a = Event (Future (Reactive a))
data Reactive a = a `Stepper` Event 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, and e `mappend` e' is the event that combines occurrences from e and e'. (Fran's neverE and (.|.).)
  • Functor: fmap f e is the event that occurs whenever e occurs, and whose occurrence values come from applying f to the values from e. (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 of ef and ex. For every occurrence f at time tf of ef and occurrence x at time tx of ex, ef <*> ex has an occurrence f x at time max tf tx.
  • Monad: return a is the same as pure a (as always). In e >>= f, each occurrence of e leads, through f, to a new event. Similarly for join ee, which is somehow simpler for me to think about. The occurrences of e >>= f (or join 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).

  • Monoid: a typical lifted monoid. If o is a monoid, then Reactive o is a monoid, with mempty = pure mempty, and mappend = 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, and join 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.