reactive-0.11.5: Push-pull functional reactive programming

Stabilityexperimental
Maintainerconal@conal.net

FRP.Reactive.Internal.Future

Contents

Description

Representation of future 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)

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.

runF :: Ord t => Sink t -> FutureG t (IO a) -> IO aSource

Run a future in the current thread. Use the given time sink to sync time, i.e., to wait for an output time before performing the action.