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

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

Control.Auto.Collection

Contents

Description

The Autos in this module are all dedicated to managing and working with (possibly dynamic) "collections" of Autos: an Auto where the output stream is typically many output streams collected from running many input streams through many internal Autos.

Particularly useful because a lot of these allow you to add or take away these "channels of inputs" (or "internal Autos") dynamically; so, useful for collections that can be added to or deleted from, like monsters on a map.

These multiplex, merge, or collect input streams through many Autos and output the multiplexed, merged, or collected output streams.

A lot of these Autos take advantaage Interval semantics (Maybe for continuous on/off periods) to signal when they want to be removed or turned off.

For these, the best way to learn them is probably by seeing examples.

If there is a time when you might want collections of things that can be added to or removed from dynamically, this might be what you are looking for.

These collections are indispensible for coding real applications; many examples of them in use are available in the auto-examples project! See those projects for "real-world" guides.

Synopsis

Static collections

zipAuto Source

Arguments

:: Monad m 
=> a

default input value

-> [Auto m a b]

Autos to zip up

-> Auto m [a] [b] 

Give a list of Auto m a b and get back an Auto m [a] [b] --- take a list of a's and feed them to each of the Autos, and collects their output b's.

If the input list doesn't have enough items to give to all of the Autos wrapped, then use the given default value. Any extra items in the input list are ignored.

For an example, we're going to make a list of Autos that output a running sum of all of their inputs, but each starting at a different beginning value:

summerList :: [Auto' Int Int]
summerList = [sumFrom 0, sumFrom 10, sumFrom 20, sumFrom 30]

Then, let's throw it into zipAuto with a sensible default value, 0:

summings0 :: Auto' [Int] [Int]
summings0 = zipAuto 0 summerList

Now let's try it out!

>>> let (r1, summings1) = stepAuto' summings0 [1,2,3,4]
>>> r1
[ 1, 12, 23, 34]
>>> let (r2, summings2) = stepAuto' summings1 [5,5]
>>> r2
[ 6, 17, 23, 34]
>>> let (r3, _        ) = stepAuto' summings2 [10,1,10,1,10000]
>>> r3
[16, 18, 33, 35]

dZipAuto Source

Arguments

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

default input value

-> [Auto m a b]

Autos to zip up

-> Auto m [a] [b] 

Like zipAuto, but delay the input by one step. The first input to all of them is the "default" value, and after that, feeds in the input streams delayed by one.

Let's try the example from zipAuto, except with dZipAuto instead:

summerList :: [Auto' Int Int]
summerList = map sumFrom [0, 10, 20, 30]

summings0 :: Auto' [Int] [Int]
summings0 = dZipAuto 0 summerList

Trying it out:

>>> let (r1, summings1) = stepAuto' summings0 [1,2,3,4]
>>> r1
[ 0, 10, 20, 30]
>>> let (r2, summings2) = stepAuto' summings1 [5,5]
>>> r2
[ 1, 12, 23, 34]
>>> let (r3, summings3) = stepAuto' summings2 [10,1,10,1,10000]
>>> r3
[ 6, 17, 23, 34]
>>> let (r4, _        ) = stepAuto' summings3 [100,100,100,100]
>>> r4
[16, 18, 33, 35]

dZipAuto_ Source

Arguments

:: Monad m 
=> a

default input value

-> [Auto m a b]

Autos to zip up

-> Auto m [a] [b] 

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

zipAutoB Source

Arguments

:: Monad m 
=> [Auto m (Blip a) b]

Autos to zip up

-> Auto m [Blip a] [b] 

Takes a bunch of Autos that take streams streams, and turns them into one Auto that takes a bunch of blip streams and feeds them into each of the original Autos, in order.

It's basically like zipAuto, except instead of taking in normal streams of values, it takes in blip streams of values.

If the input streams ever number less than the number of Autos zipped, the other Autos are stepped assuming no emitted value.

dZipAutoB Source

Arguments

:: (Serialize a, Monad m) 
=> [Auto m (Blip a) b]

Autos to zip up

-> Auto m [Blip a] [b] 

A delayed version of zipAutoB

dZipAutoB_ Source

Arguments

:: Monad m 
=> [Auto m (Blip a) b]

Autos to zip up

-> Auto m [Blip a] [b] 

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

Dynamic collections

dynZip_ :: Monad m => a -> Auto m ([a], Blip [Interval m a b]) [b] Source

A dynamic box of Intervals. Takes a list of inputs to feed to each one, in the order that they were added. Also takes a blip stream, which emits with new Intervals to add to the box.

Add new Intervals to the box however you want with the blip stream.

As soon as an Interval turns "off", the Interval is removed from the box, and its output is silenced.

The adding/removing aside, the routing of the inputs (the first field of the tuple) to the internal Autos and the outputs behaves the same as with zipAuto.

This will be a pretty powerful collection if you ever imagine adding and destroying behaviors dynamically...like spawning new enemies, or something like that.

Let's see an example...here we are going to be throwing a bunch of Autos that count to five and then die into our dynZip_...once every other step.

-- count upwards, then die when you reach 5
countThenDie :: Interval' () Int
countThenDie = onFor 5 . iterator (+1) 1

-- emit a new countThenDie every two steps
throwCounters :: Auto' () (Blip [Interval' () Int])
throwCounters = tagBlips [countThenDie] . every 2

