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

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

Control.Varying.Core

Contents

Description

Value streams represent values that change over a given domain.

A stream takes some input (the domain e.g. time, place, etc) and when sampled using runVarT - produces a value and a new value stream. This pattern is known as an automaton. varying uses this pattern as its base type with the additon of a monadic computation to create locally stateful signals that change over some domain.

Synopsis

Documentation

type Var a b = VarT Identity a b Source

A value stream parameterized with Identity that takes input of type a and gives output of type b. This is the pure, effect-free version of VarT.

newtype VarT m a b Source

A value stream is a structure that contains a value that changes over some input. It's a kind of Mealy machine (an automaton) with effects. Using runVarT with an input value of type a yields a "step", which is a value of type b and a new VarT for yielding the next value.

Constructors

VarT

Given an input value, return a computation that effectfully produces an output value and a new stream for producing the next sample.

Fields

runVarT :: a -> m (b, VarT m a b)
 

Instances

(Applicative m, Monad m) => Category * (VarT m) Source

A very simple category instance.

  id = var id
  f . g = g >>> f

or

 f . g = f <<< g

It is preferable for consistency (and readability) to use 'plug left' (<<<) and 'plug right' (>>>) instead of (.) where possible.

(Applicative m, Monad m) => Arrow (VarT m) Source

Streams are arrows, which means you can use proc notation.

v = proc a -> do
      ex <- intEventVar -< ()
      ey <- anotherIntEventVar -< ()
      returnA -< (+) <$> ex <*> ey

which is equivalent to

 v = (\ex ey -> (+) <$> ex <*> ey) <$> intEventVar <*> anotherIntEventVar
(Applicative m, Monad m) => Functor (VarT m b) Source

You can transform the sample value of any stream:

 fmap (*3) $ accumulate (+) 0

Will sum input values and then multiply the sum by 3.

(Applicative m, Monad m) => Applicative (VarT m a) Source

Streams are applicative.

 (,) <$> pure True <*> var "Applicative"
(Applicative m, Monad m, Floating b) => Floating (VarT m a b) Source

Streams can be written as floats.

 let v = pi >>> accumulate (*) 0.0

which will attempt (and succeed) to multiply pi by zero every step.

(Applicative m, Monad m, Fractional b) => Fractional (VarT m a b) Source

Streams can be written as fractionals.

 let v = 2.5 >>> accumulate (+) 0

which will add 2.5 each step.

(Applicative m, Monad m, Num b) => Num (VarT m a b) Source

Streams can be written as numbers.

 let v = 1 >>> accumulate (+) 0

which will sum the natural numbers.

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

Streams can be monoids

let v = var (const "Hello ") `mappend` var (const "World!")

Creating value streams

You can create a pure value stream by lifting a function (a -> b) with var:

addsOne :: Monad m => VarT m Int Int
addsOne = var (+1)

var is equivalent to arr.

You can create a monadic value stream by lifting a monadic computation (a -> m b) using varM:

getsFile :: VarT IO FilePath String
getsFile = varM readFile

You can create either with the raw constructor. You can also create your own combinators using the raw constructor, as it allows you full control over how value streams are stepped and sampled:

delay :: Monad m => b -> VarT m a b -> VarT m a b
delay b v = VarT $ a -> return (b, go a v)
    where go a v' = VarT $ a' -> do (b', v'') <- runVarT v' a
                                    return (b', go a' v'')

done :: (Applicative m, Monad m) => b -> VarT m a b Source

Lift a constant value into a stream.

var :: Applicative m => (a -> b) -> VarT m a b Source

Lift a pure computation into a stream.

varM :: Monad m => (a -> m b) -> VarT m a b Source

Lift a monadic computation into a stream.

mkState Source

Arguments

:: Monad m 
=> (a -> s -> (b, s))

state transformer

-> s

intial state

-> VarT m a b 

Create a stream from a state transformer.

Composing value streams

You can compose value streams together using Arrow's >>> and <<< or the synonyms ~> and <~. The "right plug" (>>> and ~>) takes the output from a value stream on the left and "plugs" it into the input of the value stream on the right. The "left plug" does the same thing in the opposite direction. This allows you to write value streams that read naturally.

(<~) :: (Monad m, Applicative m) => VarT m b c -> VarT m a b -> VarT m a c Source

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

(<<<) :: Category k cat => cat b c -> cat a b -> cat a c infixr 1

Right-to-left composition

(>>>) :: Category k cat => cat a b -> cat b c -> cat a c infixr 1

Left-to-right composition

Adjusting and accumulating

delay :: (Monad m, Applicative m) => b -> VarT m a b -> VarT m a b Source

Delays the given stream by one sample using the argument as the first sample. This enables the programmer to create streams that depend on themselves for values. For example:

let v = 1 + delay 0 v in testVar_ v

accumulate :: (Monad m, Applicative m) => (c -> b -> c) -> c -> VarT m b c Source

Accumulates input values using a folding function and yields that accumulated value each sample.

Sampling value streams (running and other entry points)

To sample a stream simply run it in the desired monad with runVarT. This will produce a sample value and a new stream.

do (sample, v') <- runVarT v inputValue

scanVar :: (Applicative m, Monad m) => VarT m a b -> [a] -> m ([b], VarT m a b) Source

Run the stream over the input values, gathering the output values in a list.

stepMany :: (Monad m, Functor m) => VarT m a b -> [a] -> a -> m (b, VarT m a b) Source

Iterate a stream over a list of input until all input is consumed, then iterate the stream using one single input. Returns the resulting output value and the new stream.

Tracing value streams in flight

vtrace :: (Applicative a, Show b) => VarT a b b Source

Trace the sample value of a stream and pass it along as output. This is very useful for debugging graphs of streams.

vstrace :: (Applicative a, Show b) => String -> VarT a b b Source

Trace the sample value of a stream with a prefix and pass the sample along as output. This is very useful for debugging graphs of streams.

vftrace :: Applicative a => (b -> String) -> VarT a b b Source

Trace the sample value after being run through a "show" function. This is very useful for debugging graphs of streams.