transformers-0.5.6.2: Concrete functor and monad transformers

Copyright(c) Andy Gill 2001
(c) Oregon Graduate Institute of Science and Technology 2001
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Class

Contents

Description

The class of monad transformers.

A monad transformer makes a new monad out of an existing monad, such that computations of the old monad may be embedded in the new one. To construct a monad with a desired set of features, one typically starts with a base monad, such as Identity, [] or IO, and applies a sequence of monad transformers.

Synopsis

Transformer class

class MonadTrans t where Source #

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a monad transformation:

Methods

lift :: Monad m => m a -> t m a Source #

Lift a computation from the argument monad to the constructed monad.

Instances
MonadTrans ListT # 
Instance details

Defined in Control.Monad.Trans.List

Methods

lift :: Monad m => m a -> ListT m a Source #

MonadTrans MaybeT # 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

lift :: Monad m => m a -> MaybeT m a Source #

MonadTrans (ErrorT e) # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

lift :: Monad m => m a -> ErrorT e m a Source #

MonadTrans (ExceptT e) # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a Source #

MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

lift :: Monad m => m a -> IdentityT m a Source #

MonadTrans (ReaderT r) # 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

lift :: Monad m => m a -> ReaderT r m a Source #

MonadTrans (SelectT r) # 
Instance details

Defined in Control.Monad.Trans.Select

Methods

lift :: Monad m => m a -> SelectT r m a Source #

MonadTrans (StateT s) # 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

lift :: Monad m => m a -> StateT s m a Source #

MonadTrans (StateT s) # 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a Source #

MonadTrans (WriterT w) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

lift :: Monad m => m a -> WriterT w m a Source #

Monoid w => MonadTrans (WriterT w) # 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

lift :: Monad m => m a -> WriterT w m a Source #

Monoid w => MonadTrans (AccumT w) # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

lift :: Monad m => m a -> AccumT w m a Source #

Monoid w => MonadTrans (WriterT w) # 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

lift :: Monad m => m a -> WriterT w m a Source #

MonadTrans (ContT r) # 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

lift :: Monad m => m a -> ContT r m a Source #

MonadTrans (RWST r w s) # 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

lift :: Monad m => m a -> RWST r w s m a Source #

Monoid w => MonadTrans (RWST r w s) # 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

lift :: Monad m => m a -> RWST r w s m a Source #

Monoid w => MonadTrans (RWST r w s) # 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

lift :: Monad m => m a -> RWST r w s m a Source #

Conventions

Most monad transformer modules include the special case of applying the transformer to Identity. For example, State s is an abbreviation for StateT s Identity.

Each monad transformer also comes with an operation runXXXT to unwrap the transformer, exposing a computation of the inner monad. (Currently these functions are defined as field labels, but in the next major release they will be separate functions.)

All of the monad transformers except ContT and SelectT are functors on the category of monads: in addition to defining a mapping of monads, they also define a mapping from transformations between base monads to transformations between transformed monads, called mapXXXT. Thus given a monad transformation t :: M a -> N a, the combinator mapStateT constructs a monad transformation

mapStateT t :: StateT s M a -> StateT s N a

For these monad transformers, lift is a natural transformation in the category of monads, i.e. for any monad transformation t :: M a -> N a,

Each of the monad transformers introduces relevant operations. In a sequence of monad transformers, most of these operations.can be lifted through other transformers using lift or the mapXXXT combinator, but a few with more complex type signatures require specialized lifting combinators, called liftOp (see Control.Monad.Signatures).

Strict monads

A monad is said to be strict if its >>= operation is strict in its first argument. The base monads Maybe, [] and IO are strict:

>>> undefined >> return 2 :: Maybe Integer
*** Exception: Prelude.undefined

However the monad Identity is not:

>>> runIdentity (undefined >> return 2)
2

In a strict monad you know when each action is executed, but the monad is not necessarily strict in the return value, or in other components of the monad, such as a state. However you can use seq to create an action that is strict in the component you want evaluated.