a :: Auto' () [Int]
a = proc _ -> do
        newCounter <- throwCounters -< ()
        dynZip_ ()  -< (repeat (), newCounter)
>>> let (res, _) = stepAutoN' 15 a ()
>>> res
[[], [1            ]
   , [2,           ]
   , [3, 1         ]
   , [4, 2         ]
   , [5, 3, 1      ]
   , [   4, 2      ]
   , [   5, 3, 1   ]
   , [      4, 2   ]
   , [      5, 3, 1]
]

This is a little unweildy, because Autos maybe disappearing out of the thing while you are trying to feed inputs into it. You might be feeding an input to an Auto...but one of the Autos before it on the list has disappeared, so it accidentally goes to the wrong one.

Because of this, it is suggested that you use dynMap_, which allows you to "target" labeled Autos with your inputs.

This Auto is inherently unserializable, but you can use dynZipF for more or less the same functionality, with serialization possible. It's only slightly less powerful...for all intents and purposes, you should be able to use both in the same situations. All of the examples here can be also done with dynZipF.

dynZipF Source

Arguments

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

function to generate a new Interval for each coming k in the blip stream.

-> a

"default" input to feed in

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

Like dynZip_, but instead of taking in a blip stream of Intervals directly, takes in a blip stream of ks to trigger adding more Intervals to the "box", using the given k -> Interval m a b function to make the new Interval to add.

Pretty much all of the power of dynZip_, but with serialization.

See dynZip_ for examples and caveats.

You could theoretically recover the behavior of dynZip_ with dynZipF id, if there wasn't a Serialize constraint on the k.

dynZipF_ Source

Arguments

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

function to generate a new Interval for each coming k in the blip stream.

-> a

"default" input to feed in

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

The non-serializing/non-resuming version of dynZipF. Well, you really might as well use dynZip_, which is more powerful...but maybe using this can inspire more disciplined usage. Also works as a drop-in replacement for dynZipF.

dynMap_ Source

Arguments

:: Monad m 
=> a

"default" input to feed in

-> Auto m (IntMap a, Blip [Interval m a b]) (IntMap b) 

A dynamic box of Autos, indexed by an Int. Takes an IntMap of inputs to feed into their corresponding Autos, and collect all of the outputs into an output IntMap.

Whenever any of the internal Autos return Nothing, they are removed from the collection.

Toy examples here are of limited use, but let's try it out. Here we will have a dynMap_ that feeds each internal Auto back to itself. The result of each is sent directly back to itself.

>>> import qualified Data.IntMap as IM
>>> let dm0 :: Auto' (IM.IntMap Int) (IM.IntMap Int)
        dm0 = proc x -> do
                  initials <- immediately -< [ Just <$> sumFrom 0
                                             , Just <$> sumFrom 10 ]
                  newIs    <- every 3     -< [ Just <$> sumFrom 0  ]
                  dynMap_ (-1) -< (x, initials `mergeL` newIs)
>>> let (res1, dm1) = stepAuto' dm0 mempty
>>> res1
fromList [(0, -1), (1, 9)]
>>> let (res2, dm2) = stepAuto' dm1 (IM.fromList [(0,100),(1,50)])
>>> res2
fromList [(0, 99), (1, 59)]
>>> let (res3, dm3) = stepAuto' dm2 (IM.fromList [(0,10),(1,5)])
>>> res3
fromList [(0, 109), (1, 64), (2, -1)]
>>> let (res4, _  ) = stepAuto' dm3 (IM.fromList [(1,5),(2,5)])
>>> res4
fromList [(0, 108), (1, 69), (2, 4)]

One quirk is that every internal Auto is "stepped" at every step with the default input; gatherMany is a version of this where Autos that do not have a corresponding "input" are left unstepped, and their last output preserved in the aggregate output. As such, gatherMany might be seen more often.

