varying-0.3.0.1: 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 m c = SplineT Event a b m c Source

Spline is a specialized SplineT that uses Event as its output container. This means that new values overwrite/replace old values due to Event's Last-like monoid instance.

execSpline :: (Applicative m, Monad m) => b -> Spline a b m c -> Var m a b Source

Using a default start value, evaluate the spline to a value stream. A spline is only defined over a finite domain so we must supply a default value to use before the spline produces its first output value.

spline :: (Applicative m, Monad m) => b -> Var m a (Event b) -> Spline a b m b Source

Create a spline using an event stream. The spline will run until the stream inhibits, using the stream's last produced value as the current output value. In the case the stream inhibits before producing a value the default value is used. The spline's result value is the last output value.

Spline Transformer

data SplineT f a b m c Source

SplineT shares a number of types with Var, specifically its monad, input and output types (m, a and b, respectively). A spline adds a container type that determines how empty output values should be created, appended and applied (the type must be monoidal and applicative). It also 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 return value, where the internal state is the output value. The result value is used only in determining the next spline to sequence.

Constructors

SplineT 

Fields

SplineTConst c 

Instances

Monoid (f b) => MonadTrans (SplineT f a b) Source

A spline is a transformer and other monadic computations can be lifted int a spline.

Methods

lift :: Monad m => m c -> SplineT f a b m c

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

A spline is monad if its output type is a monoid. A spline responds to bind by running until it produces an eventual value, then uses that value to run the next spline.

Methods

(>>=) :: SplineT f a b m c -> (c -> SplineT f a b m d) -> SplineT f a b m d

(>>) :: SplineT f a b m c -> SplineT f a b m d -> SplineT f a b m d

return :: c -> SplineT f a b m c

fail :: String -> SplineT f a b m c

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

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

Methods

fmap :: (c -> d) -> SplineT f a b m c -> SplineT f a b m d

(<$) :: c -> SplineT f a b m d -> SplineT f a b m c

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

A spline is an applicative if its output type is a monoid. It responds to pure by returning a spline that immediately returns the argument. It responds to <*> by applying the left arguments eventual value (the function) to the right arguments eventual value. The output values will me combined with mappend.

Methods

pure :: c -> SplineT f a b m c

(<*>) :: SplineT f a b m (c -> d) -> SplineT f a b m c -> SplineT f a b m d

(*>) :: SplineT f a b m c -> SplineT f a b m d -> SplineT f a b m d

(<*) :: SplineT f a b m c -> SplineT f a b m d -> SplineT f a b m c

(Monoid (f b), Functor m, Applicative m, MonadIO m) => MonadIO (SplineT f 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 and uses mempty to generate an empty output value.

Methods

liftIO :: IO c -> SplineT f a b m c

runSplineT :: (Applicative m, Monad m, Monoid (f b)) => SplineT f a b m c -> Var m a (Step (f b) c) Source

Unwrap a spline into a value stream.

evalSplineT :: (Applicative m, Monad m, Monoid (f b)) => SplineT f a b m c -> Var m a (Event c) Source

Evaluates a spline to an event stream of its result. The resulting value stream inhibits until the spline's domain is complete and then it produces events of the result type.

execSplineT :: (Applicative m, Monad m, Monoid (f b)) => SplineT f a b m c -> Var m a (f b) Source

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

output :: (Applicative m, Monad m, Monoid (f b), Applicative f) => b -> SplineT f a b m () Source

Produce the argument as an output value exactly once, then return ().

Special operations.

untilEvent :: (Applicative m, Monad m) => Var m a b -> Var m a (Event c) -> Spline 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.

race :: (Applicative m, Monad m, Monoid (f u)) => SplineT f i u m a -> SplineT f i u m a -> SplineT f i u m a Source

Run two splines concurrently and return the result of the SplineT that concludes first. If they conclude at the same time the result is taken from the spline on the left.

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

Run a list of splines concurrently. Restart individual splines whenever they conclude in a value. Return a list of the most recent result values once the control spline concludes.

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

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

mapOutput :: (Functor f, Monoid (f t), Applicative m, Monad m) => Var m a (b -> t) -> SplineT f a b m c -> SplineT f a t m c Source

Map the output value of a spline.

Step

data Step f b where Source

A discrete step in a continuous function. This is simply a type that discretely describes an eventual value on the right and a monoidal output value on the left.

Constructors

Step :: Monoid f => f -> Event b -> Step f b 

Instances

Functor (Step f) Source

A discrete step is a functor by applying a function to the contained event's value.

Methods

fmap :: (a -> b) -> Step f a -> Step f b

(<$) :: a -> Step f b -> Step f a

Monoid f => Applicative (Step f) Source

A discrete spline is an applicative if its left datatype is a monoid. It replies to pure with an empty left value while the right value is the argument wrapped in an event. It means "the argument happens instantly".

Methods

pure :: a -> Step f a

(<*>) :: Step f (a -> b) -> Step f a -> Step f b

(*>) :: Step f a -> Step f b -> Step f b

(<*) :: Step f a -> Step f b -> Step f a

(Monoid f, Monoid b) => Monoid (Step f b) Source

A discrete spline is a monoid if its left and right types are monoids.

Methods

mempty :: Step f b

mappend :: Step f b -> Step f b -> Step f b

mconcat :: [Step f b] -> Step f b