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

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

Control.Auto.Blip

Contents

Description

This module provides tools for generating and manipulating "blip streams". The blip stream abstraction is not fundamental to Auto, but rather, like interval, is a very useful semantic tool for the denotation of many programs, games, simulations, and computations in general that you are likely to write with this library.

Synopsis

Blip

In the context of inputs/outputs of Auto, a Blip a represents a "blip stream" that occasionally, in isolated incidents, emits a value of type a.

For example, Auto' a (Blip b) is an Auto' that a stream of a's as input and outputs a *blip stream* that occasionally emits with a b. An Auto' (Blip a) b is an Auto' that takes a *blip stream* that occasionally emits with a a and outputs a stream of b's.

If an Auto takes or outputs a "blip stream", it comes with some "semantic" contracts on to how the stream behaves. The main contract is that your blip stream should only output on (meaningfully) "isolated" incidents, and never on continuous regions of the input stream.

By this, we mean that every emitted value is (conceptually) emitted "alone", and not as a part of continuous on/off chunks.

Example situations

A good example would be, say, a blip stream that emits every time a user/player sends a certain type of command. Or a blip stream that emits every time a slowly-moving value crosses over from positive to negative.

A bad example would be a blip stream that emits when a player doesn't send a certain less-common type of command. Or a blip stream that emits whenever a slowly-moving value is positive or negative.

Contrast with Intervals

Blip streams are contrasted with another semantic tool: stream _intervals_, manipulated with Control.Auto.Interval. Intervals are adjacentcontiguous "chunks" of onoff behavior, and are on or off for contiguous "chunks" at a time. So when deciding whether or not you want to use the semantics of blip streams or the semantics of Interval, consider: is this behavior going to be "on/off" for chunks at a time (such as an interval that is on whenever a slowly-moving value is positive)? Or is it something that is usually "not on", but makes separate, isolated, "blips" --- each emitted value alone and (semantically) isolated from the rest.

Motivations

The main motivations of the semantic concept of blip streams (and why they even exist in the first place) is probably for how well they integrate with Interval semantics and, with intervals, the various powerful switching combinators from Control.Auto.Switch. Many of the combinators in that module are designed so that switches can be "triggered" by blip stream emissions.

Blip streams have many usages, as will be explained later. You'll also find that blip streams work well with their cousins, interval streams. But perhaps the use case that stands out above all (and is alone enough to motivate their existence) is in switching.

"Blip semantics"

We say that a blip stream has "blip semantics" when it is used in a way that its emitted values are "isolated", "alone", "discrete", in this way. When it is not, we say that the stream "breaks" blip semantics.

Note that this can't really be enforced by the types, so if you're a library or framework developer, it's up to you to take care that the blip streams you offer all conform to blip semantics. However, if you're just making an application, you can use most of the combinators in this library/module and not worry.

Also note that in many of these cases, "blip semantics" depends on how the Autos are composed, and what they are composed to. If the value in question is "almost always" positive and only negative at isolated points in time, then such a "blip stream that emits whenever the value is negative" has proper blip semantics. If the value in question is slowly-moving and meandering, and might spend a lot of time negative at a time, then the same blip stream would not preserve blip semantics.

Why semantics are important

Why should you care? I can't tell you want to do, right?

Well, for the same reason that typeclasses like Eq, Functor, and Monad have laws. Yeah, you can make any instance you want that satisfies the types. But almost all of the usefulness of those typeclasses comes from our ability to "reason" about the behavior of their instances, and to be able to develop an intuition about their usage. We would be surprised if we had an Eq instance where x == x and x /= x are both true...and it would completely break down any attempt at understanding what Eq code "means".

You can think of "blip semantics" as being the "laws" of blip streams. If we assume that things follow blip semantics properly, then we can reason about them in a unified and useful way. If we can trust that blip streams actually behave "like blip streams", then blip streams become an extremely useful tool for denoting certain behaviors and programs.