This Auto is inherently unserializable, but you can use dynMapF for more or less the same functionality, with serialization possible. It's only slightly less powerful...for all intents and purposes, you should be able to use both in the same situations. All of the examples here can be also done with dynMapF.

dynMapF Source

Arguments

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

function to generate a new Interval for each coming k in the blip stream.

-> a

"default" input to feed in

-> Auto m (IntMap a, Blip [k]) (IntMap b) 

Like dynMap_, but instead of taking in a blip stream of Intervals directly, takes in a blip stream of ks to trigger adding more Intervals to the "box", using the given k -> Interval m a b function to make the new Interval to add.

Pretty much all of the power of dynMap_, but with serialization.

See dynMap_ for examples and use cases.

You could theoretically recover the behavior of dynMap_ with dynMapF id, if there wasn't a Serialize constraint on the k.

dynMapF_ Source

Arguments

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

function to generate a new Interval for each coming k in the blip stream.

-> a

"default" input to feed in

-> Auto m (IntMap a, Blip [k]) (IntMap b) 

The non-serializing/non-resuming version of dynMapF. Well, you really might as well use dynMap_, which is more powerful...but maybe using this can inspire more disciplined usage. Also works as a drop-in replacement for dynMapF.

Multiplexers

Single input, single output

mux Source

Arguments

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

function to create a new Auto if none at that key already exists.

-> Auto m (k, a) b 

Auto multiplexer. Stores a bunch of internal Autos indexed by a key. At every step, takes a key-input pair, feeds the input to the Auto stored at that key and outputs the output.

If the key given does not yet have an Auto stored at that key, initializes a new Auto at that key by using the supplied function.

Once initialized, these Autos are stored there forever.

You can play around with some combinators from Control.Auto.Switch; for example, with resetOn, you can make Autos that "reset" themselves when given a certain input. switchOnF could be put to use here too in neat ways.

>>> let mx0 = mux (\_ -> sumFrom 0)
>>> let (res1, mx1) = stepAuto' mx0 ("hello", 5)
>>> res1
5
>>> let (res2, mx2) = stepAuto' mx1 ("world", 3)
>>> res2
3
>>> let (res3, mx3) = stepAuto' mx2 ("hello", 4)
>>> res3
9
>>> streamAuto' mx3 [("world", 2), ("foo", 6), ("foo", 1), ("hello", 2)]
[5, 6, 7, 11]

mux_ Source

Arguments

:: (Ord k, Monad m) 
=> (k -> Auto m a b)

function to create a new Auto if none at that key already exists

-> Auto m (k, a) b 

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

Multiple input, multiple output

muxMany Source

Arguments

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

function to create a new Auto if none at that key already exists

-> Auto m (Map k a) (Map k b) 

Auto multiplexer, like mux, except allows update/access of many Autos at a time. Instead of taking in a single key-value pair and outputting a single result, takes in an entire Map of key-value pairs and outputs a Map of key-result pairs.

>>> import qualified Data.Map as M
>>> let mx0 = mux (\_ -> sumFrom 0)
>>> let (res1, mx1) = stepAuto' mx0 (M.fromList [ ("hello", 5)
                                                , ("world", 3) ])
>>> res1
fromList [("hello", 5), ("world", 3)]
>>> let (res2, mx2) = stepAuto' mx1 (M.fromList [ ("hello", 4)
                                                , ("foo"  , 7) ])
>>> res2
fromList [("foo", 7), ("hello", 9)]
>>> let (res3, _  ) = mx2 (M.fromList [("world", 3), ("foo", 1)])
>>> res3
fromList [("foo", 8), ("world", 6)]

See mux for more notes.

muxMany_ Source

Arguments

:: (Ord k, Monad m) 
=> (k -> Auto m a b)

function to create a new Auto if none at that key already exists

-> Auto m (Map k a) (Map k b) 

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

Gathering/accumulating collections

Single input, multiple output

gather Source

Arguments

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

function to create a new Auto if none at that key already exists

-> Auto m (k, a) (Map k b) 

Keeps an internal Map of Intervals and, at every step, the output is the last seen output of every Interval, indexed under the proper key.

At every step, the input is a key-value pair; gather will feed that input value to the Interval under the proper key and update the output map with that new result.

If the key offered the input is not yet a part of the collection, initializes it with the given function.

Any Interval that turns "off" (outputs Nothing) from this will be immediately removed from the collection. If something for that key is received again, it will re-initialize it.

>>> let sumUntil :: Interval' Int Int
        sumUntil = proc x -> do
                       sums <- sumFrom 0     -< x
                       stop <- became (> 10) -< sums
                       before -< (sums, stop)
    -- (a running sum, "on" until the sum is greater than 10)
