monad-wrap-0.0: Wrap functions such as catch around different monads

Control.Monad.Wrap

Contents

Description

Class of monad transformers whose computations can be wrapped by functions such as catch and finally that operate on inner monadic types. This works for all standard monad transformers except for ContT.

The main method in this module is wrap, which wraps a function on one monad around a transformed version of that monad. This is useful in many situations, but it is important to keep in mind that this will affect the semantics of the monad. For example, if you wrap forkIO around a StateT X IO monad, it will fork the state of the monad into two independently updated copies of the state, one for each thread. Similarly, if you wrap catch around a WriterT X IO monad, you can catch an exception and return a value, but the writer state will be re-wound to the point at which you computed the result value (using result or resultF).

Synopsis

The MonadWrap type

class MonadWrap t a r | t a -> r whereSource

Methods

wrap :: Monad m => (m r -> m r) -> t m a -> t m aSource

This function is called to wrap a computation in a tansformed monad, t m, with a function that expects an argument and returns a result of the inner monadic type, m. The canonical example of this is using a monad transformer such as ReaderT, having a computation x :: ReaderT MyConfig IO a, and wanting to wrap a function such as finally :: IO b -> IO b around x to run a cleanup function even when an exception is thrown. If x invokes a ReaderT function such as ask, this cannot be accomplished with the ordinary monad transformer method lift. Instead, it can be achieved with:

    wrap (\op -> op `finally` cleanup) x

If the inner monad is nested within multiple levels of transformer, you can invoke wrap multiple times, e.g.:

    wrap (wrap (\op -> op `finally` cleanup)) x

result :: (Monad m, Monad (t m)) => a -> t m rSource

Sometimes the wrapping function passed as the first argument of wrap needs to produce its own return value rather than passing one straight through. This is the case with catch. To do this, use result to tranlate a pure value into the inner-monad value required by the outer monad transformer.

(Note that result is basically a pure transofmation, but it produces a value in the outer monad primarily just so that it can infer from context what type of result to produce. The pure value returned must be lifted into the inner monad with return.)

result is perhaps best illustrated by example. With a single level of nesting, use something like:

    err <- result Nothing
    wrap (handle (\(SomeException _) -> return err))
          $ liftM Just $ someIOComputation

For multiple levels of nesting, you will need to invoke result multiple times, e.g.:

    outerErr <- result Nothing
    innerErr <- lift $ result outerErr
    wrap (wrap (handle (\(SomeException _) -> return innerErr)))
          $ liftM Just $ someIOComputation

Note the use of lift so as to compute the inner result transformation in the inner monad. Further levels of nesting require increasing numbers of lifts.

It is important to keep in mind that where you invoke result (or resultF) may affect the result. For instance, with the StateT or WriterT transformer, if you return a value computed with result, the state will be re-wound to the point at which you called result, discarding any changes that may have taken place in the mean time.

resultF :: Monad m => t m (a -> r)Source

resultF returns a function that can be used to perform the same transformation as result. This is necessary if you need to compute the result type dynamically within the wrapping function. result can be implemented in terms of resultF as:

  result a = do f <- resultF
                return (f a)

The example given above for result could altenratively have been implemented as:

    fout <- resultF
    fin <- lift resultF
    let f = fin . fout
    wrap (wrap (handle (\(SomeException _) -> return $ f Nothing)))
          $ liftM Just $ someIOComputation

Note that the order of composition is f = fin . fout, and not f = fout . fin. This is because types and result values nest in opposite directions with monad transformers. Even though IO is the inner monad in a type such as WriterT String IO (), running any computation of this type produces a value of type IO ((), String).

Instances

MonadWrap ListT a [a] 
MonadWrap (ReaderT r) a a 
Monoid w => MonadWrap (WriterT w) a (a, w) 
MonadWrap (StateT s) a (a, s) 
Error e => MonadWrap (ErrorT e) a (Either e a) 
Monoid w => MonadWrap (RWST r w s) a (a, s, w) 

Wrapping IO functions around other monads

class Monad m => MonadWrapIO m a r | m a -> r whereSource

MonadWrapIO is analogous to MonadWrap, but where the wrapping function is always of type IO r -> IO r. The point of MonadWrapIO is to go through as many nested monad transformers as necessary to reach the IO monad, so you don't have to keep track of where you are in terms of monad nesting depth.

Methods

wrapIO :: (IO r -> IO r) -> m a -> m aSource

wrapIO is to wrap as liftIO is to lift.

resultFIO :: m (a -> r)Source

resultFIO is to resultF as liftIO is to lift.

resultIO :: a -> m rSource

resultIO is to result as liftIO is to lift.

Instances

MonadWrapIO IO a a 
(Monad m, MonadTrans t, Monad (t m), MonadWrapIO m ar r, MonadWrap t a ar) => MonadWrapIO (t m) a r 

Example

Here is a longer example showing finally and catch used within the WriterT and StateT monads. (Note that it would be easier to use resultIO and wrapIO in middle, but here we show how to wrap through multiple monads manually.)

    {-# LANGUAGE DeriveDataTypeable #-}
    module Main where

    import Prelude hiding (catch)
    import Control.Exception
    import Control.Monad.State
    import Control.Monad.Writer
    import Data.Typeable

    import Control.Monad.Wrap

    type OuterMonad = WriterT String IO
    
    type MyState = Int
    type InnerMonad = StateT MyState OuterMonad
    
    data Trap = Trap deriving (Typeable, Show)
    instance Exception Trap
    
    handler :: String -> IO a -> Trap -> IO a
    handler place a e = do
      putStrLn $ "caught " ++ show e ++ " in " ++ place
      a
    
    inner :: InnerMonad ()
    inner = do
      liftIO $ putStrLn "running inner"
      liftIO $ throwIO Trap
    
    middle :: InnerMonad ()
    middle = do
      put 1                         -- Can do StateT operations
      liftIO $ putStrLn "running middle"
      x <- result ()
      y <- lift $ result x
      wrap (wrap (handle $ handler "middle" $ return y)) inner
      wrap (wrap do_finally) inner
        where
          do_finally = flip finally $ putStrLn "middle finally!"
    
    outer :: OuterMonad ()
    outer = do
      tell "This is outer"          -- Can do WriteT operations
      liftIO $ putStrLn "About to run middle"
      x <- result ()
      wrap (handle $ handler "outer" $ return x) (evalStateT middle 0)
      liftIO $ putStrLn "Just ran middle"
      wrap do_finally (evalStateT middle 0)
      liftIO $ putStrLn "This line won't be reached"
        where
          do_finally = flip finally $ putStrLn "outer finally!"
    
    main :: IO ((), String)
    main = runWriterT outer

The above code should produce the following output:

    *Main> main
    About to run middle
    running middle
    running inner
    caught Trap in middle
    running inner
    middle finally!
    caught Trap in outer
    Just ran middle
    running middle
    running inner
    caught Trap in middle
    running inner
    middle finally!
    outer finally!
    *** Exception: Trap
    *Main>