| Safe Haskell | Trustworthy |
|---|
Data.IterIO.Trans
Contents
Description
This module contains various helper functions and instances for
using Iters of different Monads together in the same pipeline.
For example, as-is the following code is illegal:
iter1 ::IterString IO Bool iter1 = ... iter2 ::IterString (StateTMyState IO) () iter2 = do ... s <- iter1 -- ILLEGAL: iter1 is in wrong monad ...
You can't invoke iter1 from within iter2 because the Iter
type is wrapped around a different Monad in each case. However,
the function liftI exactly solves this problem:
s <- liftI iter1
Conversely, you may be in a Monad like and
need to invoke a computation that requires some other monad
functionality, such as a reader. There are a number of
iteratee-specific runner functions that help you run other
Iter String IOMonadTrans transformers inside the Iter monad. These typically
use the names of the runner functions in the mtl library, but with
an I appended--for instance runReaderTI, runStateTI,
runWriterTI. Here's a fuller example of adapting the inner
Iter Monad. The example also illustrates that is
member any mtl classes (such as Iter t mMonadReader and MonadState)
that m is.
iter1 :: Iter String (ReaderTMyState IO) Bool iter1 = do s <-askliftIO $ (putStrLn(shows) >> return True) `catch` (SomeException_) -> return False iter2 :: Iter String (StateTMyState IO) () iter2 = do s <-getok <-liftI$runReaderTIiter1 s if ok then return () else fail "iter1 failed"
- liftI :: (MonadTrans t, Monad m, Monad (t m), ChunkData s) => Iter s m a -> Iter s (t m) a
- liftIterIO :: (ChunkData t, MonadIO m) => Iter t IO a -> Iter t m a
- runContTI :: (ChunkData t, Monad m) => Iter t (ContT (Iter t m a) m) a -> Iter t m a
- runErrorTI :: (Monad m, ChunkData t, Error e) => Iter t (ErrorT e m) a -> Iter t m (Either e a)
- runListTI :: (Monad m, ChunkData t) => Iter t (ListT m) a -> Iter t m [a]
- runReaderTI :: (ChunkData t, Monad m) => Iter t (ReaderT r m) a -> r -> Iter t m a
- runRWSI :: (ChunkData t, Monoid w, Monad m) => Iter t (RWST r w s m) a -> r -> s -> Iter t m (a, s, w)
- runRWSLI :: (ChunkData t, Monoid w, Monad m) => Iter t (RWST r w s m) a -> r -> s -> Iter t m (a, s, w)
- runStateTI :: (ChunkData t, Monad m) => Iter t (StateT s m) a -> s -> Iter t m (a, s)
- runStateTLI :: (ChunkData t, Monad m) => Iter t (StateT s m) a -> s -> Iter t m (a, s)
- runWriterTI :: (ChunkData t, Monoid w, Monad m) => Iter t (WriterT w m) a -> Iter t m (a, w)
- runWriterTLI :: (ChunkData t, Monoid w, Monad m) => Iter t (WriterT w m) a -> Iter t m (a, w)
- adaptIter :: (ChunkData t, Monad m1) => (a -> b) -> (m1 (Iter t m1 a) -> Iter t m2 b) -> Iter t m1 a -> Iter t m2 b
- adaptIterM :: (ChunkData t, Monad m1, Monad m2) => (m1 (Iter t m1 a) -> m2 (Iter t m1 a)) -> Iter t m1 a -> Iter t m2 a
- newtype IterStateT s m a = IterStateT (s -> m (a, s))
- runIterStateT :: (ChunkData t, Monad m) => Iter t (IterStateT s m) a -> s -> Iter t m (IterR t m a, s)
- iget :: Monad m => Iter t (IterStateT s m) s
- igets :: Monad m => (s -> a) -> Iter t (IterStateT s m) a
- iput :: Monad m => s -> Iter t (IterStateT s m) ()
- imodify :: Monad m => (s -> s) -> Iter t (IterStateT s m) ()
Adapters for Iters of mtl transformers
liftI :: (MonadTrans t, Monad m, Monad (t m), ChunkData s) => Iter s m a -> Iter s (t m) aSource
Run an computation from witin the Iter s m
monad, where Iter s (t m)t is a MonadTrans.
runErrorTI :: (Monad m, ChunkData t, Error e) => Iter t (ErrorT e m) a -> Iter t m (Either e a)Source
runWriterTLI :: (ChunkData t, Monoid w, Monad m) => Iter t (WriterT w m) a -> Iter t m (a, w)Source
Run an computation from within
the Iter t (WriterT w m) monad. This is the same as Iter t mrunWriterT but for
the Lazy WriterT, rather than the strict one.
Functions for building new monad adapters
Arguments
| :: (ChunkData t, Monad m1) | |
| => (a -> b) | How to adapt result values |
| -> (m1 (Iter t m1 a) -> Iter t m2 b) | How to adapt computations |
| -> Iter t m1 a | Input computation |
| -> Iter t m2 b | Output computation |
Adapt an Iter from one monad to another. This function is the
lowest-level monad adapter function, upon which all of the other
adapters are built. adaptIter requires two functions as
arguments. One adapts the result to a new type (if required). The
second adapts monadic computations from one monad to the other.
For example, liftI could be implemented as:
liftI :: (MonadTranst, Monad m, Monad (t m),ChunkDatas) =>Iters m a ->Iters (t m) a liftI = adaptIterid(\m ->lift(liftm) >>= liftI)
Here executes a computation lift (lift m)m of type m
( from within the Iter s m a) monad. The
result, of type Iter s (t m), can then be fed back into
Iter s m aliftI recursively.
Note that in general a computation adapters must invoke the outer
adapter function recursively. adaptIter is designed this way
because the result adapter function may need to change. An example
is runStateTI, which could be implemented as follows:
runStateTI :: (ChunkData t, Monad m) =>
Iter t (StateT s m) a -> s -> Iter t m (a, s)
runStateTI iter s = adaptIter adaptResult adaptComputation iter
where adaptResult a = (a, s)
adaptComputation m = do (r', s') <- lift (runStateT m s)
runStateTI r' s'
Here, after executing runStateT, the state may be modified.
Thus, adaptComputation invokes runStateTI recursively with the
modified state, s', to ensure that subsequent IterM
computations will be run on the latest state, and that eventually
adaptResult will pair the result a with the newest state.
Arguments
| :: (ChunkData t, Monad m1, Monad m2) | |
| => (m1 (Iter t m1 a) -> m2 (Iter t m1 a)) | Conversion function |
| -> Iter t m1 a |
|
| -> Iter t m2 a | Returns |
Simplified adapter function to translate Iter computations from
one monad to another. This only works on monads m for which
running m a returns a result of type a. For more complex
scenarios (such as ListT or StateT), you need to use the more
general adaptIter.
As an example, the liftIterIO function is implemented as follows:
liftIterIO :: (ChunkData t,MonadIOm) => Iter t IO a -> Iter t m a liftIterIO = adaptIterMliftIO
Iter-specific state monad transformer
newtype IterStateT s m a Source
IterStateT is a variant of the StateT monad transformer
specifically designed for use inside Iters. The IterStateT
Monad itself is the same as StateT. However, the runIterStateT
function works differently from runStateT--it returns an IterR
and the result state separately. The advantage of this approach is
that you can still recover the state at the point of the excaption
even after an IterFail or InumFail condition.
Constructors
| IterStateT (s -> m (a, s)) |
Instances
| MonadError e m => MonadError e (IterStateT s m) | |
| MonadReader r m => MonadReader r (IterStateT s m) | |
| MonadWriter w m => MonadWriter w (IterStateT s m) | |
| MonadTrans (IterStateT s) | |
| Monad m => Monad (IterStateT s m) | |
| MonadIO m => MonadIO (IterStateT s m) | |
| MonadCont m => MonadCont (IterStateT s m) |
runIterStateT :: (ChunkData t, Monad m) => Iter t (IterStateT s m) a -> s -> Iter t m (IterR t m a, s)Source
Runs an computation on some state IterStateT s ms.
Returns the result (IterR) of the Iter and the state of s as
a pair. Pulls residual input up to the enclosing Iter monad (as
with in Data.IterIO.Inum).
pullupResid
iget :: Monad m => Iter t (IterStateT s m) sSource
Returns the state in an monad.
Analogous to Iter t (IterStateT s m) for a get monad.
StateT s m
igets :: Monad m => (s -> a) -> Iter t (IterStateT s m) aSource
Returns a particular field of the IterStateT state, analogous
to for gets.
StateT
iput :: Monad m => s -> Iter t (IterStateT s m) ()Source
Sets the IterStateT state. Analogous to for
put.
StateT
imodify :: Monad m => (s -> s) -> Iter t (IterStateT s m) ()Source
Modifies the IterStateT state. Analogous to for
modify.
StateT