Copyright | (c) Justin Le 2015 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides utilities for "running" and "unrolling" Auto
s.
You'll find "enhanced" versions of stepAuto
, mechanisms for running
Auto
s "interactively" inside IO
, monadic and non-monadic
"self-runners" (provide the handlers, and the Auto
just recursively
runs intself), and finally, ways of "unrolling" the underlying Monad
of Auto
s into more manageable and composable and easy to work with
forms.
- streamAuto :: Monad m => Auto m a b -> [a] -> m [b]
- streamAuto' :: Auto' a b -> [a] -> [b]
- overList :: Monad m => Auto m a b -> [a] -> m ([b], Auto m a b)
- overList' :: Auto' a b -> [a] -> ([b], Auto' a b)
- stepAutoN :: Monad m => Int -> Auto m a b -> a -> m ([b], Auto m a b)
- stepAutoN' :: Int -> Auto' a b -> a -> ([b], Auto' a b)
- evalAutoN :: Monad m => Int -> Auto m a b -> a -> m [b]
- evalAutoN' :: Int -> Auto' a b -> a -> [b]
- interactAuto :: Interval' String String -> IO (Interval' String String)
- interactRS :: (Read a, Show b) => Interval' a b -> IO (Interval' String String)
- interactM :: Monad m => (forall c. m c -> IO c) -> (b -> IO Bool) -> Auto m String b -> IO (Auto m String b)
- duringRead :: (Monad m, Read a) => Auto m a b -> Interval m String b
- bindRead :: (Monad m, Read a) => Interval m a b -> Interval m String b
- run :: Monad m => m a -> (b -> m (Maybe a)) -> Auto m a b -> m (Auto m a b)
- runM :: (Monad m, Monad m') => (forall c. m' c -> m c) -> m a -> (b -> m (Maybe a)) -> Auto m' a b -> m (Auto m' a b)
- runOnChan :: (b -> IO Bool) -> Chan a -> Auto' a b -> IO (Auto' a b)
- runOnChanM :: Monad m => (forall c. m c -> IO c) -> (b -> IO Bool) -> Chan a -> Auto m a b -> IO (Auto m a b)
Special stepAuto
versions.
Streaming over lists
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
into an Auto
m a b[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
, except at every step, prints the input
item to stdout as a side-effect.sumFrom
0
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
into an Auto'
a b[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]
:: Monad m | |
=> Auto m a b | the |
-> [a] | list of inputs to step the |
-> m ([b], Auto m a b) | list of outputs and the updated |
Streams the Auto
over a list of inputs; that is, "unwraps" the [a]
-> m [b]
inside. Streaming is done in the context of the underlying
monad; when done consuming the list, the result is the list of outputs
updated/next Auto
in the context of the underlying monad.
Basically just steps the Auto
by feeding in every item in the list and
pops out the list of results and the updated/next Auto
, monadically
chaining the steppings.
See overList'
for a simpler example; the following example uses
effects from IO
to demonstrate the monadic features of overList
.
>>>
let a = arrM print *> sumFrom 0 :: Auto IO Int Int
>>>
(ys, a') <- overList a [1..5]
1 -- IO effects 2 3 4 5>>>
ys
[1,3,6,10,15]>>>
(ys', _) <- overList a' [11..15]
11 -- IO effects 12 13 14 15>>>
ys'
[26,38,51,65,80]
a
is like
, except at every step, prints the input item
to stdout as a side-effect. Note that in executing we get the updated
sumFrom
0a'
, which ends up with an accumulator of 15. Now, when we stream
a'
, we pick up were we left off (from 15) on the results.
:: Auto' a b | the |
-> [a] | list of inputs to step the |
-> ([b], Auto' a b) | list of outputs and the updated |
Streams an Auto'
over a list of inputs; that is, "unwraps" the [a]
-> [b]
inside. When done comsuming the list, returns the outputs and
the updated/next Auto'
.
>>>
let (ys, updatedSummer) = overList' (sumFrom 0) [1..5]
>>>
ys
[1, 3, 6, 10, 15]>>>
let (ys', _) = streamAuto' updatedSummer [1..5]
>>>
ys'
[16, 18, 21, 25, 30]
If you wanted to stream over an infinite list then you don't care about
the Auto'
at the end, and probably want streamAuto'
.
Running over one item repetitively
:: Monad m | |
=> Int | number of times to step the |
-> Auto m a b | the |
-> a | the repeated input |
-> m ([b], Auto m a b) | list of outputs and the updated |
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
, except at every step, prints the input
item to stdout as a side-effect.sumFrom
0
:: Int | number of times to step the |
-> Auto' a b | the |
-> a | the repeated input |
-> ([b], Auto' a b) | list of outputs and the updated |
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]
:: Monad m | |
=> Int | number of times to step the |
-> Auto m a b | the |
-> a | the repeated input |
-> m [b] | list of outputs |
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 in the context
of the underlying monad.
Like stepAutoN
, but drops the "next Auto
". Only returns the list
of results.
>>>
let a = arrM print *> sumFrom 0 :: Auto IO Int Int
>>>
ys <- evalAutoN 5 a 3
3 -- IO effects 3 3 3 3>>>
ys
[3,6,9,12,15] -- the result
a
here is like
, except at every step, prints the input
item to stdout as a side-effect.sumFrom
0
:: Int | number of times to step the |
-> Auto' a b | the |
-> a | the repeated input |
-> [b] | list of outputs and the updated |
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
.
Like stepAutoN'
, but drops the "next Auto'
". Only returns the list
of results.
>>>
evalAutoN' 5 (sumFrom 0) 3
[3,6,9,12,15]
Running "interactively"
:: Interval' String String |
|
-> IO (Interval' String String) | final |
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 read
able, 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.
:: Monad m | |
=> (forall c. m c -> IO c) | natural transformation from the underlying |
-> (b -> IO Bool) | function to "handle" each succesful |
-> Auto m String b |
|
-> IO (Auto m String b) | final |
Like interact
, but much more general. You can run it with an Auto
of any underlying Monad
, as long as you provide the natural
transformation from that Monad
to IO
.
The Auto
can any
; you have to provide
a function to "handle" it yourself; a Maybe
bb ->
. You can print
the result, or write the result to a file, etc.; the IO
Bool
Bool
parameter
determines whether or not to "continue running", or to stop and return
the final updated Auto
.
Helpers
Turn an Auto
that takes a "readable" a
and outputs a b
into an
Auto
that takes a String
and outputs a
. When the
Maybe
bString
is successfuly readable as the a
, it steps the Auto
and
outputs a succesful Just
result; when it isn't, it outputs a Nothing
on that step.
>>>
let a0 = duringRead (accum (+) (0 :: Int))
>>>
let (y1, a1) = stepAuto' a0 "12"
>>>
y1
Just 12>>>
let (y2, a2) = stepAuto' a1 "orange"
>>>
y2
Nothing>>>
let (y3, _ ) = stepAuto' a2 "4"
>>>
y3
Just 16
See interact
for neat use cases.
Generalized "self-runners"
:: Monad m | |
=> m a | action to retrieve starting input |
-> (b -> m (Maybe a)) | handling output and next input in |
-> Auto m a b | |
-> m (Auto m a b) | return the ran/updated |
Heavy duty abstraction for "self running" an Auto
. Give a starting
input action, a (possibly side-effecting) function from an output to
the next input to feed in, and the Auto
, and you get a feedback
loop that constantly feeds back in the result of the function applied to
the previous output. Stops when the "next input" function returns
Nothing
.
Note that the none of the results are actually returned from the loop. Instead, if you want to process the results, they must be utilized in the "side-effects' of the "next input" function. (ie, a write to a file, or an accumulation to a state).