varying-0.1.4.0: Automaton based varying values, event streams and tweening.

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

Control.Varying.Core

Contents

Description

Values that change over a given domain.

Varying values take some input (the domain ~ time, place, etc) and produce a sample and a new varying value. 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

data Var m b c Source

The vessel of a varying value. A Var is a structure that contains a value that changes over some input. That input could be time (Float, Double, etc) or Events or Char - whatever. It's a kind of Mealy machine (an automaton) with effects.

Constructors

Var 

Fields

  • runVar :: b -> m (c, Var m b c)

    Given an input value, return a computation that effectfully produces an output value (a sample) and a Var for producing the next sample.

Instances

(Applicative m, Monad m) => Category * (Var 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.

Methods

id :: Var m a a

(.) :: Var m b c -> Var m a b -> Var m a c

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

Vars 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

Methods

arr :: (b -> c) -> Var m b c

first :: Var m b c -> Var m (b, d) (c, d)

second :: Var m b c -> Var m (d, b) (d, c)

(***) :: Var m b c -> Var m b' c' -> Var m (b, b') (c, c')

(&&&) :: Var m b c -> Var m b c' -> Var m b (c, c')

(Applicative m, Monad m) => Functor (Var m b) Source

You can transform the sample value of any Var:

 fmap (*3) $ accumulate (+) 0

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

Methods

fmap :: (a -> c) -> Var m b a -> Var m b c

(<$) :: a -> Var m b c -> Var m b a

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

Vars are applicative.

 (,) <$> pure True <*> var "Applicative"

Methods

pure :: b -> Var m a b

(<*>) :: Var m a (b -> c) -> Var m a b -> Var m a c

(*>) :: Var m a b -> Var m a c -> Var m a c

(<*) :: Var m a b -> Var m a c -> Var m a b

(Applicative m, Monad m, Floating b) => Floating (Var m a b) Source

Vars can be written as floats.

 let v = pi ~> accumulate (*) 0.0

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

Methods

pi :: Var m a b

exp :: Var m a b -> Var m a b

log :: Var m a b -> Var m a b

sqrt :: Var m a b -> Var m a b

(**) :: Var m a b -> Var m a b -> Var m a b

logBase :: Var m a b -> Var m a b -> Var m a b

sin :: Var m a b -> Var m a b

cos :: Var m a b -> Var m a b

tan :: Var m a b -> Var m a b

asin :: Var m a b -> Var m a b

acos :: Var m a b -> Var m a b

atan :: Var m a b -> Var m a b

sinh :: Var m a b -> Var m a b

cosh :: Var m a b -> Var m a b

tanh :: Var m a b -> Var m a b

asinh :: Var m a b -> Var m a b

acosh :: Var m a b -> Var m a b

atanh :: Var m a b -> Var m a b

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

Vars can be written as fractionals.

 let v = 2.5 ~> accumulate (+) 0

which will add 2.5 each step.

Methods

(/) :: Var m a b -> Var m a b -> Var m a b

recip :: Var m a b -> Var m a b

fromRational :: Rational -> Var m a b

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

Vars can be written as numbers.

 let v = 1 ~> accumulate (+) 0

which will sum the natural numbers.

Methods

(+) :: Var m a b -> Var m a b -> Var m a b

(-) :: Var m a b -> Var m a b -> Var m a b

(*) :: Var m a b -> Var m a b -> Var m a b

negate :: Var m a b -> Var m a b

abs :: Var m a b -> Var m a b

signum :: Var m a b -> Var m a b

fromInteger :: Integer -> Var m a b

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

Vars can be monoids

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

Methods

mempty :: Var m a b

mappend :: Var m a b -> Var m a b -> Var m a b

mconcat :: [Var m a b] -> Var m a b

Creating varying values

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

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

var is also equivalent to arr.

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

getsFile :: Var 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 varying values are stepped and sampled:

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

var :: Applicative a => (b -> c) -> Var a b c Source

Lift a pure computation into a Var.

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

Lift a monadic computation into a Var.

mkState Source

Arguments

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

state transformer

-> s

intial state

-> Var m a b 

Create a Var from a state transformer.

Composing varying values

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

(<~) :: Monad m => Var m b c -> Var m a b -> Var m a c infixl 1 Source

Same as ~> with flipped parameters.

(~>) :: Monad m => Var m a b -> Var m b c -> Var m a c infixr 1 Source

Connects two Vars by chaining the first's output into the input of the second. This is the defacto Var composition method and in fact . is an alias of <~, which is just ~> flipped.

Adjusting and accumulating

delay :: Monad m => b -> Var m a b -> Var m a b Source

Delays the given Var by one sample using a parameter as the first sample. This enables the programmer to create Vars that depend on themselves for values. For example:

let v = 1 + delay 0 v in testVar_ v

accumulate :: Monad m => (c -> b -> c) -> c -> Var m b c Source

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

Sampling varying values (running, entry points)

The easiest way to sample a Var is to run it in the desired monad with runVar. This will give you a sample value and a new Var bundled up in a tuple:

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

Much like Control.Monad.State there are other entry points for running varying values like evalVar, execVar. There are also extra control structures like loopVar and whileVar and more.

evalVar :: Functor m => Var m a b -> a -> m b Source

Iterate a Var once and return the sample value.

execVar :: Functor m => Var m a b -> a -> m (Var m a b) Source

Iterate a Var once and return the next Var.

loopVar :: Monad m => a -> Var m a a -> m a Source

Loop over a Var that produces its own next input value.

loopVar_ :: (Functor m, Monad m) => Var m () a -> m () Source

Loop over a Var that takes no input value.

whileVar Source

Arguments

:: Monad m 
=> (a -> Bool)

The predicate to evaluate samples.

-> a

The initial input/sample value.

-> Var m a a

The Var to iterate

-> m a

The last sample

Iterate a Var that produces its own next input value until the given predicate fails.

whileVar_ :: Monad m => (a -> Bool) -> Var m () a -> m a Source

Iterate a Var that requires no input until the given predicate fails.

Testing varying values

testVar :: (Read a, Show b) => Var IO a b -> IO () Source

A utility function for testing Vars that require input. The input must have a Read instance. Use this in GHCI to step through your Vars by typing the input and hitting return.

testVar_ :: Show b => Var IO () b -> IO () Source

A utility function for testing Vars that don't require input. Use this in GHCI to step through your Vars using the return key.

testWhile_ :: Show a => (a -> Bool) -> Var IO () a -> IO () Source

A utility function for testing Vars that don't require input. Runs a Var printing each sample until the given predicate fails.

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

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

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

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

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

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