If we can't...then it becomes a lot less useful :)

In particular, one big use case for blip streams (the switching mechanisms Control.Auto.Switch) all only "work well" when your blip streams follow proper semantics.

Combinators preserve semantics

Most of the combinators in this module try their best to preserve blip semantics. That is, you can't use them in a way that will produce a non-semantic-abiding blip stream. You can "trust" them, and if you use only safe combinators, you don't ever have to worry. Well. That much, at least.

There are a few notable exceptions:

Practical examples

There are many practical examples of using blip streams in the various examples in auto-examples, especially from chatbot. There, blip streams are used in many situations, primarily streams for players sending certain commands. It's also used in hangman, to signify player events such as victory, good/bad guesses, etc.

Blip streams work very closely with the various switching combinators in Control.Auto.Switch. If anything, if there is only one reason to use blip streams, it's with the various switching mechanisms in that module. All of the switching combinators rely on the fact that your blip streams follow proper semantics, further emphasizing the importance of conforming to the semantics.

For library, framework, and back-end developers

Remember that this module is only meant to export "safe" combinators that try their best to maintain blip semantics. Think of this module as a useful guideline to help programmers maintain semantics at compile-time, by only exporting not-as-dangerous combinators.

However, all of these rules are for the denotation of your /program logic/. These rules are for the benefit of reasoning about the behavior of your program at the logic level.

As a library or framework or back-end developer, however, you aren't programming at the logic level, but rather at the gritty implementation level. So, you might want to provide blip streams and for your library users or application developers or the game logic you are writing.

For this, you might find the hidden constructors and tools in Control.Auto.Blip.Internal helpful, and there is more information at the documentation for that module.

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) 

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]

Merging

merge Source

Arguments

:: (a -> a -> a)

merging function

-> Blip a

first stream

-> Blip a

second stream

-> Blip a

merged stream

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 applying the given function on the two emitted values.

Note that this might be too strict for some purposes; see mergeL and mergeR for lazier alternatives.

mergeL infixr 5 Source

Arguments

:: Blip a

first stream (higher priority)

-> Blip a

second stream

-> Blip a 

Merges two blip streams together into one, which emits either of the original blip streams emit. If both emit at the same time, the left (first) one is favored.

Lazy on the second stream if the first stream is emitting.

If we discount laziness, this is merge const.

mergeR infixl 5 Source

Arguments

:: Blip a

first stream

-> Blip a

second stream (higher priority)

-> Blip a 

Merges two blip streams together into one, which emits either of the original blip streams emit. If both emit at the same time, the right (second) one is favored.

Lazy on the first stream if the second stream is emitting.

If we discount laziness, this is merge (flip const).

mergeLs :: [Blip a] -> Blip a Source

Merge all the blip streams together into one, favoring the first emitted value.

mergeRs :: [Blip a] -> Blip a Source

Merge all the blip streams together into one, favoring the last emitted value.

foldrB :: (a -> a -> a) -> a -> [Blip a] -> Blip a Source

Merge all of the blip streams together, using the given merging function associating from the right.

foldlB' :: (a -> a -> a) -> a -> [Blip a] -> Blip a Source

Merge all of the blip streams together, using the given merging function associating from the left.

Blip stream creation (dangerous!)

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.

onJusts :: Auto m (Maybe a) (Blip a) Source

An Auto that emits whenever it receives a Just input, with the value inside the Just.

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.

Blip stream collapse

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.

Step/"time" based Blip streams and generators

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]

inB Source

Arguments

:: Int

number of steps before value is emitted.

-> Auto m a (Blip a) 

Produces a blip stream that only emits once, with the input value on the given step number. It emits the input on that many steps.

immediately == inB 1

every Source

Arguments

:: Int

emit every n steps.

-> Auto m a (Blip a) 

every n is an Auto that emits with the incoming inputs on every nth input value. First emitted value is on the nth step.

Will obviously break blip semantics when you pass in 1.

eachAt Source

Arguments