>>> let gt0 = gather (\_ -> sumUntil)
>>> let (res1, gt1) = stepAuto' gt0 ("hello", 5)
>>> res1
fromList [("hello", 5)]
>>> let (res2, gt2) = stepAuto' gt1 ("world", 7)
>>> res2
fromList [("hello", 5), ("world", 7)]
>>> let (res3, gt3) = stepAuto' gt2 ("foo", 4)
>>> res3
fromList [("foo", 4), ("hello", 5), ("world", 7)]
>>> let (res4, gt4) = stepAuto' gt3 ("world", 8)
>>> res4
fromList [("foo", 4), ("hello", 5)]
>>> streamAuto' gt4 [("world", 2),("bar", 9),("world", 6),("hello", 11)]
[ fromList [("foo", 4), ("hello", 5), ("world", 2)]
, fromList [("bar", 9), ("foo", 4), ("hello", 5), ("world", 2)]
, fromList [("bar", 9), ("foo", 4), ("hello", 5), ("world", 8)]
, fromList [("bar", 9), ("foo", 4), ("world", 8)]
]

In practice this ends up being a very common collection; see the auto-examples project for many examples!

Because everything needs a key, you don't have the fancy "auto-generate new keys" feature of dynMap...however, you could always pull a new key from perBlip enumFromA or something.

Like with mux, combinators from Control.Auto.Switch like resetOn and switchOnF are very useful here!

gather_ Source

Arguments

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

function to create a new Auto if none at that key already exists

-> Auto m (k, a) (Map k b) 

The non-serializing/non-resuming version of gather:

Does serialize the actual Autos themselves; the Autos are all serialized and re-loaded/resumed when 'gather_ f' is resumed.

Does not serialize the "last outputs", so resumed Autos that have not yet been re-run/accessed to get a fresh output are not represented in the output map at first.

gather__ Source

Arguments

:: (Ord k, Monad m) 
=> (k -> Interval m a b)

function to create a new Auto if none at that key already exists

-> Auto m (k, a) (Map k b) 

The non-serializing/non-resuming vervsion of gather:

Serializes neither the Autos themselves nor the "last outputs" --- essentially, serializes/resumes nothing.

gatherMany Source

Arguments

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

function to create a new Auto if none at that key already exists

-> Auto m (Map k a) (Map k b) 

Much like gather, except allows you to pass in multiple key-value pairs every step, to update multiple internal Autos.

>>> import qualified Data.Map as M
>>> let sumUntil :: Interval' Int Int
        sumUntil = proc x -> do
                       sums <- sumFrom 0     -< x
                       stop <- became (> 10) -< sums
                       before -< (sums, stop)
    -- (a running sum, "on" until the sum is greater than 10)
>>> let gm0 = gatherMany (\_ -> sumUntil)
>>> let (res1, gm1) = stepAuto' gm0 (M.fromList [ ("hello", 5)
                                                , ("world", 7)
                                                ])
>>> res1
fromList [("hello", 5), ("world", 7)]
>>> let (res2, gm2) = stepAuto' gm1 (M.fromList [ ("foo", 4)
                                                , ("hello", 3)
                                                ])
>>> res2
fromList [("foo", 4), ("hello", 8), ("world", 7)]
>>> let (res3, gm3) = stepAuto' gm2 (M.fromList [ ("world", 8)
                                                , ("bar", 9)
                                                ])
>>> res3
fromList [("bar", 9), ("foo", 4), ("hello", 8)]
>>> let (res4, _  ) = stepAuto' gm3 (M.fromList [ ("world", 2)
                                                , ("bar", 10)
                                                ])
>>> res4
fromList [("foo", 4), ("hello", 8), ("world", 2)]

See gather for more notes.

gatherMany_ Source

Arguments

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

function to create a new Auto if none at that key already exists

-> Auto m (Map k a) (Map k b) 

The non-serializing/non-resuming version of gatherMany:

Does serialize the actual Autos themselves; the Autos are all serialized and re-loaded/resumed when 'gatherMany_ f' is resumed.

Does not serialize the "last outputs", so resumed Autos that have not yet been re-run/accessed to get a fresh output are not represented in the output map at first.

gatherMany__ Source

Arguments

:: (Ord k, Monad m) 
=> (k -> Interval m a b)

function to create a new Auto if none at that key already exists

-> Auto m (Map k a) (Map k b) 

The non-serializing/non-resuming vervsion of gatherMany:

Serializes neither the Autos themselves nor the "last outputs" --- essentially, serializes/resumes nothing.