base-4.7.0.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad

Contents

Description

The Functor, Monad and MonadPlus classes, with some useful operations on monads.

Synopsis

Functor and monad classes

class Functor f where Source

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 satisfy these laws.

Methods

fmap ∷ (a → b) → f a → f b Source

class Monad m where Source

The Monad class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory. From the perspective of a Haskell programmer, however, it is best to think of a monad as an abstract datatype of actions. Haskell's do expressions provide a convenient syntax for writing monadic expressions.

Minimal complete definition: >>= and return.

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.

Minimal complete definition

(>>=), return

Methods

(>>=) ∷ ∀ a b. m a → (a → m b) → m b infixl 1 Source

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

(>>) ∷ ∀ a b. m a → m b → m b infixl 1 Source

Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.

return ∷ a → m a Source

Inject a value into the monadic type.

failString → m a Source

Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do expression.

Instances

class Monad m ⇒ MonadPlus m where Source

Monads that also support choice and failure.

Methods

mzero ∷ m a Source

the identity of mplus. It should also satisfy the equations

mzero >>= f  =  mzero
v >> mzero   =  mzero

mplus ∷ m a → m a → m a Source

an associative operation

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: The monad type constructor 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, for example:
 sequence  :: Monad m => [m a] -> m [a] 
 sequence_ :: Monad m => [m a] -> m () 
  • A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
 sum  :: Num a       => [a]   -> a
 msum :: MonadPlus m => [m a] -> m a

Basic Monad functions

mapMMonad m ⇒ (a → m b) → [a] → m [b] Source

mapM f is equivalent to sequence . map f.

mapM_Monad m ⇒ (a → m b) → [a] → m () Source

mapM_ f is equivalent to sequence_ . map f.

forMMonad m ⇒ [a] → (a → m b) → m [b] Source

forM is mapM with its arguments flipped

forM_Monad m ⇒ [a] → (a → m b) → m () Source

forM_ is mapM_ with its arguments flipped

sequenceMonad m ⇒ [m a] → m [a] Source

Evaluate each action in the sequence from left to right, and collect the results.

sequence_Monad m ⇒ [m a] → m () Source

Evaluate each action in the sequence from left to right, and ignore the results.

(=<<)Monad m ⇒ (a → m b) → m a → m b infixr 1 Source

Same as >>=, but with the arguments interchanged.

(>=>)Monad m ⇒ (a → m b) → (b → m c) → a → m c infixr 1 Source

Left-to-right Kleisli composition of monads.

(<=<)Monad m ⇒ (b → m c) → (a → m b) → a → m c infixr 1 Source

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped

foreverMonad m ⇒ m a → m b Source

forever act repeats the action infinitely.

voidFunctor f ⇒ f a → f () Source

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Generalisations of list functions

joinMonad m ⇒ m (m a) → m a Source

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.

msumMonadPlus m ⇒ [m a] → m a Source

This generalizes the list-based concat function.

mfilterMonadPlus m ⇒ (a → Bool) → m a → m a Source

Direct MonadPlus equivalent of filter filter = (mfilter:: (a -> Bool) -> [a] -> [a] applicable to any MonadPlus, for example mfilter odd (Just 1) == Just 1 mfilter odd (Just 2) == Nothing

filterMMonad m ⇒ (a → m Bool) → [a] → m [a] Source

This generalizes the list-based filter function.

mapAndUnzipMMonad m ⇒ (a → m (b, c)) → [a] → m ([b], [c]) Source

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.

zipWithMMonad m ⇒ (a → b → m c) → [a] → [b] → m [c] Source

The zipWithM function generalizes zipWith to arbitrary monads.

zipWithM_Monad m ⇒ (a → b → m c) → [a] → [b] → m () Source

zipWithM_ is the extension of zipWithM which ignores the final result.

foldMMonad m ⇒ (a → b → m a) → a → [b] → m a Source

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

Like foldM, but discards the result.

replicateMMonad m ⇒ Int → m a → m [a] Source

replicateM n act performs the action n times, gathering the results.

replicateM_Monad m ⇒ Int → m a → m () Source

Like replicateM, but discards the result.

Conditional execution of monadic expressions

guardMonadPlus m ⇒ Bool → m () Source

guard b is return () if b is True, and mzero if b is False.

whenMonad m ⇒ Bool → m () → m () Source

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.

unlessMonad m ⇒ Bool → m () → m () Source

The reverse of when.

Monadic lifting operators

liftMMonad m ⇒ (a1 → r) → m a1 → m r Source

Promote a function to a monad.

liftM2Monad m ⇒ (a1 → a2 → r) → m a1 → m a2 → m r Source

Promote a function to a monad, scanning the monadic arguments from left to right. For example,

   liftM2 (+) [0,1] [0,2] = [0,2,1,3]
   liftM2 (+) (Just 1) Nothing = Nothing

liftM3Monad m ⇒ (a1 → a2 → a3 → r) → m a1 → m a2 → m a3 → m r Source

Promote a function to a monad, scanning the monadic arguments from left to right (cf. liftM2).

liftM4Monad m ⇒ (a1 → a2 → a3 → a4 → r) → m a1 → m a2 → m a3 → m a4 → m r Source

Promote a function to a monad, scanning the monadic arguments from left to right (cf. liftM2).

liftM5Monad m ⇒ (a1 → a2 → a3 → a4 → a5 → r) → m a1 → m a2 → m a3 → m a4 → m a5 → m r Source

Promote a function to a monad, scanning the monadic arguments from left to right (cf. liftM2).

apMonad m ⇒ m (a → b) → m a → m b Source

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