auto-0.2.0.5: Denotative, locally stateful programming DSL & platform

Copyright(c) Justin Le 2015
LicenseMIT
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Auto

Contents

Description

This module serves as the main entry point for the library; these are all basically re-exports. The re-exports are chosen so you can start doing "normal things" off the bat, including all of the types used in this library.

Conspicuously missing are the most of the tools for working with Interval, Blip streams, switches, and the "collection" autos; those are all pretty heavy, and if you do end up working with any of those tools, simply importing the appropriate module should give you all you need.

See the tutorial if you need help getting started!

Synopsis

Types

Auto

data Auto m a b Source

The Auto type. For this library, an Auto semantically representsdenotes a a relationship/ between an input and an output that is preserved over multiple steps, where that relationship is (optionally) maintained within the context of a monad.

A lot of fancy words, I know...but you can think of an Auto as nothing more than a "stream transformer". A stream of sequential inputs come in one at a time, and a stream of outputs pop out one at a time, as well.

Using the streamAuto function, you can "unwrap" the inner stream transformer from any Auto: if a :: Auto m a b, streamAuto lets you turn it into an [a] -> m [b]. "Give me a stream of as, one at a time, and I'll give you a list of bs, matching a relationship to your stream of as."

-- unwrap your inner [a] -> m [b]!
streamAuto :: Monad m => Auto m a b -> ([a] -> m [b])

There's a handy type synonym Auto' for relationships that don't really need a monadic context; the m is just Identity:

type Auto' = Auto Identity

So if you had an a :: Auto' a b, you can use streamAuto' to "unwrap" the inner stream transformer, [a] -> [b].

-- unwrap your inner [a] -> [b]!
streamAuto' :: Auto' a b -> ([a] -> [b])

All of the Autos given in this library maintain some sort of semantic relationship between streams --- for some, the outputs might be the inputs with a function applied; for others, the outputs might be the cumulative sum of the inputs.

See the tutorial for more information!

Operationally, an Auto m a b is implemented as a "stateful function". A function from an a where, every time you "apply" it, you get a b and an "updated Auto"/function with updated state.

You can get this function using stepAuto:

stepAuto :: Auto m a b -> (a -> m (b, Auto m a b))

Or, for Auto', stepAuto':

