Copyright | (c) Justin Le 2015 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides combinators and utilities for working with the
semantic concept of "intervals": an Auto
whose output stream is "on"
or "off" for (conceputally) contiguous chunks of time.
- type Interval m a b = Auto m a (Maybe b)
- type Interval' a b = Auto' a (Maybe b)
- off :: Interval m a b
- toOn :: Interval m a a
- fromInterval :: a -> Auto m (Maybe a) a
- fromIntervalWith :: b -> (a -> b) -> Auto m (Maybe a) b
- onFor :: Int -> Interval m a a
- offFor :: Int -> Interval m a a
- window :: Int -> Int -> Interval m a a
- whenI :: (a -> Bool) -> Interval m a a
- unlessI :: (a -> Bool) -> Interval m a a
- (<|!>) :: Monad m => Interval m a b -> Auto m a b -> Auto m a b
- (<|?>) :: Monad m => Interval m a b -> Interval m a b -> Interval m a b
- chooseInterval :: Monad m => [Interval m a b] -> Interval m a b
- choose :: Monad m => Auto m a b -> [Interval m a b] -> Auto m a b
- after :: Interval m (a, Blip b) a
- before :: Interval m (a, Blip b) a
- between :: Interval m (a, (Blip b, Blip c)) a
- hold :: Serialize a => Interval m (Blip a) a
- hold_ :: Interval m (Blip a) a
- holdFor :: Serialize a => Int -> Interval m (Blip a) a
- holdFor_ :: Int -> Interval m (Blip a) a
- during :: Monad m => Auto m a b -> Auto m (Maybe a) (Maybe b)
- compI :: Monad m => Interval m b c -> Interval m a b -> Interval m a c
- bindI :: Monad m => Interval m a b -> Interval m (Maybe a) b
Intervals
An auto that exhibits this "interval" behavior is represented with the
Interval
type synonym:
typeInterval
m a b =Auto
m a (Maybe
b) typeInterval'
a b =Auto'
a (Maybe
b)
So, the compiler sees an
as if it were an Interval
m a b
. If it helps you reason about type signatures and type
inference, you can make the substitution in your head too!Auto
m a (Maybe
b)
An
takes an input stream of Interval
m a ba
s and output stream of
b
s that are "on" and "off" for chunks at a time; Nothing
is
interpreted as "off", and
is interpreted as "on" with a value
of Just
xx
.
A classic example is
. With
onFor
:: Int
-> Interval
m a a
, the output stream behaves exactly like the input stream for
the first onFor
nn
steps, then is "off" forever after:
>>>
streamAuto' (onFor 3) [1..7]
[Just 1, Just 2, Just 3, Nothing, Nothing, Nothing, Nothing]
Motivation
Intervals happen to particularly useful when used with the various switching combinators from Control.Auto.Switch.
You might find it useful to "sequence" Auto
s such that they "switch"
from one to the other, dynamically. For example, an Auto
that acts
like
for three steps, and then like pure
0count
for the rest:
>>>
let a1 = (onFor 3 . pure 0) --> count
>>>
take 8 . streamAuto' a1 $ repeat ()
[0, 0, 0, 1, 2, 3, 4, 5]
(Recall that
is the pure
xAuto
that ignores the input stream and
gives an output stream of constant x
s)
Or in reverse, an Auto
that behaves like count
until the count is
above 3, then switches to pure
0
>>>
let a2 = (whenI (<= 3) . count) --> pure 0
>>>
take 8 . streamAuto' a2 $ repeat ()
[1, 2, 3, 0, 0, 0, 0, 0]
That's just a small example using one switching combinator, -->
. But
hopefully it demonstrates that one powerful motivation behind
"intervals" being a "thing" is because of how it works with switches.
Another neat motivation is that intervals work pretty well with the
Blip
semantic tool, as well.
The following Interval
will be "off" and suppress all of its input
(from count
) until the blip stream produced by
emits
something, then it'll allow inB
3count
to pass.
>>>
let a3 = after . (count &&& inB 3)
>>>
let a3 = proc () -> do
c <- count -< () blp <- inB 3 -< () after -< (c, blp)>>>
take 5 . streamAuto' a3 $ repeat ()
[Nothing, Nothing, Just 3, Just 4, Just 4]
Intervals are also used for things that want their Auto
s to "signal"
when they are "off". Interval
is the universal language for, "you can
be done with me", when it is needed. For example, the interactAuto
loop takes an 'Interval String String', and "turns off" on the first
Nothing
or "off" value. gather
keeps a collection of Interval
s,
and removes them whenever they output a Nothing
/turn "off".
The Contract
So, why have an Interval
type, and not always just use Auto
?
You can say that, if you are given an Interval
, then it comes with
a "contract" (by documentation) that the Auto
will obey /interval
semantics/.
can mean a lot of things and represent a lot of
things.Auto
m a (Maybe
b)
However, if you offer something of an Interval
type, or if you find
something of an Interval
type, it comes with some sort of assurance
that that Auto
will behave like an interval: on and off for
contiguous periods of time.
In addition, this allows us to further clarify /what our functions
expect/. By saying that a function expects an Interval
:
chooseInterval :: [Interval m a b] -> Interval m a b
chooseInterval
has the ability to "state" that it expects things
that follow interval semantics in order to "function" properly and in
order to properly "return" an Interval
.
Of course, this is not enforced by the compiler. However, it's useful to create a way to clearly state that what you are offering or what you are expecting does indeed follow this useful pattern.
Combinators
Converting back into normal streams
You can take an incoming interval stream and output a "normal"
"always-on" stream by using the fromInterval
and fromIntervalWith
Auto
s, analogous to fromMaybe
and maybe
from Data.Maybe,
respectively:
>>>
let a = fromIntervalWith "off" show . onFor 2
>>>
streamAuto' a [1..5]
["1", "2", "off", "off", "off"]
You can also use <|!>
, coming up next....
Choice
You can "choose" between interval streams, with choice combinators like
<|?>
and <|!>
.
>>>
let a = onFor 2 . pure "hello"
<|!> onFor 4 . pure "world" <|!> pure "goodbye!">>>
take 6 . streamAuto' a $ repeat ()
["hello", "hello", "world", "world", "goodbye!", "goodbye!"]
The above could also be written with choose
:
>>>
let a = choose (pure "goodbye!")
[ onFor 2 . pure "hello" , onFor 4 . pure "world" ]
Composition
Another tool that makes Interval
s powerful is the ability to compose
them.
If you have an
and an Auto
m a b
, then you can
compose them with Auto
m b c.
.
If you have an
and an Auto
m a b
, then you can
compose them by throwing in a Interval
m b ctoOn
in the chain, or
:fmap
Just
a ::Auto
m a b i ::Interval
m b c i .toOn
. a ::Interval
m a cfmap
Just
a ::Interval
m a b i .fmap
Just
a ::Interval
m a c
If you have an
and an Interval
m a b
, you can "lift"
the second Auto
m b cAuto
to be an Auto
that only "acts" on "on"/Just
outputs of the Interval
:
i ::Interval
m a b a ::Auto
m b cduring
a ::Auto
m (Maybe
a) (Maybe
b)during
a . i ::Interval
m a c
Finally, the kleisli composition: if you have an
and
an Interval
m a b
, you can use Interval
m b ccompI
: (or also bindI
)
i1 ::Interval
m a b i2 ::Interval
m b c i2 `'compI'` i1 ::Interval
m a b cbindI
i2 . i1 ::Interval
m a b c
>>>
let a1 = when (< 5) `compI` offFor 2
>>>
streamAuto' a1 [1..6]
[Nothing, Nothing, Just 3, Just 4, Nothing, Nothing]
The implementation works so that any "on"/Just
inputs will step the
lifted Auto
like normal, with the contents of the Just
, and any
"off"/Nothing
inputs cause the lifted Auto
to be skipped.
compI
adds a lot of power to Interval
because now you can always
work "with Interval
s", bind them just like normal Auto
s, and then
finally "exit" them after composing and combining many.
Warning: Switching
Note that when any of these combinators "block" (or "inhibit" or
"suppress", whatever you call it) their input as a part of a composition
pipeline (as in for off
, onFor
, offFor
, etc.), the input Auto
s
are still stepped and "run". If the inputs had any monad effects,
they would too be executed at every step. In order to "freeze" and not
run or step an Auto
at all, you have to use switches.
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
. If you ended up here
with a link...no worries! If you see Auto
m a (Maybe
b)
, just think
Interval
m a b
for type inference/type checking purposes.Auto
m a (Maybe
b)
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.
Static Interval
s
The output stream is always on, with exactly the value of the corresponding input.
toOn == arr Just
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)
:: b | default value, when input is off |
-> (a -> b) | function to apply when input is on |
-> Auto m (Maybe a) b |
An "interval collapsing" Auto
. A stream of on/off values comes in;
when the input is off, the output is the "default value". When the
input is off, the output is the given function applied to the "on"
value.
Much like maybe
from Data.Maybe.
fromIntervalWith d f = arr (maybe d f)
For
, the first onFor
nn
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.
For
, the first offFor
nn
items in the output stream are always
"off", suppressing all input; for the rest, the output stream is always
"on", outputting exactly the value of the corresponding input.
Filter Interval
s
The output is "on" with exactly the value of he corresponding input when the input passes the predicate, and is "off" otherwise.
>>>
let a = whenI (\x -> x >= 2 && x <= 4)
>>>
streamAuto' a [1..6]
[Nothing, Just 2, Just 3, Just 4, Nothing, Nothing]
Careful when using this; you could exactly create an Interval
that
"breaks" "interval semantics"; for example, 'whenI even', when you know
your input stream does not consist of chunks of even numbers and odd
numbers at a time.
Like whenI
, but only allows values to pass whenever the input does
not satisfy the predicate. Blocks whenever the predicate is true.
>>>
let a = unlessI (\x -> x < 2 &&& x > 4)
>>>
steamAuto' a [1..6]
>>>
res
[Nothing, Just 2, Just 3, Just 4, Nothing, Nothing]
Choice
Forks a common input stream between an Interval
and an Auto
, and
returns, itself, a normal non-interval Auto
.. If the
output of the first one is "on", the output of the whole thing is that
"on" value. Otherwise, the output is exactly that of the second one.
>>>
let a1 = (onFor 2 . pure "hello") <|!> pure "world"
>>>
take 5 . streamAuto' a1 $ repeat ()
["hello", "hello", "world", "world", "world"]
This one is neat because it associates from the right, so it can be "chained":
>>>
let a2 = onFor 2 . pure "hello"
<|!> onFor 4 . pure "world" <|!> pure "goodbye!">>>
take 6 . streamAuto' a2 $ repeat ()
["hello", "hello", "world", "world", "goodbye!", "goodbye!"]
a <|!> b <|!> c
associates as
a <|!> (b <|!> c)
So using this, you can "chain" a bunch of choices between intervals, and then at the right-most, "final" one, provide the default behavior.
Warning: If your underlying monad produces effects, remember that both
Auto
s are run at every step, along with any monadic effects,
regardless of whether they are "on" or "off".
Forks a common input stream between the two Interval
s and returns,
itself, an Interval
. If the output of the first one is "on", the
whole thing is on with that output. Otherwise, the output is exactly
that of the second one.
>>>
let a = (onFor 2 . pure "hello") <|?> (onFor 4 . pure "world")
>>>
take 5 . streamAuto' a $ repeat ()
>>>
res
[Just "hello", Just "hello", Just "world", Just "world", Nothing]
You can drop the parentheses, because of precedence; the above could have been written as:
>>>
let a' = onFor 2 . pure "hello" <|?> onFor 4 . pure "world"
Warning: If your underlying monad produces effects, remember that both
Auto
s are run at every step, along with any monadic effects,
regardless of whether they are "on" or "off".
Note that more often than not, <|!>
is probably more useful. This
is useful only in the case that you really, really want an interval at
the end of it all.
Blip-based Interval
s
after :: Interval m (a, Blip b) a Source
Takes two input streams --- a stream of normal values, and a blip stream. Before the first emitted value of the input blip stream, the output is always "off", suppressing all inputs. After the first emitted value of the input blip stream, the output is always "on" with the corresponding value of the first input stream.
>>>
let a = after . (count &&& inB 3)
>>>
take 6 . streamAuto' a $ repeat ()
>>>
res
[Nothing, Nothing, Just 3, Just 4, Just 5, Just 6]
(count
is the Auto
that ignores its input and outputs the current
step count at every step, and
is the inB
3Auto
generating
a blip stream that emits at the third step.)
Be careful to remember that in the above example, count
is still "run"
at every step, and is progressed (and if it were an Auto
with monadic
effects, they would still be executed). It just isn't allowed to pass
its output values through after
until the blip stream emits.
before :: Interval m (a, Blip b) a Source
Takes two input streams --- a stream of normal values, and a blip stream. Before the first emitted value of the input blip stream, the output is always "on" with the corresponding value of the first input stream. After the first emitted value of the input blip stream, the output will be "off" forever, suppressing all input.
>>>
let a = before . (count &&& inB 3)
>>>
take 5 . streamAuto' a $ repeat ()
>>>
res
[Just 1, Just 2, Nothing, Nothing, Nothing]
(count
is the Auto
that ignores its input and outputs the current
step count at every step, and
is the inB
3Auto
generating
a blip stream that emits at the third step.)
Be careful to remember that in the above example, count
is still "run"
at every step, and is progressed (and if it were an Auto
with monadic
effects, they would still be executed). It just isn't allowed to pass
its output values through before
after the blip stream emits.
between :: Interval m (a, (Blip b, Blip c)) a Source
Takes three input streams: a stream of normal values, a blip stream of "turning-on" blips, and a blip stream of "turning-off" blips. After the first blip stream emits, the output will switch to "on" with the value of the first input stream. After the second blip stream emits, the output will switch to "off", supressing all inputs. An emission from the first stream toggles this "on"; an emission from the second stream toggles this "off".
>>>
let a = between . (count &&& (inB 3 &&& inB 5))
>>>
take 7 . streamAuto' a $ repeat ()
[Nothing, Nothing, Just 3, Just 4, Nothing, Nothing, Nothing]
hold :: Serialize a => Interval m (Blip a) a Source
The output is constantly "on" with the last emitted value of the input blip stream. However, before the first emitted value, it is "off". value of the input blip stream. From then on, the output is always the last emitted value
>>>
let a = hold . inB 3
>>>
streamAuto' a [1..5]
[Nothing, Nothing, Just 3, Just 3, Just 3]
If you want an
(no Auto
m (Blip
a) aNothing
...just a "default
value" before everything else), then you can use holdWith
from
Control.Auto.Blip...or also just hold
with <|!>
or fromInterval
.
For
, The output is only "on" if there was an emitted
value from the input blip stream in the last holdFor
nn
steps. Otherwise, is
off.
Like hold
, but it only "holds" the last emitted value for the given
number of steps.
>>>
let a = holdFor 2 . inB 3
>>>
streamAuto' 7 a [1..7]
>>>
res
[Nothing, Nothing, Just 3, Just 3, Nothing, Nothing, Nothing]
The non-serializing/non-resuming version of holdFor
.
Composition with Interval
Lifts an
(transforming Auto
m a ba
s into b
s) into an
(or, Auto
m (Maybe
a) (Maybe
b)
,
transforming intervals of Interval
m (Maybe
a) ba
s 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
is the pure
xAuto
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
was suppressed
by pure
1offFor
, and
was only summing on the times
that the 1's were "allowed through"...so it only "starts counting" on
the third step.during
(sumFrom
0)
In the second case (with a3
), the output of the
is never
suppressed, and went straight into the pure
1
. sumFrom
0sumFrom
is
always summing, the entire time. The final output of that
is suppressed at the end with sumFrom
0
.offFor
2
:: Monad m | |
=> Interval m b c | compose this |
-> Interval m a b | ...to this one |
-> Interval m a c |
Composes two Interval
s, the same way that .
composes two Auto
s:
(.) :: Auto m b c -> Auto m a b -> Auto m a c compI :: Interval m b c -> Interval m a b -> Interval m a c
Basically, if any Interval
in the chain is "off", then the entire rest
of the chain is "skipped", short-circuiting a la Maybe
.
(Users of libraries with built-in inhibition semantics like Yampa and netwire might recognize this as the "default" composition in those other libraries)
As a contrived example, how about an Auto
that only allows values
through during a window...between, say, the second and fourth steps:
>>>
let window' start dur = onFor dur `compI` offFor (start - 1)
>>>
streamAuto' (window' 2 3)
[Nothing, Just 2, Just 3, Just 4, Nothing, Nothing]
Lifts (more technically, "binds") an
into
an Interval
m a b
.Interval
m (Maybe
a) b
Does this by running the Auto
as normal when the input is "on", and
freezing itbeing "off" when the input is off/.
It's kind of like during
, but the resulting
is
"joined" back into a Maybe
(Maybe
b))
.Maybe
b
bindI a == fmap join (during a)
This is really an alternative formulation of compI
; typically, you
will be using compI
more often, but this form can also be useful (and
slightly more general). Note that:
bindI f == compI f id
This combinator allows you to properly "chain" ("bind") together series
of inhibiting Auto
s. If you have an
and an
Interval
m a b
, you can chain them into an Interval
m b c
.Interval
m a c
f ::Interval
m a b g ::Interval
m b cbindI
g . f ::Interval
m a c
(Users of libraries with built-in inhibition semantics like Yampa and netwire might recognize this as the "default" composition in those other libraries)
See compI
for examples of this use case.