reactive-0.11.5: Push-pull functional reactive programming

Stabilityexperimental
Maintainerconal@conal.net

FRP.Reactive.Future

Contents

Description

A simple formulation of functional futures, roughly as described at http://en.wikipedia.org/wiki/Futures_and_promises.

A future is a value with an associated time of arrival. Typically, neither the time nor the value can be known until the arrival time.

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. Some comments on the Future instances of these classes:

  • Monoid: mempty is a future that never arrives (infinite time and undefined value), and a mappend b is the earlier of a and b, preferring a when simultaneous.
  • Functor: apply a function to a future argument. The (future) result arrives simultaneously with the argument.
  • Applicative: pure gives value arriving negative infinity. '(<*>)' applies a future function to a future argument, yielding a future result that arrives once both function and argument have arrived (coinciding with the later of the two times).
  • Monad: return is the same as pure (as usual). (>>=) cascades futures. join resolves a future future value into a future value.

Futures are parametric over time as well as value types. The time parameter can be any ordered type and is particularly useful with time types that have rich partial information structure, such as /improving values/.

Synopsis

Time & futures

type Time = MaxSource

Time used in futures. The parameter t can be any Ord and Bounded type. Pure values have time minBound, while never-occurring futures have time 'maxBound.' type Time t = Max (AddBounds t)

ftime :: t -> Time tSource

Make a finite time

newtype FutureG t a Source

A future value of type a with time type t. Simply a time/value pair. Particularly useful with time types that have non-flat structure.

Constructors

Future 

Fields

unFuture :: (Time t, a)
 

Instances

(Bounded t, Ord t) => Monad (FutureG t) 
Functor (FutureG t) 
(Bounded t, Ord t) => Applicative (FutureG t) 
Comonad (FutureG t) 
Copointed (FutureG t) 
(Eq t, Eq a, Bounded t) => Eq (FutureG t a) 
(Show t, Show a, Eq t, Bounded t) => Show (FutureG t a) 
(Arbitrary t, Arbitrary a) => Arbitrary (FutureG t a) 
(CoArbitrary t, CoArbitrary a) => CoArbitrary (FutureG t a) 
(Ord t, Bounded t) => Monoid (FutureG t a) 
(Bounded t, Eq t, EqProp t, EqProp a) => EqProp (FutureG t a) 

isNeverF :: (Bounded t, Eq t) => FutureG t t1 -> BoolSource

inFuture :: ((Time t, a) -> (Time t', b)) -> FutureG t a -> FutureG t' bSource

Apply a unary function within the FutureG representation.

inFuture2 :: ((Time t, a) -> (Time t', b) -> (Time t', c)) -> FutureG t a -> FutureG t' b -> FutureG t' cSource

Apply a binary function within the FutureG representation.

futTime :: FutureG t a -> Time tSource

A future's time

futVal :: FutureG t a -> aSource

A future's value

future :: t -> a -> FutureG t aSource

A future value with given time & value

withTimeF :: FutureG t a -> FutureG t (Time t, a)Source

Access time of future

Tests