varying-0.5.0.3: FRP through value streams and monadic splines.

Copyright(c) 2015 Schell Scivally
LicenseMIT
MaintainerSchell Scivally <schell.scivally@synapsegroup.com>
Safe HaskellNone
LanguageHaskell2010

Control.Varying.Spline

Contents

Description

Using splines we can easily create continuous value streams from multiple piecewise event streams. A spline is a monadic layer on top of event streams which are only continuous over a certain domain. The idea is that we use do notation to "run an event stream" from which we will consume produced values. Once the event stream inhibits the computation completes and returns a result value. That result value is then used to determine the next spline in the sequence.

A spline can be converted back into a value stream using execSpline or execSplineT. This allows us to build long, complex, sequential behaviors using familiar notation.

Synopsis

Spline

type Spline a b c = SplineT a b Identity c Source

A SplineT monad parameterized with Identity that takes input of type a, output of type b and a result value of type c.

Spline Transformer

data SplineT a b m c Source

SplineT shares all the types of VarT and adds a result value. Its monad, input and output types (m, a and b, respectively) reflect the underlying VarT. A spline adds a result type which represents the monadic computation's result value. Much like the State monad it has an "internal state" and an eventual result value, where the internal state is the output value. The result value is used only in determining the next spline to sequence.

Constructors

Pass c 
SplineT (VarT m a (b, Event c)) 

Instances

Monoid b => MonadTrans (SplineT a b) Source

A spline is a transformer if its output type is a Monoid.

(Applicative m, Monad m) => Monad (SplineT a b m) Source

A spline responds to bind by running until it produces an eventual value, then uses that value to run the next spline.

(Applicative m, Monad m) => Functor (SplineT a b m) Source

A spline is a functor by applying the function to the result.

(Applicative m, Monad m) => Applicative (SplineT a b m) Source 
(Monoid b, Applicative m, Monad m, MonadIO m) => MonadIO (SplineT a b m) Source

A spline can do IO if its underlying monad has a MonadIO instance. It takes the result of the IO action as its immediate return value.

Running and streaming

runSplineT :: (Applicative m, Monad m) => SplineT a b m c -> b -> VarT m a (b, Event c) Source

Convert a spline into a stream of output value and eventual result value tuples. Requires a default output value in case none are produced.

runSplineE :: Monad m => SplineT a b m c -> a -> m (Either b c, SplineT a b m c) Source

Run a spline without converting it into a stream. Produces either an output value on the left or the result value on the right.

scanSpline :: (Applicative m, Monad m) => SplineT a b m c -> b -> [a] -> m [b] Source

Run the spline over the input values, gathering the output and result values in a list.

outputStream :: (Applicative m, Monad m) => SplineT a b m c -> b -> VarT m a b Source

Evaluates a spline into a value stream of its output type.

resultStream :: (Applicative m, Monad m) => SplineT a b m c -> b -> VarT m a (Event c) Source

Combinators

step :: (Applicative m, Monad m) => b -> SplineT a b m () Source

Produce the argument as an output value exactly once.

effect :: (Applicative m, Monad m) => b -> m x -> SplineT a b m x Source

Run the side effect and use its result as the spline's result. This discards the output argument and switches immediately, but the argument is needed to construct the spline. For this reason spline's can't be an instance of MonadTrans or MonadIO.

fromEvent :: (Applicative m, Monad m) => VarT m a (Event b) -> SplineT a (Event b) m b Source

Create a spline from an event stream.

untilEvent :: (Applicative m, Monad m) => VarT m a b -> VarT m a (Event c) -> SplineT a b m (b, c) Source

Create a spline from a value stream and an event stream. The spline uses the value stream as its output value. The spline will run until the event stream produces a value, at that point the last output value and the event value are tupled and returned as the spline's result value.

untilEvent_ :: (Applicative m, Monad m) => VarT m a b -> VarT m a (Event c) -> SplineT a b m b Source

A variant of untilEvent that only results in the left result, discarding the right result.

_untilEvent :: (Applicative m, Monad m) => VarT m a b -> VarT m a (Event c) -> SplineT a b m c Source

A variant of untilEvent that only results in the right result, discarding the left result.

_untilEvent_ :: (Applicative m, Monad m) => VarT m a b -> VarT m a (Event c) -> SplineT a b m () Source

A variant of untilEvent that discards both the right and left results.

race :: (Applicative m, Monad m) => (a -> b -> c) -> SplineT i a m d -> SplineT i b m e -> SplineT i c m (Either d e) Source

Run two splines in parallel, combining their output. Return the result of the spline that concludes first. If they conclude at the same time the result is taken from the left spline.

raceMany :: (Applicative m, Monad m, Monoid b) => [SplineT a b m c] -> SplineT a b m c Source

merge :: (Applicative m, Monad m) => (b -> b -> b) -> (c -> d -> e) -> SplineT a b m c -> SplineT a b m d -> SplineT a b m e Source

Run two splines in parallel, combining their output. Once both splines have concluded, return the results of each in a tuple.

capture :: (Applicative m, Monad m) => SplineT a b m c -> SplineT a b m (Maybe b, c) Source

Capture the spline's last output value and tuple it with the spline's result. This is helpful when you want to sample the last output value in order to determine the next spline to sequence.

mapOutput :: (Applicative m, Monad m) => VarT m a (b -> t) -> SplineT a b m c -> SplineT a t m c Source

Map the output value of a spline.

adjustInput :: (Applicative m, Monad m) => VarT m a (a -> r) -> SplineT r b m c -> SplineT a b m c Source

Map the input value of a spline.