Copyright | (c) Justin Le 2015 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module defines and provides the core types, (smart) constructors, and general high and low-level utilities used by the auto library.
Note that importing and using functions from this module in part voids
some of the "semantic contracts" of the Auto
types you get, so use
with caution!
A lot of low-level functionality is provided here which is most likely unnecessary for most applications; many are mostly for internal usage or advanced/fine-grained usage. It also isn't really enough to do too many useful things, either. It's recommended that you import Control.Auto instead, which re-organizes the more useful parts of this module in addition with useful parts of others to provide a nice packaged entry point. If something in here becomes useful for more than just fine-tuning or low-level tweaking, it is probably supposed to be in Control.Auto anyway.
Information on how to use these types is available in the tutorial!
- data Auto m a b
- type Auto' = Auto Identity
- autoConstr :: Auto m a b -> String
- toArb :: Monad m => Auto m a b -> Auto m a b
- purifyAuto :: Auto' a b -> Auto' a b
- stepAuto :: Monad m => Auto m a b -> a -> m (b, Auto m a b)
- stepAuto' :: Auto' a b -> a -> (b, Auto' a b)
- evalAuto :: Monad m => Auto m a b -> a -> m b
- evalAuto' :: Auto' a b -> a -> b
- execAuto :: Monad m => Auto m a b -> a -> m (Auto m a b)
- execAuto' :: Auto' a b -> a -> Auto' a b
- encodeAuto :: Auto m a b -> ByteString
- decodeAuto :: Auto m a b -> ByteString -> Either String (Auto m a b)
- saveAuto :: Auto m a b -> Put
- resumeAuto :: Auto m a b -> Get (Auto m a b)
- unserialize :: Monad m => Auto m a b -> Auto m a 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
- interceptO :: Monad m => ((b, Auto m a b) -> m c) -> Auto m a b -> Auto m a c
- mkConst :: b -> Auto m a b
- mkConstM :: m b -> Auto m a b
- mkFunc :: (a -> b) -> Auto m a b
- mkFuncM :: (a -> m b) -> Auto m a b
- mkState :: Serialize s => (a -> s -> (b, s)) -> s -> Auto m a b
- mkState_ :: (a -> s -> (b, s)) -> s -> Auto m a b
- mkStateM :: Serialize s => (a -> s -> m (b, s)) -> s -> Auto m a b
- mkStateM_ :: (a -> s -> m (b, s)) -> s -> Auto m a b
- mkState' :: Get s -> (s -> Put) -> (a -> s -> (b, s)) -> s -> Auto m a b
- mkStateM' :: Get s -> (s -> Put) -> (a -> s -> m (b, s)) -> s -> Auto m a b
- accum :: Serialize b => (b -> a -> b) -> b -> Auto m a b
- accum_ :: (b -> a -> b) -> b -> Auto m a b
- accumM :: (Serialize b, Monad m) => (b -> a -> m b) -> b -> Auto m a b
- accumM_ :: Monad m => (b -> a -> m b) -> b -> Auto m a b
- accumD :: Serialize b => (b -> a -> b) -> b -> Auto m a b
- accumD_ :: (b -> a -> b) -> b -> Auto m a b
- accumMD :: (Serialize b, Monad m) => (b -> a -> m b) -> b -> Auto m a b
- accumMD_ :: Monad m => (b -> a -> m b) -> b -> Auto m a b
- mkAuto :: Get (Auto m a b) -> Put -> (a -> (b, Auto m a b)) -> Auto m a b
- mkAuto_ :: (a -> (b, Auto m a b)) -> Auto m a b
- mkAutoM :: Get (Auto m a b) -> Put -> (a -> m (b, Auto m a b)) -> Auto m a b
- mkAutoM_ :: (a -> m (b, Auto m a b)) -> Auto m a b
- forceSerial :: Auto m a b -> Auto m a b
- forcer :: NFData a => Auto m a a
- seqer :: Auto m a a
Auto
Type
The Auto
type. For this library, an Auto
semantically
representsdenotes a a relationship/ between an input and an
output that is preserved over multiple steps, where that relationship is
(optionally) maintained within the context of a monad.
A lot of fancy words, I know...but you can think of an Auto
as nothing
more than a "stream transformer" of value streams. A stream of
sequential input values come in one at a time, and a stream of outputs
pop out one at a time, as well.
Using the streamAuto
function, you can "unwrap" the inner value stream
transformer from any Auto
: if a ::
, Auto
m a bstreamAuto
lets
you turn it into an [a] -> m [b]
. "Give me a stream of a
s, one at
a time, and I'll give you a list of b
s, matching a relationship to
your stream of a
s."
-- unwrap your inner [a] -> m [b]!streamAuto
:: Monad m =>Auto
m a b -> ([a] -> m [b])
You can also turn an
into an effects stream that
executes effects sequentially with Auto
m a btoEffectStream
and
streamAutoEffects
, so you can run it with a ListT-compatible library
like pipes.
There's a handy type synonym Auto'
for relationships that don't really
need a monadic context; the m
is just Identity
:
type Auto' = Auto Identity
So if you had an a ::
, you can use Auto'
a bstreamAuto'
to
"unwrap" the inner stream transformer, [a] -> [b]
.
-- unwrap your inner [a] -> [b]!streamAuto'
::Auto'
a b -> ([a] -> [b])
All of the Auto
s given in this library maintain some sort of semantic
relationship between streams --- for some, the outputs might be the
inputs with a function applied; for others, the outputs might be the
cumulative sum of the inputs.
See the tutorial for more information!
Operationally, an
is implemented as a "stateful
function". A function from an Auto
m a ba
where, every time you "apply" it, you
get a b
and an "updated Auto
"/function with updated state.
You can get this function using stepAuto
:
stepAuto
::Auto
m a b -> (a -> m (b,Auto
m a b))
stepAuto'
::Auto'
a b -> (a -> (b,Auto'
a b))
"Give me an a
and I'll give you a b
and your "updated" Auto
".
Auto
s really are mostly useful because they can be composed, chained,
and modified using their various typeclass instances, like Category
,
Applicative
, Functor
, Arrow
, etc., and also with the combinators
in this library. You can build complex programs as a complex Auto
by
building up smaller and smaller components. See the tutorial for more
information on this.
This type also contains information on its own serialization, so you can
serialize and re-load the internal state to binary or disk. See the
"serialization" section in the documentation for Control.Auto.Core, or
the documentation for mkAutoM
for more details.
Monad m => Category * (Auto m) | Gives the ability to "compose" two |
Monad m => Arrow (Auto m) | Gives us
Also allows you to have an
Most importantly, however, allows for "proc" notation; see the tutorial! for more details. |
Monad m => ArrowChoice (Auto m) | Allows you to have an
Again mostly useful for "proc" notation, with branching. |
MonadFix m => ArrowLoop (Auto m) | Finds the fixed point of self-referential |
Monad m => Strong (Auto m) | See |
Monad m => Choice (Auto m) | See |
MonadFix m => Costrong (Auto m) | See |
Monad m => Profunctor (Auto m) |
|
(Monad m, Alternative m) => Alternative (Auto m a) | When the underlying 'Monad'/'Applicative'
|
Monad m => Functor (Auto m a) | Maps over the output stream of the
|
Monad m => Applicative (Auto m a) |
For effectful
would, for example, behave just like |
Typeable ((* -> *) -> * -> * -> *) Auto | |
(Monad m, Floating b) => Floating (Auto m a b) | A bunch of constant producers, mappers-of-output-streams, and forks-and-recombiners. |
(Monad m, Fractional b) => Fractional (Auto m a b) | Fork the input stream and divide the outputs. |
(Monad m, Num b) => Num (Auto m a b) | Fork the input stream and add, multiply, etc. the outputs.
|
(Monad m, IsString b) => IsString (Auto m a b) | String literals in code will be
|
(Monad m, Monoid b) => Monoid (Auto m a b) | Fork the input stream and mappend the outputs.
|
(Monad m, Semigroup b) => Semigroup (Auto m a b) | Fork the input stream and |
autoConstr :: Auto m a b -> String Source
Returns a string representation of the internal constructor of the
Auto
. Useful for debugging the result of compositions and functions
and seeing how they affect the internal structure of the Auto
.
In the order of efficiency, AutoFuncs tend to be faster than
AutoStates tend to be faster than AutoArbs. However, when composing
one with the other (using Category
or Applicative
), the two have to
be "reduced" to the greatest common denominator; composing an AutoFunc
with an AutoArb produces an AutoArb.
More benchmarking is to be done to be able to rigorously say what these really mean, performance wise.
toArb :: Monad m => Auto m a b -> Auto m a b Source
Re-structure Auto
internals to use the Arb
("arbitrary")
constructors, as recursion-based mealy machines.
Almost always a bad idea in every conceivable situation. Why is it even here?
I'm sorry.
purifyAuto :: Auto' a b -> Auto' a b Source
Running
:: Monad m | |
=> Auto m a b | the |
-> a | the input |
-> m (b, Auto m a b) | the output, and the updated |
Runs the Auto
through one step.
That is, given an
, returns a function that takes an Auto
m a ba
and returns a b
and an "updated"/"next" Auto
; an a -> m (b,
.Auto
m a b)
This is the main way of running an Auto
"step by step", so if you have
some sort of game loop that updates everything every "tick", this is
what you're looking for. At every loop, gather input a
, feed it into
the Auto
, "render" the result b
, and get your new Auto
to run the
next time.
Here is an example with
, the sumFrom
0Auto
whose output is the
cumulative sum of the inputs, and an underying monad of Identity
.
Here,
stepAuto :: Auto Identity Int Int -> (Int -> Identity (Int, Auto Identity Int Int))
Every time you "step", you give it an Int
and get a resulting Int
(the cumulative sum) and the "updated Auto
", with the updated
accumulator.
>>>
let a0 :: Auto Identity Int Int
a0 = sumFrom 0>>>
let Identity (res1, a1) = stepAuto a0 4 -- run with 4
>>>
res1
4 -- the cumulative sum, 4>>>
let Identity (res2, a2) = stepAuto a1 5 -- run with 5
>>>
res2
9 -- the cumulative sum, 4 + 5>>>
let Identity (res3, _ ) = stepAuto a2 3 -- run with 3
>>>
res3
12 -- the cumulative sum, 4 + 5 + 3
By the way, for the case where your Auto
is under Identity
, we have
a type synomym Auto'
...and a convenience function to make "running" it
more streamlined:
>>>
let a0 :: Auto' Int Int
a0 = sumFrom 0>>>
let (res1, a1) = stepAuto' a0 4 -- run with 4
>>>
res1
4 -- the cumulative sum, 4>>>
let (res2, a2) = stepAuto' a1 5 -- run with 5
>>>
res2
9 -- the cumulative sum, 4 + 5>>>
let (res3, _ ) = stepAuto' a2 3 -- run with 3
>>>
res3
12 -- the cumulative sum, 4 + 5 + 3
But, if your Auto
actaully has effects when being stepped, stepAuto
will execute them:
>>>
let a0 :: Auto IO Int Int
a0 = effect (putStrLn "hey!") *> sumFrom 0>>>
(res1, a1) <- stepAuto a0 4 -- run with 4
hey! -- IO effect>>>
res1
4 -- the cumulative sum, 4>>>
(res2, a2) <- stepAuto a1 5 -- run with 5
hey! -- IO effect>>>
res2
9 -- the cumulative sum, 4 + 5>>>
(res3, _ ) <- stepAuto a2 3 -- run with 3
hey! -- IO effect>>>
res3
12 -- the cumulative sum, 4 + 5 + 3
(Here,
is an effect
(putStrLn
"hey")
, which
ignores its input and just executes Auto
IO Int ()
every time it is
run. When we use putStrLn
"hey"*>
from Control.Applicative, we "combine" the two
Auto
s together and run them both on each input (4, 5, 3...)...but
for the "final" output at the end, we only return the output of the
second one,
(5, 9, 12...))sumFrom
0
If you think of an
as a "stateful function" Auto
m a ba -> m b
,
then stepAuto
lets you "run" it.
In order to directly run an Auto
on a stream, an [a]
, use
streamAuto
. That gives you an [a] -> m [b]
.
Runs an Auto'
through one step.
That is, given an
, returns a function that takes an Auto'
a ba
and returns a b
and an "updated"/"next" Auto'
; an a -> (b,
.Auto'
a b)
See stepAuto
documentation for motivations, use cases, and more
details. You can use this instead of stepAuto
when your underyling
monad is Identity
, and your Auto
doesn't produce any effects.
Here is an example with
, the sumFrom
0Auto'
whose output is the
cumulative sum of the inputs
stepAuto' :: Auto' Int Int -> (Int -> (Int, Auto' Int Int))
Every time you "step", you give it an Int
and get a resulting Int
(the cumulative sum) and the "updated Auto'
", with the updated
accumulator.
>>>
let a0 :: Auto' Int Int
a0 = sumFrom 0>>>
let (res1, a1) = stepAuto' a0 4 -- run with 4
>>>
res1
4 -- the cumulative sum, 4>>>
let (res2, a2) = stepAuto' a1 5 -- run with 5
>>>
res2
9 -- the cumulative sum, 4 + 5>>>
let (res3, _ ) = stepAuto' a2 3 -- run with 3
>>>
res3
12 -- the cumulative sum, 4 + 5 + 3
If you think of an
as a "stateful function" Auto'
a ba -> b
,
then stepAuto'
lets you "run" it.
In order to directly run an Auto'
on a stream, an [a]
, use
streamAuto'
. That gives you an [a] -> [b]
.
Serializing
The Auto
type offers an interface in which you can serialize
("freeze") and "resume" an Auto, in ByteString
(binary) form.
You can "freeze" any Auto
into a ByteString
using encodeAuto
(or,
if you want the raw Put
(from Data.Serialize) for some reason,
there's saveAuto
.
You can "resume" any Auto
from a ByteString
using decodeAuto
(or,
if you want the raw Get
for some reason, there's resumeAuto
).
Note decodeAuto
and resumeAuto
"resume" a given Auto
. That is,
if you call decodeAuto
on a "fresh Auto
", it'll decode
a ByteString
into that Auto
, but "resumed". That is, it'll "fast
forward" that Auto
into the state it was when it was saved.
For example, let's say I have a =
, the sumFrom
0Auto
whose output
is the cumulative sum of all of its inputs so far. If I feed it 3 and
10, it'll have its internal accumulator as 13, keeping track of all the
numbers it has seen so far.
>>>
let a = sumFrom 0
>>>
let (_, a' ) = stepAuto' a 3
>>>
let (_, a'') = stepAuto' a' 10
I can then use encodeAuto
to "freeze"/"save" the Auto
into the
ByteString
bs
:
>>>
let bs = encodeAuto a''
To "resume" / "load" it, I can use decodeAuto
to "resume" the
original a
. Remember, a
was our original Auto
, the summer
Auto
with a starting accumulator of 0. We use decodeAuto
to
"resume" it, with and resume it with its internal accumulator at 13.
>>>
let (Right resumed) = decodeAuto a bs
>>>
let (y, _) = stepAuto' resumed 0
13
Note that all of these would have had the same result:
>>>
let (Right resumed) = decodeAuto a' bs
>>>
let (Right resumed) = decodeAuto a'' bs
>>>
let (Right resumed) = decodeAuto (sumFrom 0) bs
I mean, after all, if decodeAuto
"fast forwards" an Auto
to the
state it was at when it was frozen...then all of these should really be
resumed to the same point, right?
One way you can think about it is that resumeAuto
/ decodeAuto
takes
an Auto
and creates a "blueprint" from that Auto
, on how to "load
it"; the blueprint contains what the form of the internal state is, and
their offets in the ByteString
. So in the above, a
, a'
, a''
,
and
all have the same "blueprint" --- their internal
states are of the same structure.sumFrom
0
Now, the magic of this all is that combining and transforming Auto
s
with the combinators in this library will also /compose serialization
strategies .... complex Auto
s and combinationschains of Auto
s
create serialization strategies "for free". The
auto-examples repo has a lot
of examples that use this to great effect, serializing entire
applications and entire chat bots without writing any serialization
code; it all does it "by itself". Be sure to read about the caveats in
the
tutorial.
Some specific Auto
s (indicated by a naming convention) might choose to
have internal state, yet ignore it when saving/loading. So, saving it
actaully saves no state, and "resuming" it really doesn't do anything.
That is,
. There isn't a real way to
identify from the type of the decodeAuto
a_ bs = Right a_Auto
if it will properly save/resume or
not, so you have to keep track of this yourself. In all of the Auto
"included" in this library, any Auto
whose name does not end in _
will serialize and resume. An Auto
whose name ends in _
is taken
by naming convention to be a non-resuming Auto
.
In your own compositions, if you are sure to always use resuming
Auto
s, your composition will also be properly resuming...so you don't
have to worry about this! You shouldn't really ever be "surprised",
because you'll always explicitly chose the resuming version for Auto
s
you want to resume, and the non-resuming version for those you don't.
Now, making or writing your own generic Auto
combinators and
transformers that take advantage of serialization is a bit of
a headache. When you can, you might be able to make combinators out of
the existing functions in this library. Sometimes, however, it's
unavoidable. If you are making your own Auto
combinators, making sure
serialization works as expected is tough; check out the documentation
for mkAutoM
for more details.
encodeAuto :: Auto m a b -> ByteString Source
Encode an Auto
and its internal state into a ByteString
.
decodeAuto :: Auto m a b -> ByteString -> Either String (Auto m a b) Source
Resume an Auto
from its ByteString
serialization, giving
a Left
if the deserialization is not possible.
saveAuto :: Auto m a b -> Put Source
Returns a Put
--- instructions (from Data.Serialize) on how to
"freeze" the Auto
, with its internal state, and save it to a binary
encoding. It can later be reloaded and "resumed" by
'resumeAuto'/'decodeAuto'.
resumeAuto :: Auto m a b -> Get (Auto m a b) Source
Returns a Get
from an Auto
--- instructions (from
Data.Serialize) on taking a ByteString and "restoring" the originally
saved Auto
, in the originally saved state.
unserialize :: Monad m => Auto m a b -> Auto m a b Source
Takes an Auto
that is serializable/resumable and returns an Auto
that is not. That is, when it is "saved", saves no data, and when it is
"resumed", resets itself back to the initial configuration every time;
in other words,
. Trying to "resume" it will just always give itself, unchanged.decodeAuto
(unserialize a) bs = Right (unserialize
a)
Underlying monad
:: (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
Special modifiers
Abstraction over lower-level funging with serialization; lets you
modify the result of an Auto
by being able to intercept the (b,
output and return a new output value Auto
m a b)m c
.
Note that this is a lot like fmap
:
fmap :: (b -> c) -> Auto m a b -> Auto m a c
Except gives you access to both the b
and the "updated Auto
";
instead of an b -> c
, you get to pass a (b,
.Auto
m a b) -> m c
Basically experimenting with a bunch of abstractions over different
lower-level modification of Auto
s, because making sure the
serialization works as planned can be a bit difficult.
Auto constructors
Lifting values and functions
:: b | constant value to be outputted |
-> Auto m a b |
Construct the Auto
whose output is always the given value, ignoring
its input.
Provided for API constency, but you should really be using pure
from
the Applicative
instance, from Control.Applicative, which does the
same thing.
:: m b | monadic action to be executed at every step |
-> Auto m a b |
Construct the Auto
that always "executes" the given monadic value at
every step, yielding the result as its output and ignoring its input.
Provided for API consistency, but you shold really be using effect
from Control.Auto.Effects, which does the same thing.
:: (a -> b) | pure function |
-> Auto m a b |
Construct a stateless Auto
that simply applies the given (pure)
function to every input, yielding the output. The output stream is just
the result of applying the function to every input.
streamAuto' (mkFunc f) = map f
This is rarely needed; you should be using arr
from the Arrow
instance, from Control.Arrow.
:: (a -> m b) | "monadic" function |
-> Auto m a b |
Construct a stateless Auto
that simply applies and executes the givne
(monadic) function to every input, yielding the output. The output
stream is the result of applying the function to every input,
executing/sequencing the action, and returning the returned value.
streamAuto (mkFuncM f) = mapM f
It's recommended that you use arrM
from Control.Auto.Effects. This
is only really provided for consistency.
from State transformers
Construct an Auto
from a state transformer: an a -> s -> (b, s)
gives you an
, for any Auto
m a bMonad
m
. At every step, it
takes in the a
input, runs the function with the stored internal
state, returns the b
result, and now contains the new resulting state.
You have to intialize it with an initial state, of course.
From the "stream transformer" point of view, this is rougly equivalent
to mapAccumL
from Data.List, with the function's arguments and
results in the backwards order.
streamAuto' (mkState f s0) = snd . mapAccumL (\s x -> swap (f x s))
Try not to use this if it's ever avoidable, unless you're a framework
developer or something. Try make something by combining/composing the
various Auto
combinators.
If your state s
does not have a Serialize
instance, then you should
either write a meaningful one, provide the serialization methods
manually with mkState'
, or throw away serializability and use
mkState_
.
:: (a -> s -> (b, s)) | state transformer |
-> s | initial state |
-> Auto m a b |
Construct an Auto
from a "monadic" state transformer: a -> s ->
m (b, s)
gives you an
. At every step, it takes in the
Auto
m a ba
input, runs the function with the stored internal state and
"executes" the m (b, s)
to get the b
output, and stores the s
as
the new, updated state. Must be initialized with an initial state.
Try not to use this if it's ever avoidable, unless you're a framework
developer or something. Try make something by combining/composing the
various Auto
combinators.
This version is a wrapper around mkAuto
, that keeps track of the
serialization and re-loading of the internal state for you, so you don't
have to deal with it explicitly.
If your state s
does not have a Serialize
instance, then you should
either write a meaningful one, provide the serialization methods
manually with mkStateM'
, or throw away serializability and use
mkStateM_
.
:: (a -> s -> m (b, s)) | (monadic) state transformer |
-> s | initial state |
-> Auto m a b |
from Accumulators
Result-first
Construct an Auto
from a "folding" function: b -> a -> b
yields an
. Basically acts like a Auto
m a bfoldl
or a scanl
. There is
an internal accumulator that is "updated" with an a
at every step.
Must be given an initial accumulator.
Example: an Auto
that sums up all of its input.
>>>
let summer = accum (+) 0
>>>
let (sum1, summer') = stepAuto' summer 3
>>>
sum1
3>>>
let (sum2, summer'') = stepAuto' summer' 10
>>>
sum2
13>>>
streamAuto' summer'' [1..10]
[14,16,19,23,28,34,41,49,58,68]
If your accumulator b
does not have a Serialize
instance, then you
should either write a meaningful one, or throw away serializability and
use accum_
.
:: (b -> a -> b) | accumulating function |
-> b | intial accumulator |
-> Auto m a b |
:: (Serialize b, Monad m) | |
=> (b -> a -> m b) | (monadic) accumulating function |
-> b | initial accumulator |
-> Auto m a b |
Construct an Auto
from a "monadic" "folding" function: b -> a ->
m b
yields an
. Basically acts like a Auto
m a bfoldM
or scanM
(if it existed). here is an internal accumulator that is "updated" with
an input a
with the result of the executed m b
at every step. Must
be given an initial accumulator.
See accum
for more details.
If your accumulator b
does not have a Serialize
instance, then you
should either write a meaningful one, or throw away serializability and
use accumM_
.
Initial accumulator-first
A "delayed" version of accum
, where the first output is the initial
state of the accumulator, before applying the folding function. Useful
in recursive bindings.
>>>
let summerD = accumD (+) 0
>>>
let (sum1, summerD') = stepAuto' summerD 3
>>>
sum1
0>>>
let (sum2, summerD'') = stepAuto' summerD' 10
>>>
sum2
3>>>
streamAuto' summerD'' [1..10]
[13,14,16,19,23,28,34,41,49,58]
(Compare with the example in accum
)
:: (b -> a -> b) | accumulating function |
-> b | intial accumulator |
-> Auto m a b |
The non-resuming/non-serializing version of accumD
.
:: (Serialize b, Monad m) | |
=> (b -> a -> m b) | (monadic) accumulating function |
-> b | initial accumulator |
-> Auto m a b |
A "delayed" version of accumM
, where the first output is the initial
state of the accumulator, before applying the folding function. Useful
in recursive bindings.
The non-resuming/non-serializing version of accumMD
.
Arbitrary Autos
:: Get (Auto m a b) | resuming/loading |
-> Put | saving |
-> (a -> (b, Auto m a b)) | step function |
-> Auto m a b |
Construct an Auto
by explicity giving its serialization,
deserialization, and the function from a
to a b
and "updated
Auto
".
Ideally, you wouldn't have to use this unless you are making your own framework. Try your best to make what you want by assembling primtives together. Working with serilization directly is hard.
See mkAutoM
for more detailed instructions on doing this right.
Like mkAuto
, but without any way of meaningful serializing or
deserializing.
Be careful! This Auto
can still carry arbitrary internal state, but
it cannot be meaningfully serialized or re-loaded/resumed. You can
still pretend to do so using
'resumeAuto'/'saveAuto'/'encodeAuto'/'decodeAuto' (and the type system
won't stop you), but when you try to "resume"/decode it, its state will
be lost.
:: Get (Auto m a b) | resuming/loading |
-> Put | saving |
-> (a -> m (b, Auto m a b)) | (monadic) step function |
-> Auto m a b |
Construct an Auto
by explicitly giving its serializiation,
deserialization, and the (monadic) function from a
to a b
and the
"updated Auto
".
See the "serialization" section in the Control.Auto.Core module for more information.
Ideally, you wouldn't have to use this unless you are making your own framework. Try your best to make what you want by assembling primtives together.
But sometimes you have to write your own combinators, and you're going
to have to use mkAutoM
to make it work.
Sometimes, it's simple:
fmap :: (a -> b) -> Auto r a -> Auto r b fmap f a0 = mkAutoM (do aResumed <- resumeAuto a0 return (fmap f aResumed) ) (saveAuto a0) $ x -> do (y, a1) <- stepAuto a0 x return (f y, fmap f a1)
Serializing
is just the same as serializing fmap
f a0a0
. And to
resume it, we resume a0
to get a resumed version of a0
, and then we
apply
to the fmap
fAuto
that we resumed.
Also another nice "simple" example is:
catchA :: Exception e => Auto IO a b -> Auto IO a (Either e b) catchA a = mkAutoM (do aResumed <- resumeAuto a return (catchA aResumed) ) (saveAuto a) $ x -> do eya' <- try $ stepAuto a x case eya' of Right (y, a') -> return (Right y, catchA a') Left e -> return (Left e , catchA a )
Which is basically the same principle, in terms of serializing and resuming strategies.
When you have "switching" --- things that behave like different Auto
s
at different points in time --- then things get a little complicated,
because you have to figure out which Auto
to resume.
For example, let's look at the source of -?>
:
(-?>) :: Monad m => Interval m a b -- ^ initial behavior -> Interval m a b -- ^ final behavior, when the initial -- behavior turns off. -> Interval m a b a1 -?> a2 = mkAutoM l s t where l = do flag <- get if flag then resumeAuto (switched a2) else (-?> a2) $ resumeAuto a1 s = put False *> saveAuto a1 t x = do (y1, a1') <- stepAuto a1 x case y1 of Just _ -> return (y1, a1' -?> a2) Nothing -> do (y, a2') <- stepAuto a2 x return (y, switched a2') switched a = mkAutoM (switched $ resumeAuto a) (put True *> saveAuto a) $ x -> do (y, a') <- stepAuto a x return (y, switched a')
We have to invent a serialization and reloading scheme, taking into
account the two states that the resulting Auto
can be in:
- Initially, it is behaving like
a1
. So, to save it, we put a flag saying that we are still in stage 1 (False
), and then puta1
's current serialization data. - After the switch, it is behaving like
a2
. So, to save it, we put a flag saying that we are now in stage 2 (True
), and then puta2
's current.
Now, when we resume a1
, -?>
a2resumeAuto
on a1
will
give us -?>
a2l
. So the Get
we use --- the process we use to resume the
entire a1
, will start at the initial -?>
a2Get
/loading
function, l
here. We have to encode our branching and
resuming/serialization scheme into the initial, front-facing l
. So
l
has to check for the flag, and if the flag is true, load in the data
for the switched state; otherwise, load in the data for the pre-switched
state.
Not all of them are this tricky. Mostly "switching" combinators will be tricky, because switching means changing what you are serializing.
This one might be considerably easier, because of mapM
:
zipAuto :: Monad m
=> a -- ^ default input value
-> [Auto m a b] -- ^ Auto
s to zip up
-> Auto m [a] [b]
zipAuto x0 as = mkAutoM (zipAuto x0 $ mapM resumeAuto as)
(mapM_ saveAuto as)
$ xs -> do
res <- zipWithM stepAuto as (xs ++ repeat x0)
let (ys, as') = unzip res
return (ys, zipAuto x0 as')
To serialize, we basically sequence saveAuto
over all of the internal
Auto
s --- serialize each of their serialization data one-by-one one
after the other in our binary.
To load, we do the same thing; we go over every Auto
in as
and
resumeAuto
it, and then collect the results in a list --- a list of
resumed Auto
s. And then we apply
to that list of
zipAuto
x0Auto
s, to get our resumed
.zipAuto
x0 as
So, it might be complicated. In the end, it might be all worth it, too,
to have implicit serialization compose like this. Think about your
serialization strategy first. Step back and think about what you need
to serialize at every step, and remember that it's _the initial_
"resuming" function that has to "resume everything"...it's not the
resuming function that exists when you finally save your Auto
, it's
the resuming Get
that was there at the beginning. For -?>
, the
intial l
had to know how to "skip ahead".
And of course as always, test.
If you need to make your own combinator or transformer but are having trouble with the serializtion, feel free to contact me at justin@jle.im, on freenode at #haskell or #haskell-auto, open a github issue, etc. Just contact me somehow, I'll be happy to help!
Like mkAutoM
, but without any way of meaningful serializing or
deserializing.
Be careful! This Auto
can still carry arbitrary internal state, but
it cannot be meaningfully serialized or re-loaded/resumed. You can
still pretend to do so using
'resumeAuto'/'saveAuto'/'encodeAuto'/'decodeAuto' (and the type system
won't stop you), but when you try to "resume"/decode it, its state will
be reset.
Strictness
forceSerial :: Auto m a b -> Auto m a b Source
Force the serializing components of an Auto
.
TODO: Test if this really works