:: Serialize b 
=> Int

emit every n steps

-> [b]

list to emit values from

-> Auto m a (Blip b) 

eachAt n xs is an Auto that ignores its input and creates a blip stream that emits each element of xs one at a time, evey n steps. First emitted value is at step n.

Once the list is exhausted, never emits again.

Obviously breaks blip semantics when you pass in 1.

The process of serializing and resuming this Auto is O(n) space and time with the length of xs. So don't serialize this if you plan on passing an infinite list :) See Control.Auto.Generate for more options.

eachAt n xs == perBlip (fromList xs) . every n

eachAt_ Source

Arguments

:: Int

emit every n steps

-> [b]

list to emit values from

-> Auto m a (Blip b) 

The non-serializing/non-resumable version of eachAt.

Modifying Blip streams

tagBlips Source

Arguments

:: b

value to replace every emitted value with

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

Re-emits every emission from the input blip stream, but replaces its value with the given value.

tagBlips x == modifyBlips (const x)

modifyBlips Source

Arguments

:: (a -> b)

function to modify emitted values with

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

Re-emits every emission from the input blip stream, but applies the given function to the emitted value.

(<&) :: Monad m => Auto m a (Blip b) -> Auto m a (Blip b) -> Auto m a (Blip b) infixr 5 Source

Takes two Autos producing blip streams and returns a "merged" Auto that emits when either of the original Autos emit. When both emit at the same time, the left (first) one is favored.

a1 <& a2 == mergeL <$> a1 <*> a2

(&>) :: Monad m => Auto m a (Blip b) -> Auto m a (Blip b) -> Auto m a (Blip b) infixl 5 Source

Takes two Autos producing blip streams and returns a "merged" Auto that emits when either of the original Autos emit. When both emit at the same time, the right (second) one is favored.

a1 &> a2 == mergeR <$> a1 <*> a2

once :: Auto m (Blip a) (Blip a) Source

Supress all upstream emitted values except for the very first.

notYet :: Auto m (Blip a) (Blip a) Source

Suppress only the first emission coming from upstream, and let all the others pass uninhibited.

lagBlips :: Serialize a => Auto m (Blip a) (Blip a) Source

Takes in a blip stream and outputs a blip stream where each emission is delayed/lagged by one step.

>>> streamAuto' (emitOn (\x -> x `mod` 3 == 0)) [1..9]
>>> [NoBlip, NoBlip, Blip 3, NoBlip, NoBlip, Blip 6, NoBlip, NoBlip, Blip 9]
>>> streamAuto' (lagBlips . emitOn (\x -> x `mod` 3 == 0)) [1..9]
>>> [NoBlip, NoBlip, NoBlip, Blip 3, NoBlip, NoBlip, Blip 6, NoBlip, NoBlip]

lagBlips_ :: Auto m (Blip a) (Blip a) Source

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

filterB Source

Arguments

:: (a -> Bool)

filtering predicate

-> Auto m (Blip a) (Blip a) 

Suppress all upstream emissions when the predicate (on the emitted value) fails.

forkB :: (a -> Bool) -> Auto m (Blip a) (Blip a, Blip a) Source

Forks a blip stream based on a predicate. Takes in one blip stream and produces two: the first emits whenever the input emits with a value that passes the predicate, and the second emits whenever the input emits with a value that doesn't.

joinB :: Auto m (Blip (Blip a)) (Blip a) Source

Collapses a blip stream of blip streams into single blip stream. that emits whenever the inner-nested stream emits.

mapMaybeB :: (a -> Maybe b) -> Auto m (Blip a) (Blip b) Source

Applies the given function to every emitted value, and suppresses all those for which the result is Nothing. Otherwise, lets it pass through with the value in the Just.

takeB Source

Arguments

:: Int

number of emissions to allow to pass

-> Auto m (Blip a) (Blip a) 

takeB n allows only the first n emissions to pass; it suppresses all of the rest.

takeWhileB Source

