iterIO-0.1: Iteratee-based IO with pipe operators

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 :: Iter String IO Bool
iter1 = ...

iter2 :: Iter String (StateT MyState 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 Iter String IO 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 MonadTrans 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 Iter t m is member any mtl classes (such as MonadReader and MonadState) that m is.

iter1 :: Iter String (ReaderT MyState IO) Bool
iter1 = do
  s <- ask
  liftIO $ (putStrLn (show s) >> return True)
        `catch` (SomeException _) -> return False

iter2 :: Iter String (StateT MyState IO) ()
iter2 = do
  s <- get
  ok <- liftI $ runReaderTI iter1 s
  if ok then return () else fail "iter1 failed"

Synopsis

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 Iter s m computation from witin the Iter s (t m) monad, where t is a MonadTrans.

liftIterIO :: (ChunkData t, MonadIO m) => Iter t IO a -> Iter t m aSource

Run an Iter t IO computation from within an Iter t m monad where m is in class MonadIO.

runContTI :: (ChunkData t, Monad m) => Iter t (ContT (Iter t m a) m) a -> Iter t m aSource

Turn a computation of type Iter t (ContT (Iter t m a) m) a into one of type Iter t m a. Note the continuation has to return type Iter t m a and not a so that runContTI can call itself recursively.

runErrorTI :: (Monad m, ChunkData t, Error e) => Iter t (ErrorT e m) a -> Iter t m (Either e a)Source

Run a computation of type Iter t (ErrorT e m) from within the Iter t m monad. This function is here for completeness, but please consider using throwI instead, since the Iter monad already has built-in exception handling and it's best to have a single, uniform approach to error reporting.

runListTI :: (Monad m, ChunkData t) => Iter t (ListT m) a -> Iter t m [a]Source

Run an Iter t (ListT m) computation from within the Iter t m monad.

runReaderTI :: (ChunkData t, Monad m) => Iter t (ReaderT r m) a -> r -> Iter t m aSource

Run an Iter t (ReaderT r m) computation from within the Iter t m monad.

runRWSISource

Arguments

:: (ChunkData t, Monoid w, Monad m) 
=> Iter t (RWST r w s m) a

Computation to transform

-> r

Reader State

-> s

Mutable State

-> Iter t m (a, s, w)

Returns result, mutable state, writer

Run an Iter t (RWST r w s m) computation from within the Iter t m monad.

runRWSLISource

Arguments

:: (ChunkData t, Monoid w, Monad m) 
=> Iter t (RWST r w s m) a

Computation to transform

-> r

Reader State

-> s

Mutable State

-> Iter t m (a, s, w)

Returns result, mutable state, writer

Run an Iter t (RWST r w s m) computation from within the Iter t m monad. Just like runRWSI, execpt this function is for Lazy RWST rather than strict RWST.

runStateTI :: (ChunkData t, Monad m) => Iter t (StateT s m) a -> s -> Iter t m (a, s)Source

Run an Iter t (StateT m) computation from within the Iter t m monad.

runStateTLI :: (ChunkData t, Monad m) => Iter t (StateT s m) a -> s -> Iter t m (a, s)Source

Run an Iter t (StateT m) computation from within the Iter t m monad. Just like runStateTI, except this function works on Lazy StateT rather than strict StateT.

runWriterTI :: (ChunkData t, Monoid w, Monad m) => Iter t (WriterT w m) a -> Iter t m (a, w)Source

Run an Iter t (WriterT w m) computation from within the Iter t m monad.

runWriterTLI :: (ChunkData t, Monoid w, Monad m) => Iter t (WriterT w m) a -> Iter t m (a, w)Source

Run an Iter t (WriterT w m) computation from within the Iter t m monad. This is the same as runWriterT but for the Lazy WriterT, rather than the strict one.

Functions for building new monad adapters

adaptIterSource

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 :: (MonadTrans t, Monad m, Monad (t m), ChunkData s) =>
           Iter s m a -> Iter s (t m) a
  liftI = adaptIter id (\m -> lift (lift m) >>= liftI)

Here lift (lift m) executes a computation m of type m (Iter s m a) from within the Iter s (t m) monad. The result, of type Iter s m a, can then be fed back into liftI 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.

adaptIterMSource

Arguments

:: (ChunkData t, Monad m1, Monad m2) 
=> (m1 (Iter t m1 a) -> m2 (Iter t m1 a))

Conversion function

-> Iter t m1 a

Iter of input monad

-> Iter t m2 a

Returns Iter of output monad

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, MonadIO m) => Iter t IO a -> Iter t m a
 liftIterIO = adaptIterM liftIO

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)) 

runIterStateT :: (ChunkData t, Monad m) => Iter t (IterStateT s m) a -> s -> Iter t m (IterR t m a, s)Source

Runs an IterStateT s m computation on some state s. 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 pullupResid in Data.IterIO.Inum).

iget :: Monad m => Iter t (IterStateT s m) sSource

Returns the state in an Iter t (IterStateT s m) monad. Analogous to get for a StateT s m monad.

igets :: Monad m => (s -> a) -> Iter t (IterStateT s m) aSource

Returns a particular field of the IterStateT state, analogous to gets for StateT.

iput :: Monad m => s -> Iter t (IterStateT s m) ()Source

Sets the IterStateT state. Analogous to put for StateT.

imodify :: Monad m => (s -> s) -> Iter t (IterStateT s m) ()Source

Modifies the IterStateT state. Analogous to modify for StateT.