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

Safe HaskellNone
LanguageHaskell2010

Control.Varying.Core

Description

 

Synopsis

Documentation

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.

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 => Var m () a -> m () Source

Loop over a Var that takes no input value.

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

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

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

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

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.

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.

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.

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.

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.

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

(<~) :: 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.

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 a stream of Char - whatever. Similar to the State monad. 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

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.

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
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.

Monad m => Applicative (Var m a) Source

Vars are applicative.

 (,) <$> pure True <*> var "Applicative"
(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.

(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.

(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.