Haskell Hierarchical Libraries (base package)ContentsIndex
Control.Monad
Portability portable
Stability provisional
Maintainer libraries@haskell.org
Contents
Functor and monad classes
Functions
Naming conventions
Basic functions from the Prelude
Generalisations of list functions
Conditional execution of monadic expressions
Monadic lifting operators
Description
The Functor, Monad and MonadPlus classes, with some useful operations on monads.
Synopsis
class Functor f where
fmap :: (a -> b) -> f a -> f b
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
return :: a -> m a
fail :: String -> m a
class Monad m => MonadPlus m where
mzero :: m a
mplus :: m a -> m a -> m a
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
sequence :: Monad m => [m a] -> m [a]
sequence_ :: Monad m => [m a] -> m ()
(=<<) :: Monad m => (a -> m b) -> m a -> m b
join :: Monad m => m (m a) -> m a
msum :: MonadPlus m => [m a] -> m a
filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]
mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c])
zipWithM :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM_ :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m ()
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a
foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m ()
replicateM :: Monad m => Int -> m a -> m [a]
replicateM_ :: Monad m => Int -> m a -> m ()
guard :: MonadPlus m => Bool -> m ()
when :: Monad m => Bool -> m () -> m ()
unless :: Monad m => Bool -> m () -> m ()
liftM :: Monad m => (a1 -> r) -> m a1 -> m r
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
ap :: Monad m => m (a -> b) -> m a -> m b
Functor and monad classes
class Functor f where

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

 fmap id  ==  id
 fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Maybe and IO defined in the Prelude satisfy these laws.

Methods
fmap :: (a -> b) -> f a -> f b
Instances
Functor (Cont r)
Monad m => Functor (ContT r m)
Functor (Either e)
Monad m => Functor (ErrorT e m)
Functor Identity
Monad m => Functor (ListT m)
Functor (RWS r w s)
Monad m => Functor (RWST r w s m)
Functor ((->) r)
Functor (Reader r)
Monad m => Functor (ReaderT r m)
Functor (ST s)
Functor (State s)
Monad m => Functor (StateT s m)
Functor (Writer w)
Monad m => Functor (WriterT w m)
Functor Maybe
Ix i => Functor (Array i)
Functor []
Functor IO
Functor (ST s)
Functor ReadP
Functor ReadPrec
class Monad m where

The Monad class defines the basic operations over a monad. Instances of Monad should satisfy the following laws:

 return a >>= k  ==  k a
 m >>= return  ==  m
 m >>= (\x -> k x >>= h)  ==  (m >>= k) >>= h

Instances of both Monad and Functor should additionally satisfy the law:

 fmap f xs  ==  xs >>= return . f

The instances of Monad for lists, Maybe and IO defined in the Prelude satisfy these laws.

Methods
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
return :: a -> m a
fail :: String -> m a
Instances
ArrowApply a => Monad (ArrowMonad a)
Monad (Cont r)
Monad m => Monad (ContT r m)
Error e => Monad (Either e)
(Monad m, Error e) => Monad (ErrorT e m)
Monad Identity
Monad m => Monad (ListT m)
Monoid w => Monad (RWS r w s)
(Monoid w, Monad m) => Monad (RWST r w s m)
Monad ((->) r)
Monad (Reader r)
Monad m => Monad (ReaderT r m)
Monad (ST s)
Monad (State s)
Monad m => Monad (StateT s m)
Monoid w => Monad (Writer w)
(Monoid w, Monad m) => Monad (WriterT w m)
Monad Maybe
Monad []
Monad IO
Monad (ST s)
Monad P
Monad ReadP
Monad ReadPrec
class Monad m => MonadPlus m where
The MonadPlus class definition
Methods
mzero :: m a
mplus :: m a -> m a -> m a
Instances
MonadPlus []
MonadPlus Maybe
MonadPlus IO
Error e => MonadPlus (Either e)
(Monad m, Error e) => MonadPlus (ErrorT e m)
Monad m => MonadPlus (ListT m)
(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m)
MonadPlus m => MonadPlus (ReaderT r m)
MonadPlus m => MonadPlus (StateT s m)
(Monoid w, MonadPlus m) => MonadPlus (WriterT w m)
MonadPlus P
MonadPlus ReadP
MonadPlus ReadPrec
Functions
Naming conventions

The functions in this library use the following naming conventions:

  • A postfix `M' always stands for a function in the Kleisli category: m is added to function results (modulo currying) and nowhere else. So, for example,
  filter  ::              (a ->   Bool) -> [a] ->   [a]
  filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
  • A postfix `_' changes the result type from (m a) to (m ()). Thus (in the Prelude):
  sequence  :: Monad m => [m a] -> m [a] 
  sequence_ :: Monad m => [m a] -> m () 
  • A prefix `m' generalises an existing function to a monadic form. Thus, for example:
  sum  :: Num a       => [a]   -> a
  msum :: MonadPlus m => [m a] -> m a
Basic functions from the Prelude
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
sequence :: Monad m => [m a] -> m [a]
sequence_ :: Monad m => [m a] -> m ()
(=<<) :: Monad m => (a -> m b) -> m a -> m b
Generalisations of list functions
join :: Monad m => m (m a) -> m a
The join function is the conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.
msum :: MonadPlus m => [m a] -> m a
filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]
mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c])
The mapAndUnzipM function maps its first argument over a list, returning the result as a pair of lists. This function is mainly used with complicated data structures or a state-transforming monad.
zipWithM :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m [c]
The zipWithM function generalises zipWith to arbitrary monads.
zipWithM_ :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_ is the extension of zipWithM which ignores the final result.
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a

The foldM function is analogous to foldl, except that its result is encapsulated in a monad. Note that foldM works from left-to-right over the list arguments. This could be an issue where '(>>)' and the `folded function' are not commutative.

	foldM f a1 [x1, x2, ..., xm ]

==

	do
	  a2 <- f a1 x1
	  a3 <- f a2 x2
	  ...
	  f am xm

If right-to-left evaluation is required, the input list should be reversed.

foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m ()
replicateM :: Monad m => Int -> m a -> m [a]
replicateM_ :: Monad m => Int -> m a -> m ()
Conditional execution of monadic expressions
guard :: MonadPlus m => Bool -> m ()
when :: Monad m => Bool -> m () -> m ()

Conditional execution of monadic expressions. For example,

	when debug (putStr "Debugging\n")

will output the string Debugging\n if the Boolean value debug is True, and otherwise do nothing.

unless :: Monad m => Bool -> m () -> m ()
The reverse of when.
Monadic lifting operators

The monadic lifting operators promote a function to a monad. The function arguments are scanned left to right. For example,

	liftM2 (+) [0,1] [0,2] = [0,2,1,3]
	liftM2 (+) (Just 1) Nothing = Nothing
liftM :: Monad m => (a1 -> r) -> m a1 -> m r
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
ap :: Monad m => m (a -> b) -> m a -> m b

In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.

	return f `ap` x1 `ap` ... `ap` xn

is equivalent to

	liftMn f x1 x2 ... xn
Produced by Haddock version 0.6