Copyright | (c) Justin Le 2015 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module contains various Auto
s that act as "producing" streams;
they all ignore their input streams and produce output streams through
a pure or monadic process.
- fromList :: Serialize b => [b] -> Interval m a b
- fromList_ :: [b] -> Interval m a b
- fromLongList :: [b] -> Interval m a b
- pure :: Applicative f => forall a. a -> f a
- effect :: m b -> Auto m a b
- iterator :: Serialize b => (b -> b) -> b -> Auto m a b
- iterator_ :: (b -> b) -> b -> Auto m a b
- iteratorM :: (Serialize b, Monad m) => (b -> m b) -> b -> Auto m a b
- iteratorM_ :: Monad m => (b -> m b) -> b -> Auto m a b
- discreteF :: (Enum c, Serialize c) => (c -> b) -> c -> Auto m a b
- discreteF_ :: Enum c => (c -> b) -> c -> Auto m a b
- unfold :: Serialize c => (c -> Maybe (b, c)) -> c -> Interval m a b
- unfold_ :: (c -> Maybe (b, c)) -> c -> Interval m a b
- unfoldM :: (Serialize c, Monad m) => (c -> m (Maybe (b, c))) -> c -> Interval m a b
- unfoldM_ :: Monad m => (c -> m (Maybe (b, c))) -> c -> Interval m a b
- enumFromA :: (Serialize b, Enum b) => b -> Auto m a b
- enumFromA_ :: Enum b => b -> Auto m a b
From lists
An Interval
that ignores the input stream and just outputs items
from the given list. Is "on" as long as there are still items in the
list left, and "off" after there is nothing left in the list to output.
Serializes itself by storing the entire rest of the list in binary, so if your list is long, it might take up a lot of space upon storage. If your list is infinite, it makes an infinite binary, so be careful!
fromLongList
can be used for longer lists or infinite lists; or, if
your list can be boild down to an unfoldr
, you can use unfold
.
- Storing: O(n) time and space on length of remaining list
- Loading: O(1) time in the number of times the
Auto
has been stepped + O(n) time in the length of the remaining list.
:: [b] | list to output element-by-element |
-> Interval m a b |
The non-resuming/non-serializing version of fromList
.
:: [b] | list to output element-by-element |
-> Interval m a b |
A version of fromList
that is safe for long or infinite lists, or
lists with unserializable elements.
There is a small cost in the time of loading/resuming, which is O(n)
on the number of times the Auto had been stepped at the time of
saving. This is because it has to drop the n
first elements in the
list, to "resume" to the proper position.
- Storing: O(1) time and space on the length of the remaining list
- Loading: O(n) time on the number of times the
Auto
has been stepped, maxing out at O(n) on the length of the entire input list.
Constant producers
Here we have the "constant producers": Auto
s whose output is always
the same value, or the result of executing the same monadic action.
pure
::Monad
m => b ->Auto
m a beffect
::Monad
m => m b ->Auto
m a b
pure
always outputs the same value, ignoring its input, and effect
always outputs the result of executing the same monadic action, ignoring
its input.
pure :: Applicative f => forall a. a -> f a
Lift a value.
:: 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 functions
Iterating
:: (b -> b) | iterating function |
-> b | starting value and initial output |
-> Auto m a b |
The non-resuming/non-serializing version of iterator
.
:: (Serialize b, Monad m) | |
=> (b -> m b) | (monadic) iterating function |
-> b | starting value and initial output |
-> Auto m a b |
Like iterator
, but with a monadic function.
:: Monad m | |
=> (b -> m b) | (monadic) iterating function |
-> b | starting value and initial output |
-> Auto m a b |
The non-resuming/non-serializing version of iteratorM
.
Enumerating results of a function
Given a function from discrete enumerable inputs, iterates through all of the results of that function.
>>>
take 10 . streamAuto' (discreteF (^2) 0) $ repeat ()
[0, 1, 4, 9, 16, 25, 36, 49, 64, 81]
The non-resuming/non-serializing version of discreteF
.
Unfolding
"Iterating with state".
Analogous to unfoldr
from Prelude. Creates an Interval
(that ignores its input) by maintaining an internal accumulator of type
c
and, at every step, applying to the unfolding function to the
accumulator. If the result is Nothing
, then the Interval
will turn
"off" forever (output Nothing
forever); if the result is
, then it will output Just
(y,
acc)y
and store acc
as the new accumulator.
Given an initial accumulator.
>>>
let countFromTil n m = flip unfold n $ \i -> if i <= m
then Just (i, i+1) else Nothing>>>
take 8 . streamAuto' (countFromTil 5 10) $ repeat ()
[Just 5, Just 6, Just 7, Just 8, Just 9, Just 10, Nothing, Nothing]
behaves like unfold
f c0
.overList
(unfoldr
f c0)
The non-resuming & non-serializing version of unfold
.
:: (Serialize c, Monad m) | |
=> (c -> m (Maybe (b, c))) | unfolding function |
-> c | initial accumulator |
-> Interval m a b |
Like unfold
, but the unfolding function is monadic.
The non-resuming & non-serializing version of unfoldM
.
Enumerating
Continually enumerate from the starting value, using succ
.
The non-serializing/non-resuming version of enumFromA
.