Arguments

:: (a -> Bool)

filtering predicate

-> Auto m (Blip a) (Blip a) 

Allow all emitted valuesto pass until the first that fails the predicate.

dropB Source

Arguments

:: Int

number of emissions to suppress initially

-> Auto m (Blip a) (Blip a) 

dropB n suppresses the first n emissions from upstream and passes through the rest uninhibited.

dropWhileB Source

Arguments

:: (a -> Bool)

filtering predicate

-> Auto m (Blip a) (Blip a) 

Suppress all emited values until the first one satisfying the predicate, then allow the rest to pass through.

Scanning & Accumulating Blip streams

accumB Source

Arguments

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

folding function

-> b

initial value

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

Accumulates all emissions in the incoming blip stream with a "folding function", with a given starting value. b -> a -> b, with a starting b, gives Auto m (Blip a) (Blip b).

The resulting blip stream will emit every time the input stream emits, but with the "accumulated value".

Basically accum, but on blip stream emissions.

accumB f x0 == perBlip (accum f x0)

accumB_ Source

Arguments

:: (b -> a -> b)

folding function

-> b

initial value

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

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

scanB Source

Arguments

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

folding function

-> b

initial value

-> Auto m (Blip a) b 

The output is the result of folding up every emitted value seen thus far, with the given folding function and initial value.

scanB f x0 == holdWith x0 . accumB f x0
>>> let a = scanB (+) 0 . eachAt 2 [1,2,3]
>>> take 8 . streamAuto' a $ repeat ()
[0, 1, 1, 3, 3, 6, 6, 6, 6]

scanB_ Source

Arguments

:: (b -> a -> b) 
-> b

folding function

-> Auto m (Blip a) b

initial value

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

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

The output is the mconcat (monoid sum) of all emitted values seen this far.

mscanB_ :: Monoid a => Auto m (Blip a) a Source

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

countB :: Auto m (Blip a) Int Source

The output is the number of emitted values received from the upstream blip stream so far.

Blips on edges

onChange :: (Serialize a, Eq a) => Auto m a (Blip a) Source

Blip stream that emits whenever the input value changes. Emits with the new value.

Warning: Note that, when composed on a value that is never expected to keep the same value twice, this technically breaks blip semantics.

onChange_ :: Eq a => Auto m a (Blip a) Source

The non-serializing/non-resumable version of onChange.

became Source

Arguments

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

change condition

-> Auto m a (Blip a) 

Blip stream that emits whenever the predicate applied to the input switches from false to true. Emits with the triggering input value.

became_ Source

Arguments

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

change condition

-> Auto m a (Blip a) 

The non-serializing/non-resumable version of became.

became' Source

Arguments

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

change condition

-> Auto m a (Blip ()) 

Like became, but emits a '()' instead of the triggering input value.

Useful because it can be serialized without the output needing a Serialize instance.

noLonger Source

Arguments

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

change condition

-> Auto m a (Blip a) 

Blip stream that emits whenever the predicate applied to the input switches from true to false. Emits with the triggering input value.

noLonger_ Source

Arguments

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

change condition

-> Auto m a (Blip a) 

The non-serializing/non-resumable version of noLonger.

noLonger' Source

Arguments

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

change condition

-> Auto m a (Blip ()) 

Like noLonger, but emits a '()' instead of the triggering input value.

Useful because it can be serialized without the output needing a Serialize instance.

onFlip Source

Arguments

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

change condition

-> Auto m a (Blip a) 

Blip stream that emits whenever the predicate applied to the input switches from true to false or false to true. Emits with the triggering input value.

onFlip_ Source

Arguments

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

change condition

-> Auto m a (Blip a) 

The non-serializing/non-resumable version of onFlip.

onFlip' Source

Arguments

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

change condition

-> Auto m a (Blip Bool) 

Like onFlip, but emits a '()' instead of the triggering input value.

Useful because it can be serialized without the output needing a Serialize instance.