stepAuto' :: Auto' a b -> (a -> (b, Auto' a b))

"Give me an a and I'll give you a b and your "updated" Auto".

Autos really are mostly useful because they can be composed, chained, and modified using their various typeclass instances, like Category, Applicative, Functor, Arrow, etc., and also with the combinators in this library. You can build complex programs as a complex Auto by building up smaller and smaller components. See the tutorial for more information on this.

This type also contains information on its own serialization, so you can serialize and re-load the internal state to binary or disk. See the "serialization" section in the documentation for Control.Auto.Core, or the documentation for mkAutoM for more details.

Instances

Monad m => Category * (Auto m)

Gives the ability to "compose" two Autos; feeds the input stream into the first, feeds that output stream into the second, and returns as a result the output stream of the second.

Monad m => Arrow (Auto m)

Gives us arr, which is a "stateless" Auto that behaves just like a function; its outputs are the function applied the corresponding inputs.

>>> streamAuto' (arr negate) [1..10]
[-1,-2,-3,-4,-5,-6,-7,-8,-9,-10]

Also allows you to have an Auto run on only the "first" or "second" field in an input stream that is tuples...and also allows Autos to run side-by-side on an input stream of tuples (run each on either tuple field).

>>> streamAuto' (sumFrom 0) [4,6,8,7]
[4,10,18,25]
>>> streamAuto' (first (sumFrom 0)) [(4,True),(6,False),(8,False),(7,True)]
[(4,True),(10,False),(18,False),(25,True)]
>>> streamAuto' (productFrom 1) [1,3,5,2]
[1,3,15,30]
>>> streamAuto' (sumFrom 0 *** productFrom 1) [(4,1),(6,3),(8,5),(7,2)]
[(4,1),(10,3),(18,15),(25,30)]

Most importantly, however, allows for "proc" notation; see the tutorial! for more details.

Monad m => ArrowChoice (Auto m)

Allows you to have an Auto only act on "some" inputs (only on Lefts, for example), and be "paused" otherwise.

>>> streamAuto' (sumFrom 0) [1,4,2,5]
[1,5,7,12]
>>> streamAuto' (left (sumFrom 0)) [Left 1, Right 'a', Left 4, Left 2, Right 'b', Left 5]
[Left 1, Right 'a', Left 5, Left 6, Right 'b', Left 12]

Again mostly useful for "proc" notation, with branching.

MonadFix m => ArrowLoop (Auto m)

Finds the fixed point of self-referential Autos (for example, feeding the output stream of an Auto to itself). Mostly used with proc notation to allow recursive bindings.

Monad m => Strong (Auto m)

See Arrow instance.

Monad m => Choice (Auto m)

See ArrowChoice instance

MonadFix m => Costrong (Auto m)

See ArrowLoop instance

Monad m => Profunctor (Auto m)

lmap lets you map over the input stream, and rmap lets you map over the output stream. Note that, as with all Profunctors, rmap is fmap.

(Monad m, Alternative m) => Alternative (Auto m a)

When the underlying 'Monad'/'Applicative' m is an Alternative, fork the input through each one and "squish" their results together inside the Alternative context. Somewhat rarely used, because who uses an Alternative m?

>>> streamAuto (arrM (mfilter even . Just)) [1..10]
Nothing
>>> streamAuto (arrM (Just . negate)) [1..10]
Just [-1,-2,-3,-4,-5,-6,-7,-8,-9,-10]
>>> streamAuto (arrM (mfilter even . Just)) <|> arrM (Just . negate)) [1..10]
Just [-1,2,-3,4,-5,6,-7,8,-9,10]
Monad m => Functor (Auto m a)

Maps over the output stream of the Auto.

>>> streamAuto' (sumFrom 0) [1..10]
[1,3,6,10,15,21,28,36,45,55]
>>> streamAuto' (show <$> sumFrom 0) [1..10]
["1","3","6","10","15","21","28","36","45","55"]
Monad m => Applicative (Auto m a)

pure creates the "constant" Auto:

>>> streamAuto' (pure "foo") [1..5]
["foo","foo","foo","foo","foo"]

<*> and liftA2 etc. give you the ability to fork the input stream over many Autos, and recombine the results:

>>> streamAuto' (sumFrom 0) [1..10]
[ 1, 3,  6, 10,  15]
>>> streamAuto' (productFrom 1) [1..10]
[ 1, 2,  6, 24, 120]
>>> streamAuto' (liftA2 (+) (sumFrom 0) (productFrom 1)) [1..5]
[ 2, 5, 12, 34, 135]

For effectful Auto, you can imagine *> as "forking" the input stream through both, and only keeping the result of the second:

effect print *> sumFrom 0

would, for example, behave just like sumFrom 0, except printing the input to IO at every step.

Typeable ((* -> *) -> * -> * -> *) Auto 
(Monad m, Floating b) => Floating (Auto m a b)

A bunch of constant producers, mappers-of-output-streams, and forks-and-recombiners.

(Monad m, Fractional b) => Fractional (Auto m a b)

Fork the input stream and divide the outputs. recip maps recip to the output stream; fromRational will be a constant stream of that Rational, so you can write Autos using numerical literals in code; see Num instance.

(Monad m, Num b) => Num (Auto m a b)

Fork the input stream and add, multiply, etc. the outputs. negate will negate the ouptput stream. fromInteger will be a constant stream of that Integer, so you can write Autos using numerical literals in code:

>>> streamAuto' (sumFrom 0) [1..10]
[1,3,6,10,15,21,28,36,45,55]
>>> streamAuto' (4 + sumFrom 0) [1..10]
[5,7,10,14,19,25,32,40,49,59]
(Monad m, IsString b) => IsString (Auto m a b)

String literals in code will be Autos that constanty produce that string.

>>> take 6 . streamAuto' (onFor 2 . "hello" --> "world") $ repeat ()
["hello","hello","world","world","world","world"]
(Monad m, Monoid b) => Monoid (Auto m a b)

Fork the input stream and mappend the outputs. mempty is a constant stream of memptys, ignoring its input.

>>> streamAuto' (mconcat [arr (take 3), accum (++) ""]) ["hello","world","good","bye"]
["helhello","worhelloworld","goohelloworldgood","byehelloworldgoodbye"]
(Monad m, Semigroup b) => Semigroup (Auto m a b)

Fork the input stream and <> the outputs. See the Monoid instance.

type Auto' = Auto Identity Source

Special case of Auto where the underlying Monad is Identity.

Instead of "wrapping" an [a] -> m [b], it "wraps" an [a] -> [b].

Misc

data Blip a Source

When used in the context of an input or output of an Auto, a Blip a represents a stream that occasionally, at "independent" or "discrete" points, emits a value of type a.

Contrast this to Interval, where things are meant to be "on" or "off" for contiguous chunks at a time; blip streams are "blippy", and Intervals are "chunky".

It's here mainly because it's a pretty useful abstraction in the context of the many combinators found in various modules of this library. If you think of an Auto m a (Blip b) as producing a "blip stream", then there are various combinators and functions that are specifically designed to manipulate blip streams.

For the purposes of the semantics of what Blip is supposed to represent, its constructors are hidden. (Almost) all of the various Blip combinators (and its very useful Functor instance) "preserve Blipness" --- one-at-a-time occurrences remain one-at-a-time under all of these combinators, and you should have enough so that direct access to the constructor is not needed.

If you are creating a framework, library, or backend, you might want to manually create blip stream-producing Autos for your users to access. In this case, you can import the constructors and useful internal (and, of course, semantically unsafe) functions from Control.Auto.Blip.Internal.

Instances

Functor Blip 
Show a => Show (Blip a) 
Generic (Blip a) 
Semigroup a => Monoid (Blip a)

Merge two blip streams together; the result emits with either of the two merged streams emit. When both emit at the same time, emit the result of <>-ing the values together.

Serialize a => Serialize (Blip a) 
NFData a => NFData (Blip a) 
Semigroup a => Semigroup (Blip a)

Merge two blip streams together; the result emits with either of the two merged streams emit. When both emit at the same time, emit the result of <>-ing the values together.

Typeable (* -> *) Blip 
type Rep (Blip a) 

type Interval m a b = Auto m a (Maybe b) Source

Represents a relationship between an input and an output, where the output can be "on" or "off" (using Just and Nothing) for contiguous chunks of time.

Just a type alias for Auto m a (Maybe b). If you ended up here with a link...no worries! If you see Interval m a b, just think Auto m a (Maybe b) for type inference/type checking purposes.

If you see something of type Interval, you can rest assured that it has "interval semantics" --- it is on and off for meaningfully contiguous chunks of time, instead of just on and off willy nilly. If you have a function that expects an Interval, then the function expects its argument to behave in this way.

type Interval' a b = Auto' a (Maybe b) Source

Interval, specialized with Identity as its underlying Monad. Analogous to Auto' for Auto.

Working with Auto

Running

stepAuto Source

Arguments

:: Monad m 
=> Auto m a b

the Auto to step

-> a

the input

-> m (b, Auto m a b)

the output, and the updated Auto'.

Runs the Auto through one step.

That is, given an Auto m a b, returns a function that takes an a and returns a b and an "updated"/"next" Auto; an a -> m (b, Auto m a b).

This is the main way of running an Auto "step by step", so if you have some sort of game loop that updates everything every "tick", this is what you're looking for. At every loop, gather input a, feed it into the Auto, "render" the result b, and get your new Auto to run the next time.

Here is an example with sumFrom 0, the Auto whose output is the cumulative sum of the inputs, and an underying monad of Identity. Here,

stepAuto :: Auto Identity Int Int
         -> (Int -> Identity (Int, Auto Identity Int Int))

Every time you "step", you give it an Int and get a resulting Int (the cumulative sum) and the "updated Auto", with the updated accumulator.

>>> let a0 :: Auto Identity Int Int
        a0 = sumFrom 0
>>> let Identity (res1, a1) = stepAuto a0 4      -- run with 4
>>> res1
4                -- the cumulative sum, 4
>>> let Identity (res2, a2) = stepAuto a1 5      -- run with 5
>>> res2
9                -- the cumulative sum, 4 + 5
>>> let Identity (res3, _ ) = stepAuto a2 3      -- run with 3
>>> res3
12               -- the cumulative sum, 4 + 5 + 3

By the way, for the case where your Auto is under Identity, we have a type synomym Auto'...and a convenience function to make "running" it more streamlined:

>>> let a0 :: Auto' Int Int
        a0 = sumFrom 0
>>> let (res1, a1) = stepAuto' a0 4          -- run with 4
>>> res1
4                -- the cumulative sum, 4
>>> let (res2, a2) = stepAuto' a1 5          -- run with 5
>>> res2
9                -- the cumulative sum, 4 + 5
>>> let (res3, _ ) = stepAuto' a2 3          -- run with 3
>>> res3
12               -- the cumulative sum, 4 + 5 + 3

But, if your Auto actaully has effects when being stepped, stepAuto will execute them:

>>> let a0 :: Auto IO Int Int
        a0 = effect (putStrLn "hey!") *> sumFrom 0
>>> (res1, a1) <- stepAuto a0 4              -- run with 4
hey!         -- IO effect
>>> res1
4                -- the cumulative sum, 4
>>> (res2, a2) <- stepAuto a1 5              -- run with 5
hey!         -- IO effect
>>> res2
9                -- the cumulative sum, 4 + 5
>>> (res3, _ ) <- stepAuto a2 3              -- run with 3
hey!         -- IO effect
>>> res3
12               -- the cumulative sum, 4 + 5 + 3

(Here, effect (putStrLn "hey") is an Auto IO Int (), which ignores its input and just executes putStrLn "hey" every time it is run. When we use *> from Control.Applicative, we "combine" the two Autos together and run them both on each input (4, 5, 3...)...but for the "final" output at the end, we only return the output of the second one, sumFrom 0 (5, 9, 12...))

If you think of an Auto m a b as a "stateful function" a -> m b, then stepAuto lets you "run" it.

In order to directly run an Auto on a stream, an [a], use streamAuto. That gives you an [a] -> m [b].

stepAuto' Source

Arguments

:: Auto' a b

the Auto' to step

-> a

the input

-> (b, Auto' a b)

the output, and the updated Auto'

Runs an Auto' through one step.

That is, given an Auto' a b, returns a function that takes an a and returns a b and an "updated"/"next" Auto'; an a -> (b, Auto' a b).

See stepAuto documentation for motivations, use cases, and more details. You can use this instead of stepAuto when your underyling monad is Identity, and your Auto doesn't produce any effects.

Here is an example with sumFrom 0, the Auto' whose output is the cumulative sum of the inputs

stepAuto' :: Auto' Int Int
          -> (Int -> (Int, Auto' Int Int))

Every time you "step", you give it an Int and get a resulting Int (the cumulative sum) and the "updated Auto'", with the updated accumulator.

>>> let a0 :: Auto' Int Int
        a0 = sumFrom 0
>>> let (res1, a1) = stepAuto' a0 4          -- run with 4
>>> res1
4                -- the cumulative sum, 4
>>> let (res2, a2) = stepAuto' a1 5          -- run with 5
>>> res2
9                -- the cumulative sum, 4 + 5
>>> let (res3, _ ) = stepAuto' a2 3          -- run with 3
>>> res3
12               -- the cumulative sum, 4 + 5 + 3

If you think of an Auto' a b as a "stateful function" a -> b, then stepAuto' lets you "run" it.

In order to directly run an Auto' on a stream, an [a], use streamAuto'. That gives you an [a] -> [b].

evalAuto Source

Arguments

:: Monad m 
=> Auto m a b

Auto to run

-> a

input

-> m b

output

Like stepAuto, but drops the "next Auto" and just gives the result.

evalAuto' Source

Arguments

:: Auto' a b

Auto to run

-> a

input

-> b

output

Like stepAuto', but drops the "next Auto'" and just gives the result. evalAuto for Auto'.

streamAuto Source

Arguments

:: Monad m 
=> Auto m a b

Auto to stream

-> [a]

input stream

-> m [b]

output stream

Stream an Auto over a list, returning the list of results. Does this "lazily" (over the Monad), so with most Monads, this should work fine with infinite lists.

Note that, conceptually, this turns an Auto m a b into an [a] -> m [b].

See streamAuto' for a simpler example; here is one taking advantage of monadic effects:

>>> let a = arrM print *> sumFrom 0 :: Auto IO Int Int
>>> ys <- streamAuto a [1..5]
1                -- IO effects
2
3
4
5
>>> ys
[1,3,6,10,15]    -- the result

a here is like sumFrom 0, except at every step, prints the input item to stdout as a side-effect.

streamAuto' Source

Arguments

:: Auto' a b

Auto' to stream

-> [a]

input stream

-> [b]

output stream

Stream an Auto' over a list, returning the list of results. Does this lazily, so this should work fine with (and is actually somewhat designed for) infinite lists.

Note that conceptually this turns an Auto' a b into an [a] -> [b]

>>> streamAuto' (arr (+3)) [1..10]
[4,5,6,7,8,9,10,11,12,13]
>>> streamAuto' (sumFrom 0) [1..5]
[1,3,6,10,15]
>>> streamAuto' (productFrom 1) . streamAuto' (sumFrom 0) $ [1..5]
[1,3,18,180,2700]
>>> streamAuto' (productFrom 1 . sumFrom 0) $ [1..5]
[1,3,18,180,2700]
>>> streamAuto' id [1..5]
[1,2,3,4,5]

stepAutoN Source

Arguments

:: Monad m 
=> Int

number of times to step the Auto

-> Auto m a b

the Auto to run

-> a

the repeated input

-> m ([b], Auto m a b)

list of outputs and the updated Auto

Streams (in the context of the underlying monad) the given Auto with a stream of constant values as input, a given number of times. After the given number of inputs, returns the list of results and the next/updated Auto, in the context of the underlying monad.

stepAutoN n a0 x = overList a0 (replicate n x)

See stepAutoN' for a simpler example; here is one taking advantage of monadic effects:

>>> let a = arrM print *> sumFrom 0 :: Auto IO Int Int
>>> (ys, a') <- stepAutoN 5 a 3
3                -- IO effects
3
3
3
3
>>> ys
[3,6,9,12,15]    -- the result
>>> (ys'', _) <- stepAutoN 5 a' 5
5                -- IO effects
5
5
5
5
>>> ys''
[20,25,30,35,50] -- the result

a here is like sumFrom 0, except at every step, prints the input item to stdout as a side-effect.

stepAutoN' Source

Arguments

:: Int

number of times to step the Auto'

-> Auto' a b

the Auto' to run

-> a

the repeated input

-> ([b], Auto' a b)

list of outputs and the updated Auto'

Streams the given Auto' with a stream of constant values as input, a given number of times. After the given number of inputs, returns the list of results and the next/updated Auto.

stepAutoN' n a0 x = overList' a0 (replicate n x)
>>> let (ys, a') = stepAutoN' 5 (sumFrom 0) 3
>>> ys
[3,6,9,12,15]
>>> let (ys', _) = stepAutoN' 5 a' 5
>>> ys'
[20,25,30,35,40]

Serializing

See the header of the "serializing" section of Control.Auto.Core for more detail on how these work.

encodeAuto :: Auto m a b -> ByteString Source

Encode an Auto and its internal state into a ByteString.

decodeAuto :: Auto m a b -> ByteString -> Either String (Auto m a b) Source

Resume an Auto from its ByteString serialization, giving a Left if the deserialization is not possible.

readAuto Source

Arguments

:: FilePath

filepath to read from

-> Auto m a b

Auto to resume

-> IO (Either String (Auto m a b)) 

Give a FilePath and an Auto, and readAuto will attempt to resume the saved state of the Auto from disk, reading from the given FilePath. Will return Left upon a decoding error, with the error, and Right if the decoding is succesful.

writeAuto Source

Arguments

:: FilePath

filepath to write to

-> Auto m a b

Auto to serialize

-> IO () 

Given a FilePath and an Auto, serialize and freeze the state of the Auto as binary to that FilePath.

unserialize :: Monad m => Auto m a b -> Auto m a b Source

Takes an Auto that is serializable/resumable and returns an Auto that is not. That is, when it is "saved", saves no data, and when it is "resumed", resets itself back to the initial configuration every time; in other words, decodeAuto (unserialize a) bs = Right (unserialize a). Trying to "resume" it will just always give itself, unchanged.

Strictness

forcer :: NFData a => Auto m a a Source

A special Auto that acts like the id Auto, but forces results as they come through to be fully evaluated, when composed with other Autos.

TODO: Test if this really works

seqer :: Auto m a a Source

A special Auto that acts like the id Auto, but forces results as they come through to be evaluated to Weak Head Normal Form, with seq, when composed with other Autos.

TODO: Test if this really works

Internal monad

hoistA Source

Arguments

:: (Monad m, Monad m') 
=> (forall c. m c -> m' c)

monad morphism; the natural transformation

-> Auto m a b 
-> Auto m' a b 

Swaps out the underlying Monad of an Auto using the given monad morphism "transforming function", a natural transformation.

Basically, given a function to "swap out" any m a with an m' a, it swaps out the underlying monad of the Auto.

This forms a functor, so you rest assured in things like this:

hoistA id == id
hoistA f a1 . hoistA f a2 == hoistA f (a1 . a2)

generalizeA :: Monad m => Auto' a b -> Auto m a b Source

Generalizes an Auto' a b to an Auto m a b' for any Monad m, using hoist.

You generally should be able to avoid using this if you never directly write any Auto's and always write 'Auto m' parameterized over all Monads, but...in case you import one from a library or something, you can use this.

Auto constructors

arrM Source

Arguments

:: (a -> m b)

monadic function

-> Auto m a b 

Applies the given "monadic function" (function returning a monadic action) to every incoming item; the result is the result of executing the action returned.

Note that this essentially lifts a "Kleisli arrow"; it's like arr, but for "monadic functions" instead of normal functions:

arr  :: (a -> b)   -> Auto m a b
arrM :: (a -> m b) -> Auto m a b
arrM f . arrM g == arrM (f <=< g)

One neat trick you can do is that you can "tag on effects" to a normal Auto by using *> from Control.Applicative. For example:

>>> let a = arrM print *> sumFrom 0
>>> ys <- streamAuto a [1..5]
1                -- IO output
2
3
4
5
>>> ys
[1,3,6,10,15]    -- the result

Here, a behaves "just like" sumFrom 0...except, when you step it, it prints out to stdout as a side-effect. We just gave automatic stdout logging behavior!

arrD Source

Arguments

:: Serialize b 
=> (a -> b)

function to apply

-> b

initial value

-> Auto m a b 

Like arr, but applies the function to the previous value of the input, instead of the current value. Used for the same purposes as lastVal: to manage recursive bindings.

Warning: Don't use this to do imperative programming!

arrD id == lastVal
>>> streamAuto' (arrD negate 100) [1..10]
[100,-1,-2,-3,-4,-5,-6,-7,-8,-9]

from Accumulators

Result-first

accum Source

Arguments

:: Serialize b 
=> (b -> a -> b)

accumulating function

-> b

initial accumulator

-> Auto m a b 

Construct an Auto from a "folding" function: b -> a -> b yields an Auto m a b. Basically acts like a foldl or a scanl. There is an internal accumulator that is "updated" with an a at every step. Must be given an initial accumulator.

Example: an Auto that sums up all of its input.

>>> let summer = accum (+) 0
>>> let (sum1, summer')  = stepAuto' summer 3
>>> sum1
3
>>> let (sum2, summer'') = stepAuto' summer' 10
>>> sum2
13
>>> streamAuto'  summer'' [1..10]
[14,16,19,23,28,34,41,49,58,68]

If your accumulator b does not have a Serialize instance, then you should either write a meaningful one, or throw away serializability and use accum_.

accum_ Source

Arguments

:: (b -> a -> b)

accumulating function

-> b

intial accumulator

-> Auto m a b 

A version of accum, where the internal accumulator isn't serialized. It can be "saved" and "loaded", but the state is lost in the process.

See accum for more details.

Useful if your accumulator b cannot have a meaningful Serialize instance.

accumM Source

Arguments

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

(monadic) accumulating function

-> b

initial accumulator

-> Auto m a b 

Construct an Auto from a "monadic" "folding" function: b -> a -> m b yields an Auto m a b. Basically acts like a foldM or scanM (if it existed). here is an internal accumulator that is "updated" with an input a with the result of the executed m b at every step. Must be given an initial accumulator.

See accum for more details.

If your accumulator b does not have a Serialize instance, then you should either write a meaningful one, or throw away serializability and use accumM_.

accumM_ Source

Arguments

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

(monadic) accumulating function

-> b

initial accumulator

-> Auto m a b 

A version of 'accumM_, where the internal accumulator isn't serialized. It can be "saved" and "loaded", but the state is lost in the process.

See accumM for more details.

Useful if your accumulator b cannot have a meaningful Serialize instance.

Initial accumulator-first

accumD Source

Arguments

:: Serialize b 
=> (b -> a -> b)

accumulating function

-> b

initial accumulator

-> Auto m a b 

A "delayed" version of accum, where the first output is the initial state of the accumulator, before applying the folding function. Useful in recursive bindings.

>>> let summerD = accumD (+) 0
>>> let (sum1, summerD')  = stepAuto' summerD 3
>>> sum1
0
>>> let (sum2, summerD'') = stepAuto' summerD' 10
>>> sum2
3
>>> streamAuto'  summerD'' [1..10]
[13,14,16,19,23,28,34,41,49,58]

(Compare with the example in accum)

accumD_ Source

Arguments

:: (b -> a -> b)

accumulating function

-> b

intial accumulator

-> Auto m a b 

The non-resuming/non-serializing version of accumD.

accumMD Source

Arguments

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

(monadic) accumulating function

-> b

initial accumulator

-> Auto m a b 

A "delayed" version of accumM, where the first output is the initial state of the accumulator, before applying the folding function. Useful in recursive bindings.

accumMD_ Source

Arguments

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

(monadic) accumulating function

-> b

initial accumulator

-> Auto m a b 

The non-resuming/non-serializing version of accumMD.

from State transformers

mkState Source

Arguments

:: Serialize s 
=> (a -> s -> (b, s))

state transformer

-> s

intial state

-> Auto m a b 

Construct an Auto from a state transformer: an a -> s -> (b, s) gives you an Auto m a b, for any Monad m. At every step, it takes in the a input, runs the function with the stored internal state, returns the b result, and now contains the new resulting state. You have to intialize it with an initial state, of course.

From the "stream transformer" point of view, this is rougly equivalent to mapAccumL from Data.List, with the function's arguments and results in the backwards order.

streamAuto' (mkState f s0) = snd . mapAccumL (\s x -> swap (f x s))

Try not to use this if it's ever avoidable, unless you're a framework developer or something. Try make something by combining/composing the various Auto combinators.

If your state s does not have a Serialize instance, then you should either write a meaningful one, provide the serialization methods manually with mkState', or throw away serializability and use mkState_.

mkStateM Source

Arguments

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

(monadic) state transformer

-> s

initial state

-> Auto m a b 

Construct an Auto from a "monadic" state transformer: a -> s -> m (b, s) gives you an Auto m a b. At every step, it takes in the a input, runs the function with the stored internal state and "executes" the m (b, s) to get the b output, and stores the s as the new, updated state. Must be initialized with an initial state.

Try not to use this if it's ever avoidable, unless you're a framework developer or something. Try make something by combining/composing the various Auto combinators.

This version is a wrapper around mkAuto, that keeps track of the serialization and re-loading of the internal state for you, so you don't have to deal with it explicitly.

If your state s does not have a Serialize instance, then you should either write a meaningful one, provide the serialization methods manually with mkStateM', or throw away serializability and use mkStateM_.

mkState_ Source

Arguments

:: (a -> s -> (b, s))

state transformer

-> s

initial state

-> Auto m a b 

A version of mkState, where the internal state isn't serialized. It can be "saved" and "loaded", but the state is lost in the process.

See mkState for more details.

Useful if your state s cannot have a meaningful Serialize instance.

mkStateM_ Source

Arguments

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

(monadic) state transformer

-> s

initial state

-> Auto m a b 

A version of mkStateM, where the internal state isn't serialized. It can be "saved" and "loaded", but the state is lost in the process.

See mkStateM for more details.

Useful if your state s cannot have a meaningful Serialize instance.

Generators

Effects

effect Source

Arguments

:: m b

monadic action to contually execute.

-> Auto m a b 

To get every output, executes the monadic action and returns the result as the output. Always ignores input.

This is basically like an "effectful" pure:

pure   :: b   -> Auto m a b
effect :: m b -> Auto m a b

The output of pure is always the same, and the output of effect is always the result of the same monadic action. Both ignore their inputs.

Fun times when the underling Monad is, for instance, Reader.

>>> let a = effect ask    :: Auto (Reader b) a b
>>> let r = evalAuto a () :: Reader b b
>>> runReader r "hello"
"hello"
>>> runReader r 100
100

If your underling monad has effects (IO, State, Maybe, Writer, etc.), then it might be fun to take advantage of *> from Control.Applicative to "tack on" an effect to a normal Auto:

>>> let a = effect (modify (+1)) *> sumFrom 0 :: Auto (State Int) Int Int
>>> let st = streamAuto a [1..10]
>>> let (ys, s') = runState st 0
>>> ys
[1,3,6,10,15,21,28,36,45,55]
>>> s'
10

Out Auto a behaves exactly like sumFrom 0, except at each step, it also increments the underlying/global state by one. It is sumFrom 0 with an "attached effect".

Iterators

iterator Source

Arguments

:: Serialize b 
=> (b -> b)

iterating function

-> b

starting value and initial output

-> Auto m a b 

Analogous to iterate from Prelude. Keeps accumulator value and continually applies the function to the accumulator at every step, outputting the result.

The first result is the initial accumulator value.

>>> take 10 . streamAuto' (iterator (*2) 1) $ repeat ()
[1, 2, 4, 8, 16, 32, 64, 128, 256, 512]

iterator_ Source

Arguments

:: (b -> b)

iterating function

-> b

starting value and initial output

-> Auto m a b 

The non-resuming/non-serializing version of iterator.

iteratorM Source

Arguments

:: (Serialize b, Monad m) 
=> (b -> m b)

(monadic) iterating function

-> b

starting value and initial output

-> Auto m a b 

Like iterator, but with a monadic function.

iteratorM_ Source

Arguments

:: Monad m 
=> (b -> m b)

(monadic) iterating function

-> b

starting value and initial output

-> Auto m a b 

The non-resuming/non-serializing version of iteratorM.

Common Autos and combinators

Processes

sumFrom Source

Arguments

:: (Serialize a, Num a) 
=> a

initial count

-> Auto m a a 

The stream of outputs is the cumulative/running sum of the inputs so far, starting with an initial count.

The first output takes into account the first input. See sumFromD for a version where the first output is the initial count itself.

sumFrom x0 = accum (+) x0

sumFrom_ Source

Arguments

:: Num a 
=> a

initial count

-> Auto m a a 

The non-resuming/non-serializing version of sumFrom.

sumFromD Source

Arguments

:: (Serialize a, Num a) 
=> a

initial count

-> Auto m a a 

Like sumFrom, except the first output is the starting count.

>>> let a = sumFromD 5
>>> let (y1, a') = stepAuto' a 10
>>> y1
5
>>> let (y2, _ ) = stepAuto' a' 3
>>> y2
10
>>> streamAuto' (sumFrom 0) [1..10]
[1,3,6,10,15,21,28,36,45,55]
>>> streamAuto' (sumFromD 0) [1..10]
[0,1,3,6,10,15,21,28,36,45]

It's sumFrom, but "delayed".

Useful for recursive bindings, where you need at least one value to be able to produce its "first output" without depending on anything else.

sumFromD x0 = sumFrom x0 . delay 0
sumFromD x0 = delay x0 . sumFrom x0

sumFromD_ Source

Arguments

:: Num a 
=> a

initial count

-> Auto m a a 

The non-resuming/non-serializing version of sumFromD.

productFrom Source

Arguments

:: (Serialize a, Num a) 
=> a

initial product

-> Auto m a a 

The output is the running/cumulative product of all of the inputs so far, starting from an initial product.

productFrom x0 = accum (*) x0

productFrom_ Source

Arguments

:: Num a 
=> a

initial product

-> Auto m a a 

The non-resuming/non-serializing version of productFrom.

mappender :: (Serialize a, Monoid a) => Auto m a a Source

The output is the running/cumulative mconcat of all of the input seen so far, starting with mempty.

>>> streamauto' mappender . map Last $ [Just 4, Nothing, Just 2, Just 3]
[Last (Just 4), Last (Just 4), Last (Just 2), Last (Just 3)]
>>> streamAuto' mappender ["hello","world","good","bye"]
["hello","helloworld","helloworldgood","helloworldgoodbye"]
mappender = accum mappend mempty

mappender_ :: Monoid a => Auto m a a Source

The non-resuming/non-serializing version of mappender.

mappendFrom Source

Arguments

:: (Serialize a, Semigroup a) 
=> a

initial value

-> Auto m a a 

The output is the running <>-sum (mappend for Semigroup) of all of the input values so far, starting with a given starting value. Basically like mappender, but with a starting value.

>>> streamAuto' (mappendFrom (Max 0)) [Max 4, Max (-2), Max 3, Max 10]
[Max 4, Max 4, Max 4, Max 10]
mappendFrom m0 = accum (<>) m0

lastVal Source

Arguments

:: Serialize a 
=> a

initial value

-> Auto m a a 

An Auto that returns the last value received by it. Given an "initial value" to output first.

From the signal processing world, this is known as the "lag operator" L.

This is (potentially) a very dangerous Auto, because its usage and its very existence opens the door to breaking denotative/declarative style and devolving into imperative style coding. However, when used where it is supposed to be used, it is more or less invaluable, and will be an essential part of many programs.

Its main usage is for dealing with recursive bindings. If you ever are laying out recursive bindings in a high-level/denotative way, you need to have at least one value be able to have a "initial output" without depending on anything else. lastVal and delay allow you to do this.

See the recursive example for more information on the appropriate usage of lastVal and delay.

>>> streamAuto' (lastVal 100) [1..10]
[100,1,2,3,4,5,6,7,8,9]

lastVal_ Source

Arguments

:: a

initial value

-> Auto m a a 

The non-resuming/non-serializing version of lastVal.

delay Source

Arguments

:: Serialize a 
=> a

initial value

-> Auto m a a 

An alias for lastVal; used in contexts where "delay" is more a meaningful description than "last value". All of the warnings for lastVal still apply, so you should probably read it if you haven't :)

delay_ Source

Arguments

:: a

initial value

-> Auto m a a 

The non-resuming/non-serializing version of delay.

count :: (Serialize b, Num b) => Auto m a b Source

A simple Auto that ignores all input; its output stream counts upwards from zero.

>>> take 10 . streamAuto' count $ repeat ()
[0,1,2,3,4,5,6,7,8,9]

Switches

(-->) infixr 1 Source

Arguments

:: Monad m 
=> Interval m a b

initial behavior

-> Auto m a b

final behavior, when the initial behavior turns off.

-> Auto m a b 

"This, then that". Behave like the first Interval (and run its effects) as long as it is "on" (outputting Just). As soon as it turns off (is 'Nothing), it'll "switch over" and begin behaving like the second Auto forever, running the effects of the second Auto, too. Works well if the Autos follow interval semantics from Control.Auto.Interval.

>>> let a1 = whileI (<= 4) --> pure 0
>>> streamAuto' a1 [1..10]
[1, 2, 3, 4, 0, 0, 0, 0, 0, 0]

(whileI only lets items satisfying the predicate pass through as "on", and is "off" otherwise; pure is the Auto that always produces the same output)

Association works in a way that you can "chain" -->s, as long as you have an appropriate Auto (and not Interval) at the end:

>>> let a2 = onFor 3 . sumFrom 0
         --> onFor 3 . sumFrom 100
         --> pure 0
>>> streamAuto' a2 [1..10]
[1,3,6,104,109,115,0,0,0,0]

a --> b --> c associates as a --> (b --> c)

This is pretty invaluable for having Autos "step" through a series of different Autos, progressing their state from one stage to the next. Autos can control when they want to be "moved on" from by turning "off" (outputting Nothing).

Note that recursive bindings work just fine, so:

>>> let a3 = onFor 2 . pure "hello"
         --> onFor 2 . pure "goodbye"
         --> a3
>>> let (res3, _) = stepAutoN' 8 a3 ()
>>> res3
["hello", "hello", "world", "world", "hello", "hello", "world", "world"]

the above represents an infinite loop between outputting "hello" and outputting "world".

For serialization, an extra byte cost is incurred per invocation of -->. For cyclic switches like a3, every time the cycle "completes", it adds another layer of --> byte costs. For example, initially, saving a3 incurs a cost for the two -->s. After a3 loops once, it incurs a cost for another two -->s, so it costs four -->s. After a3 loops another time, it is like a cost of six -->s. So be aware that for cyclic bindings like a3, space for serialization grows at O(n).

By the way, it might be worth contrasting this with <|!> and <|?> from Control.Auto.Interval, which have the same type signatures. Those alternative-y operators always feed the input to both sides, run both sides, and output the first Just. With <|!>, you can "switch back and forth" to the first Auto as soon as the first Auto is "on" (Just) again.

-->, in contrast, runs only the first Auto until it is off (Nothing)...then runs only the second Auto. This transition is one-way, as well.

(-?>) infixr 1 Source

Arguments

:: Monad m 
=> Interval m a b

initial behavior

-> Interval m a b

final behavior, when the initial behavior turns off.

-> Interval m a b 

A variation of -->, where the right hand side can also be an interval/Maybe. The entire result is, then, a Maybe. Probably less useful than --> in most situations.

Blips

emitJusts Source

Arguments

:: (a -> Maybe b)

"predicate" to emit on.

-> Auto m a (Blip b) 

An Auto that runs every input through a a -> Maybe b test and produces a blip stream that emits the value inside every Just result.

Particularly useful with prisms from the lens package, where things like emitJusts (preview _Right) will emit the b whenever the input Either a b stream is a Right.

Warning! Carries all of the same dangers of emitOn. You can easily break blip semantics with this if you aren't sure what you are doing. Remember to only emit at discrete, separate occurences, and not for interval-like (on and off for chunks at a time) things. For interval semantics, we have Control.Auto.Interval.

See the examples of emitOn for more concrete good/bad use cases.

emitOn Source

Arguments

:: (a -> Bool)

predicate to emit on

-> Auto m a (Blip a) 

Produces a blip stream that emits the input value whenever the input satisfies a given predicate.

Warning! This Auto has the capability of "breaking" blip semantics. Be sure you know what you are doing when using this. Blip streams are semantically supposed to only emit at discrete, separate occurrences. Do not use this for interval-like (on and off for chunks at a time) things; each input should be dealt with as a separate thing.

For interval semantics, we have Interval from Control.Auto.Interval.

Good example:

-- is only emitting at discrete blips
emitOn even . iterator (+ 1) 0

Bad examples:

-- is emitting for "durations" or "intervals" of time.
emitOn (< 10) . iterator (+ 1) 0

emitOn (const True) . foo

These bad examples would be good use cases of Interval.

Can be particularly useful with prisms from the lens package, where things like emitOn (has _Right) and emitOn (hasn't _Right) will emit the input Either a b whenever it is or isn't a Right. See emitJusts for more common uses with lens.

fromBlips Source

Arguments

:: a

the "default value" to output when the input is not emitting.

-> Auto m (Blip a) a 

fromBlips d is an Auto that decomposes the incoming blip stream by constantly outputting d except when the stream emits, and outputs the emitted value when it does.

fromBlipsWith Source

Arguments

:: b

the 'default value" to output when the input is not emitting.

-> (a -> b)

the function to apply to the emitted value whenever input is emitting.

-> Auto m (Blip a) b 

fromBlipsWith d f is an Auto that decomposes the incoming blip stream by constantly outputting d except when the stream emits, and outputs the result of applying f to the emitted value when it does.

holdWith :: Serialize a => a -> Auto m (Blip a) a Source

holdWith y0 is an Auto whose output is always the /most recently emitted/ value from the input blip stream. Before anything is emitted, y0 is outputted as a placeholder.

Contrast with hold from Control.Auto.Interval.

holdWith_ :: a -> Auto m (Blip a) a Source

A non-serializing/non-resumable version of holdWith.

perBlip :: Monad m => Auto m a b -> Auto m (Blip a) (Blip b) Source

Takes an Auto m a b (an Auto that turns incoming as into outputting bs) into an Auto m (Blip a) (Blip b); the original Auto is lifted to only be applied to emitted contents of a blip stream.

When the stream emits, the original Auto is "stepped" with the emitted value; when it does not, it is paused and frozen until the next emission.

>>> let sums = perBlip (sumFrom 0)
>>> let blps = eachAt 2 [1,5,2]
>>> take 8 . streamAuto' blps $ repeat ()
[NoBlip, Blip 1, NoBlip, Blip 5, NoBlip, Blip 2, NoBlip, NoBlip]
>>> take 8 . streamAuto' (sums . blps) $ repeat ()
[NoBlip, Blip 1, NoBlip, Blip 6, NoBlip, Blip 8, NoBlip, NoBlip]

never :: Auto m a (Blip b) Source

An Auto that ignores its input and produces a blip stream never emits.

immediately :: Auto m a (Blip a) Source

Produces a blip stream that emits with the first received input value, and never again after that.

Often used with pure:

immediately . pure "Emit me!"

Or, in proc notation:

blp <- immediately -< "Emit me!"

to get a blip stream that emits a given value (eg., "Emit me!") once and stops emitting ever again.

>>> streamAuto' (immediately . pure "Emit me!") [1..5]
[Blip "Emit Me!", NoBlip, NoBlip, NoBlip, NoBlip]

Intervals

onFor Source

Arguments

:: Int

amount of steps to stay "on" for

-> Interval m a a 

For onFor n, the first n items in the output stream are always "on" (passing through with exactly the value of the corresponding input); for the rest, the output stream is always "off", suppressing all input values forevermore.

If a number less than 0 is passed, 0 is used.

during Source

Arguments

:: Monad m 
=> Auto m a b

Auto to lift to work over intervals

-> Auto m (Maybe a) (Maybe b) 

Lifts an Auto m a b (transforming as into bs) into an Auto m (Maybe a) (Maybe b) (or, Interval m (Maybe a) b, transforming intervals of as into intervals of b.

It does this by running the Auuto as normal when the input is "on", and freezing itbeing "off" when the input is off/.

>>> let a1 = during (sumFrom 0) . onFor 2 . pure 1
>>> take 5 . streamAuto' a1 $ repeat ()
[Just 1, Just 2, Nothing, Nothing, Nothing]
>>> let a2 = during (sumFrom 0) . offFor 2 . pure 1
>>> take 5 . streamAuto' a2 $ repeat ()
[Nothing, Nothing, Just 1, Just 2, Just 3]

(Remember that pure x is the Auto that ignores its input and constantly just pumps out x at every step)

Note the difference between putting the sumFrom "after" the offFor in the chain with during (like the previous example) and putting the sumFrom "before":

>>> let a3 = offFor 2 . sumFrom 0 . pure 1
>>> take 5 . streamAuto' a3 $ repeat ()
[Nothing, Nothing, Just 3, Just 4, Just 5]

In the first case (with a2), the output of pure 1 was suppressed by offFor, and during (sumFrom 0) was only summing on the times that the 1's were "allowed through"...so it only "starts counting" on the third step.

In the second case (with a3), the output of the pure 1 is never suppressed, and went straight into the sumFrom 0. sumFrom is always summing, the entire time. The final output of that sumFrom 0 is suppressed at the end with offFor 2.

off :: Interval m a b Source

The output stream is alwayas off, regardless of the input.

Note that any monadic effects of the input Auto when composed with off are still executed, even though their result value is suppressed.

off == pure Nothing

toOn :: Interval m a a Source

The output stream is always on, with exactly the value of the corresponding input.

toOn == arr Just

fromInterval Source

Arguments

:: a

value to output for "off" periods

-> Auto m (Maybe a) a 

An "interval collapsing" Auto. A stream of on/off values comes in; the output is the value of the input when the input is on, and the "default value" when the input is off.

Much like fromMaybe from Data.Maybe.

fromInterval d = arr (fromMaybe d)

Running

interactAuto Source

Arguments

:: Interval' String String

Interval' to run interactively

-> IO (Interval' String String)

final Interval' after it all

Run an Auto' "interactively". Every step grab a string from stdin, and feed it to the Interval'. If the Interval' is "off", ends the session; if it is "on", then prints the output value to stdout and repeat all over again.

If your Auto outputs something other than a String, you can use fmap to transform the output into a String en-route (like fmap show).

If your Auto takes in something other than a String, you can lmap a function to convert the input String to whatever intput your Auto expects.

You can use duringRead or bindRead if you have an Auto' or Interval' that takes something readable, to chug along until you find something non-readable; there's also interactRS which handles most of that for you.

Outputs the final Interval' when the interaction terminates.

interactRS Source

Arguments

:: (Read a, Show b) 
=> Interval' a b

Interval' to run interactively

-> IO (Interval' String String)

final Interval' after it all

Like interact, but instead of taking Interval' String String, takes any Interval' a b as long as a is Read and b is Show.

Will "stop" if either (1) the input is not read-able or (2) the Interval' turns off.

Outputs the final Auto' when the interaction terminates.

Re-exports