Examples

Parsing

The first example is a parser monad in the style of

We can define such a parser monad by adding a state (the String remaining to be parsed) to the [] monad, which provides non-determinism:

import Control.Monad.Trans.State

type Parser = StateT String []

Then Parser is an instance of MonadPlus: monadic sequencing implements concatenation of parsers, while mplus provides choice. To use parsers, we need a primitive to run a constructed parser on an input string:

runParser :: Parser a -> String -> [a]
runParser p s = [x | (x, "") <- runStateT p s]

Finally, we need a primitive parser that matches a single character, from which arbitrarily complex parsers may be constructed:

item :: Parser Char
item = do
    c:cs <- get
    put cs
    return c

In this example we use the operations get and put from Control.Monad.Trans.State, which are defined only for monads that are applications of StateT. Alternatively one could use monad classes from the mtl package or similar, which contain methods get and put with types generalized over all suitable monads.

Parsing and counting

We can define a parser that also counts by adding a WriterT transformer:

import Control.Monad.Trans.Class
import Control.Monad.Trans.State
import Control.Monad.Trans.Writer
import Data.Monoid

type Parser = WriterT (Sum Int) (StateT String [])

The function that applies a parser must now unwrap each of the monad transformers in turn:

runParser :: Parser a -> String -> [(a, Int)]
runParser p s = [(x, n) | ((x, Sum n), "") <- runStateT (runWriterT p) s]

To define the item parser, we need to lift the StateT operations through the WriterT transformer.

item :: Parser Char
item = do
    c:cs <- lift get
    lift (put cs)
    return c

In this case, we were able to do this with lift, but operations with more complex types require special lifting functions, which are provided by monad transformers for which they can be implemented. If you use the monad classes of the mtl package or similar, this lifting is handled automatically by the instances of the classes, and you need only use the generalized methods get and put.

We can also define a primitive using the Writer:

tick :: Parser ()
tick = tell (Sum 1)

Then the parser will keep track of how many ticks it executes.

Interpreter monad

This example is a cut-down version of the one in

Suppose we want to define an interpreter that can do I/O and has exceptions, an environment and a modifiable store. We can define a monad that supports all these things as a stack of monad transformers:

import Control.Monad.Trans.Class
import Control.Monad.Trans.State
import qualified Control.Monad.Trans.Reader as R
import qualified Control.Monad.Trans.Except as E
import Control.Monad.IO.Class

type InterpM = StateT Store (R.ReaderT Env (E.ExceptT Err IO))

for suitable types Store, Env and Err.

Now we would like to be able to use the operations associated with each of those monad transformers on InterpM actions. Since the uppermost monad transformer of InterpM is StateT, it already has the state operations get and set.

The first of the ReaderT operations, ask, is a simple action, so we can lift it through StateT to InterpM using lift:

ask :: InterpM Env
ask = lift R.ask

The other ReaderT operation, local, has a suitable type for lifting using mapStateT:

local :: (Env -> Env) -> InterpM a -> InterpM a
local f = mapStateT (R.local f)

We also wish to lift the operations of ExceptT through both ReaderT and StateT. For the operation throwE, we know throwE e is a simple action, so we can lift it through the two monad transformers to InterpM with two lifts:

throwE :: Err -> InterpM a
throwE e = lift (lift (E.throwE e))

The catchE operation has a more complex type, so we need to use the special-purpose lifting function liftCatch provided by most monad transformers. Here we use the ReaderT version followed by the StateT version:

catchE :: InterpM a -> (Err -> InterpM a) -> InterpM a
catchE = liftCatch (R.liftCatch E.catchE)

We could lift IO actions to InterpM using three lifts, but InterpM is automatically an instance of MonadIO, so we can use liftIO instead:

putStr :: String -> InterpM ()
putStr s = liftIO (Prelude.putStr s)