Copyright | (c) Justin Le 2015 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
- arrM :: (a -> m b) -> Auto m a b
- effect :: m b -> Auto m a b
- effects :: Monad m => Auto m (m a) a
- arrMB :: Monad m => (a -> m b) -> Auto m (Blip a) (Blip b)
- effectB :: Monad m => m b -> Auto m (Blip a) (Blip b)
- execB :: Monad m => m b -> Auto m (Blip a) (Blip a)
- cache :: (Serialize b, Monad m) => m b -> Auto m a b
- execOnce :: Monad m => m b -> Auto m a ()
- cache_ :: Monad m => m b -> Auto m a b
- execOnce_ :: Monad m => m b -> Auto m a ()
- sealState :: (Monad m, Serialize s) => Auto (StateT s m) a b -> s -> Auto m a b
- sealState_ :: Monad m => Auto (StateT s m) a b -> s -> Auto m a b
- sealReader :: (Monad m, Serialize r) => Auto (ReaderT r m) a b -> r -> Auto m a b
- sealReader_ :: Monad m => Auto (ReaderT r m) a b -> r -> Auto m a b
- runStateA :: Monad m => Auto (StateT s m) a b -> Auto m (a, s) (b, s)
- runReaderA :: Monad m => Auto (ReaderT r m) a b -> Auto m (a, r) b
- runWriterA :: (Monad m, Monoid w) => Auto (WriterT w m) a b -> Auto m a (b, w)
- runTraversableA :: (Monad f, Traversable f) => Auto f a b -> Auto m a (f b)
- hoistA :: (Monad m, Monad m') => (forall c. m c -> m' c) -> Auto m a b -> Auto m' a b
- generalizeA :: Monad m => Auto' a b -> Auto m a b
- catchA :: Exception e => Auto IO a b -> Auto IO a (Either e b)
- fromState :: (Serialize s, Monad m) => (a -> StateT s m b) -> s -> Auto m a b
- fromState_ :: Monad m => (a -> StateT s m b) -> s -> Auto m a b
Running effects
Continually
:: (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"
...except, when you step it,
it prints out to stdout as a side-effect. We just gave automatic
stdout logging behavior!sumFrom
0
:: 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 beffect
:: 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
, except at each step,
it also increments the underlying/global state by one. It is sumFrom
0
with an "attached effect".sumFrom
0
From inputs
effects :: Monad m => Auto m (m a) a Source
The input stream is a stream of monadic actions, and the output stream is the result of their executions, through executing them.
On Blip
s
arrMB :: Monad m => (a -> m b) -> Auto m (Blip a) (Blip b) Source
Maps one blip stream to another; replaces every emitted value with the result of the monadic function, executing it to get the result.
effectB :: Monad m => m b -> Auto m (Blip a) (Blip b) Source
Maps one blip stream to another; replaces every emitted value with the result of a fixed monadic action, run every time an emitted value is received.
execB :: Monad m => m b -> Auto m (Blip a) (Blip a) Source
Outputs the identical blip stream that is received; however, every time it sees an emitted value, executes the given monadic action on the side.
One-time effects
The very first output executes a monadic action and uses the result as the output, ignoring all input. From then on, it persistently outputs that first result.
Like execOnce
, except outputs the result of the action instead of
ignoring it.
Useful for loading resources in IO on the "first step", like a word list:
dictionary :: Auto IO a [String] dictionary = cache (lines $ readFile "wordlist.txt")
Always outputs '()', but when asked for the first output, executes the given monadic action.
Pretty much like cache
, but always outputs '()'.
The non-resumable/non-serializable version of cache
. Every time the
Auto
is deserialized/reloaded, it re-executes the action to retrieve
the result again.
Useful in cases where you want to "re-load" an expensive resource on every startup, instead of saving it to in the save states.
dictionary :: Auto IO a [String] dictionary = cache_ (lines $ readFile "dictionary.txt")
Manipulating underlying monads
"Sealing off" monadic Auto
s
Takes an Auto
that works with underlying global, mutable state, and
"seals off the state" from the outside world.
An 'Auto (StateT s m) a b' maps a stream of a
to a stream of b
, but
does so in the context of requiring an initial s
to start, and
outputting a modified s
.
Consider this example State
Auto
:
foo :: Auto (State s) Int Int foo = proc x -> do execB (modify (+1)) . emitOn odd -< x execB (modify (*2)) . emitOn even -< x st <- effect get -< () sumX <- sumFrom 0 -< x id -< sumX + st
On every output, the "global" state is incremented if the input is odd
and doubled if the input is even. The stream st
is always the value
of the global state at that point. sumX
is the cumulative sum of the
inputs. The final result is the sum of the value of the global state
and the cumulative sum.
In writing like this, you lose some of the denotative properties because you are working with a global state that updates at every output. You have some benefit of now being able to work with global state, if that's what you wanted I guess.
To "run" it, you could use streamAuto
to get a
:State
Int Int
>>>
let st = streamAuto foo [1..10] :: State Int Int
>>>
runState st 5
([ 7, 15, 19, 36, 42, 75, 83,136,156,277], 222)
(The starting state is 5 and the ending state after all of that is 222)
However, writing your entire program with global state is a bad bad
idea! So, how can you get the "benefits" of having small parts like
foo
be written using State
, and being able to use it in a program
with no global state?
Using sealState
! Write the part of your program that would like
shared global state with State
...and compose it with the rest as if it
doesn't, locking it away!
sealState :: Auto (State s) a b -> s -> Auto' a b sealState foo 5 :: Auto' Int Int
bar :: Auto' Int (Int, String) bar = proc x -> do food <- sealState foo 5 -< x id -< (food, show x)
>>>
streamAuto' bar [1..10]
[ (7, "1"), (15, "2"), (19, "3"), (36, "4"), (42, "5"), (75, "6") ...
We say that
takes an input stream, and the output
stream is the result of running the stream through sealState
f s0f
, first with an
initial state of s0
, and afterwards with each next updated state.
The non-resuming/non-serializing version of sealState
.
:: (Monad m, Serialize r) | |
=> Auto (ReaderT r m) a b |
|
-> r | the perpetual environment |
-> Auto m a b |
Takes an Auto
that operates under the context of a read-only
environment, an environment value, and turns it into a normal Auto
that always "sees" that value when it asks for one.
>>>
let a = effect ask :: Auto (Reader b) a b
>>>
let rdr = streamAuto' a [1..5] :: Reader b [b]
>>>
runReader rdr "hey"
["hey", "hey", "hey", "hey", "hey"]
Useful if you wanted to use it inside/composed with an Auto
that does
not have a global environment:
bar :: Auto' Int String bar = proc x -> do hey <- sealReader (effect ask) "hey" -< () id -< hey ++ show x
>>>
streamAuto' bar [1..5]
["hey1", "hey2", "hey3", "hey4", "hey5"]
Note that this version serializes the given r
environment, so that
every time the Auto
is reloaded/resumed, it resumes with the
originally given r
environment, ignoring whatever r
is given to it
when trying to resume it. If this is not the behavior you want, use
sealReader_
.
The non-resuming/non-serializing version of sealReader
. Does not
serialize/reload the r
environment, so that whenever you "resume" the
Auto
, it uses the new r
given when you are trying to resume, instead
of loading the originally given one.
Unrolling/"reifying" monadic Auto
s
:: Monad m | |
=> Auto (StateT s m) a b |
|
-> Auto m (a, s) (b, s) |
|
Unrolls the underlying StateT
of an Auto
into an Auto
that
takes in an input state every turn (in addition to the normal input) and
outputs, along with the original result, the modified state.
So now you can use any
as if it were an StateT
s mm
. Useful if
you want to compose and create some isolated Auto
s with access to an
underlying state, but not your entire program.
Also just simply useful as a convenient way to use an Auto
over
State
with stepAuto
and friends.
When used with
, it turns an State
s
into an
Auto
(State
s) a b
.Auto'
(a, s) (b, s)
:: Monad m | |
=> Auto (ReaderT r m) a b |
|
-> Auto m (a, r) b |
|
Unrolls the underlying ReaderT
of an Auto
into an Auto
that
takes in the input "environment" every turn in addition to the normal
input.
So you can use any
as if it were an ReaderT
r mm
. Useful if you
want to compose and create some isolated Auto
s with access to an
underlying environment, but not your entire program.
Also just simply useful as a convenient way to use an Auto
over
Reader
with stepAuto
and friends.
When used with
, it turns an Reader
r
into
an Auto
(Reader
r) a b
.Auto'
(a, r) b
runWriterA :: (Monad m, Monoid w) => Auto (WriterT w m) a b -> Auto m a (b, w) Source
Unrolls the underlying WriterT
w mMonad
, so that an Auto
that takes in a stream of a
and outputs a stream of b
will now
output a stream (b, w)
, where w
is the "new log" of the underlying
Writer
at every step.
foo :: Auto (Writer (Sum Int)) Int Int foo = effect (tell 1) *> effect (tell 1) *> sumFrom 0
>>>
let fooWriter = streamAuto foo
>>>
runWriter $ fooWriter [1..10]
([1,3,6,10,15,21,28,36,45,55], Sum 20)
foo
increments an underlying counter twice every time it is stepped;
its "result" is just the cumulative sum of the inputs.
When we "stream" it, we get a [Int] ->
...which we can give an input list and Writer
(Sum Int)
[Int]runWriter
it, getting
a list of outputs and a "final accumulator state" of 10, for stepping it
ten times.
However, if we use runWriterA
before streaming it, we get:
>>>
let fooW = runWriterA foo
>>>
streamAuto' fooW [1..10]
[ (1 , Sum 2), (3 , Sum 2), (6 , Sum 2) , (10, Sum 2), (15, Sum 2), (21, Sum 2), -- ...
Instead of accumulating it between steps, we get to "catch" the Writer
output at every individual step.
We can write and compose our own Auto
s under Writer
, using the
convenience of a shared accumulator, and then "use them" with other
Auto
s:
bar :: Auto' Int Int bar = proc x -> do (y, w) <- runWriterA foo -< x blah <- blah -< w
And now you have access to the underlying accumulator of foo
to
access. There, w
represents the continually updating accumulator
under foo
, and will be different/growing at every "step".
:: (Monad f, Traversable f) | |
=> Auto f a b |
|
-> Auto m a (f b) |
|
Unrolls the underlying Monad
of an Auto
if it happens to be
Traversable
('[]', Maybe
, etc.).
It can turn, for example, an
into an Auto
[] a b
; it
collects all of the results together. Or an Auto'
a [b]
into
an Auto
Maybe
a b
.Auto'
a (Maybe
b)
This might be useful if you want to make some sort of "underyling
inhibiting" Auto
where the entire computation might just end up being
Nothing
in the end. With this, you can turn that
possibly-catastrophically-failing Auto
(with an underlying Monad
of
Maybe
) into a normal Auto
, and use it as a normal Auto
in
composition with other Auto
s...returning Just
if your computation
succeeded.
Hoists
:: (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
Working with IO
:: Exception e | |
=> Auto IO a b | Auto over IO, expecting an exception of a secific type. |
-> Auto IO a (Either e b) |
Wraps a "try" over an underlying IO
monad; if the Auto encounters a
runtime exception while trying to "step" itself, it'll output a Left
with the Exception
. Otherwise, will output left
.
Note that you have to explicitly specify the type of the exceptions you are catching; see Control.Exception documentation for more details.
TODO: Possibly look into bringing in some more robust tools from monad-control and other industry established error handling routes? Also, can we modify an underlying monad with implicit cacting behavior?