| Copyright | (c) The University of Glasgow 2001 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
GHC.Internal.Control.Monad
Synopsis
- class Functor (f :: Type -> Type) where
- class Applicative m => Monad (m :: Type -> Type) where
- class Monad m => MonadFail (m :: Type -> Type) where
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- forever :: Applicative f => f a -> f b
- void :: Functor f => f a -> f ()
- join :: Monad m => m (m a) -> m a
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- replicateM_ :: Applicative m => Int -> m a -> m ()
- guard :: Alternative f => Bool -> f ()
- when :: Applicative f => Bool -> f () -> f ()
- unless :: Applicative f => Bool -> f () -> f ()
- 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
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
Functor and monad classes
class Functor (f :: Type -> Type) where Source #
A type f is a Functor if it provides a function fmap which, given any types a and b
lets you apply any function from (a -> b) to turn an f a into an f b, preserving the
structure of f. Furthermore f needs to adhere to the following:
Note, that the second law follows from the free theorem of the type fmap and
the first law, so you need only check that the former condition holds.
See these articles by School of Haskell or
David Luposchainsky
for an explanation.
Minimal complete definition
Methods
fmap :: (a -> b) -> f a -> f b Source #
fmap is used to apply a function of type (a -> b) to a value of type f a,
 where f is a functor, to produce a value of type f b.
 Note that for any type constructor with more than one parameter (e.g., Either),
 only the last type parameter can be modified with fmap (e.g., b in `Either a b`).
Some type constructors with two parameters or more have a Bifunctor
Examples
Convert from a Maybe IntMaybe String
 using show:
>>>fmap show NothingNothing>>>fmap show (Just 3)Just "3"
Convert from an Either Int IntEither Int String using show:
>>>fmap show (Left 17)Left 17>>>fmap show (Right 17)Right "17"
Double each element of a list:
>>>fmap (*2) [1,2,3][2,4,6]
Apply even to the second element of a pair:
>>>fmap even (2,2)(2,True)
It may seem surprising that the function is only applied to the last element of the tuple
 compared to the list example above which applies it to every element in the list.
 To understand, remember that tuples are type constructors with multiple type parameters:
 a tuple of 3 elements (a,b,c) can also be written (,,) a b c and its Functor instance
 is defined for Functor ((,,) a b) (i.e., only the third parameter is free to be mapped over
 with fmap).
It explains why fmap can be used with tuples containing values of different types as in the
 following example:
>>>fmap even ("hello", 1.0, 4)("hello",1.0,True)
Instances
| Functor NonEmpty Source # | Since: base-4.9.0.0 | 
| Functor STM Source # | Since: base-4.3.0.0 | 
| Functor Handler Source # | Since: base-4.6.0.0 | 
| Functor Identity Source # | Since: base-4.8.0.0 | 
| Functor First Source # | Since: base-4.8.0.0 | 
| Functor Last Source # | Since: base-4.8.0.0 | 
| Functor Down Source # | Since: base-4.11.0.0 | 
| Functor Dual Source # | Since: base-4.8.0.0 | 
| Functor Product Source # | Since: base-4.8.0.0 | 
| Functor Sum Source # | Since: base-4.8.0.0 | 
| Functor ZipList Source # | Since: base-2.1 | 
| Functor NoIO Source # | Since: base-4.8.0.0 | 
| Functor Par1 Source # | Since: base-4.9.0.0 | 
| Functor ReadP Source # | Since: base-2.1 | 
| Functor ReadPrec Source # | Since: base-2.1 | 
| Functor IO Source # | Since: base-2.1 | 
| Functor Maybe Source # | Since: base-2.1 | 
| Functor Solo Source # | Since: base-4.15 | 
| Functor [] Source # | Since: base-2.1 | 
| Functor (Array i) Source # | Since: base-2.1 | 
| Arrow a => Functor (ArrowMonad a) Source # | Since: base-4.6.0.0 | 
| Defined in GHC.Internal.Control.Arrow Methods fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source # (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 Source # | |
| Functor (ST s) Source # | Since: base-2.1 | 
| Functor (Either a) Source # | Since: base-3.0 | 
| Functor (StateL s) Source # | Since: base-4.0 | 
| Functor (StateR s) Source # | Since: base-4.0 | 
| Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | 
| Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (ST s) Source # | Since: base-2.1 | 
| Functor ((,) a) Source # | Since: base-2.1 | 
| Functor m => Functor (Kleisli m a) Source # | Since: base-4.14.0.0 | 
| Functor (Const m :: Type -> Type) Source # | Since: base-2.1 | 
| Monad m => Functor (StateT s m) Source # | Since: base-4.18.0.0 | 
| Functor f => Functor (Ap f) Source # | Since: base-4.12.0.0 | 
| Functor f => Functor (Alt f) Source # | Since: base-4.8.0.0 | 
| (Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | Since: base-4.17.0.0 | 
| Defined in GHC.Internal.Generics Methods fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |
| Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 | 
| Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor ((,,) a b) Source # | Since: base-4.14.0.0 | 
| (Functor f, Functor g) => Functor (f :*: g) Source # | Since: base-4.9.0.0 | 
| (Functor f, Functor g) => Functor (f :+: g) Source # | Since: base-4.9.0.0 | 
| Functor (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Functor ((,,,) a b c) Source # | Since: base-4.14.0.0 | 
| Functor ((->) r) Source # | Since: base-2.1 | 
| (Functor f, Functor g) => Functor (f :.: g) Source # | Since: base-4.9.0.0 | 
| Functor f => Functor (M1 i c f) Source # | Since: base-4.9.0.0 | 
| Functor ((,,,,) a b c d) Source # | Since: base-4.18.0.0 | 
| Functor ((,,,,,) a b c d e) Source # | Since: base-4.18.0.0 | 
| Functor ((,,,,,,) a b c d e f) Source # | Since: base-4.18.0.0 | 
class Applicative m => Monad (m :: Type -> Type) 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.
Instances of Monad should satisfy the following:
- Left identity
- returna- >>=k = k a
- Right identity
- m- >>=- return= m
- Associativity
- m- >>=(\x -> k x- >>=h) = (m- >>=k)- >>=h
Furthermore, the Monad and Applicative operations should relate as follows:
The above laws imply:
and that pure and (<*>) satisfy the applicative functor laws.
The instances of Monad for List, Maybe and IO
defined in the Prelude satisfy these laws.
Minimal complete definition
Methods
(>>=) :: 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.
'as ' can be understood as the >>= bsdo expression
do a <- as bs a
An alternative name for this function is 'bind', but some people may refer to it as 'flatMap', which results from it being equivialent to
\x f ->join(fmapf x) :: Monad m => m a -> (a -> m b) -> m b
which can be seen as mapping a value with
 Monad m => m a -> m (m b) and then 'flattening' m (m b) to m b using join.
(>>) :: 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.
'as ' can be understood as the >> bsdo expression
do as bs
or in terms of (>>=)
as >>= const bs
Inject a value into the monadic type.
 This function should not be different from its default implementation
 as pure. The justification for the existence of this function is
 merely historic.
Instances
| Monad NonEmpty Source # | Since: base-4.9.0.0 | 
| Monad STM Source # | Since: base-4.3.0.0 | 
| Monad Identity Source # | Since: base-4.8.0.0 | 
| Monad First Source # | Since: base-4.8.0.0 | 
| Monad Last Source # | Since: base-4.8.0.0 | 
| Monad Down Source # | Since: base-4.11.0.0 | 
| Monad Dual Source # | Since: base-4.8.0.0 | 
| Monad Product Source # | Since: base-4.8.0.0 | 
| Monad Sum Source # | Since: base-4.8.0.0 | 
| Monad NoIO Source # | Since: base-4.4.0.0 | 
| Monad Par1 Source # | Since: base-4.9.0.0 | 
| Monad ReadP Source # | Since: base-2.1 | 
| Monad ReadPrec Source # | Since: base-2.1 | 
| Monad IO Source # | Since: base-2.1 | 
| Monad Maybe Source # | Since: base-2.1 | 
| Monad Solo Source # | Since: base-4.15 | 
| Monad [] Source # | Since: base-2.1 | 
| ArrowApply a => Monad (ArrowMonad a) Source # | Since: base-2.1 | 
| Defined in GHC.Internal.Control.Arrow Methods (>>=) :: ArrowMonad a a0 -> (a0 -> ArrowMonad a b) -> ArrowMonad a b Source # (>>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b Source # return :: a0 -> ArrowMonad a a0 Source # | |
| Monad (ST s) Source # | Since: base-2.1 | 
| Monad (Either e) Source # | Since: base-4.4.0.0 | 
| Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | 
| Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Monad (ST s) Source # | Since: base-2.1 | 
| Monoid a => Monad ((,) a) Source # | Since: base-4.9.0.0 | 
| Monad m => Monad (Kleisli m a) Source # | Since: base-4.14.0.0 | 
| Monad m => Monad (StateT s m) Source # | Since: base-4.18.0.0 | 
| Monad f => Monad (Ap f) Source # | Since: base-4.12.0.0 | 
| Monad f => Monad (Alt f) Source # | Since: base-4.8.0.0 | 
| Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 | 
| (Monoid a, Monoid b) => Monad ((,,) a b) Source # | Since: base-4.14.0.0 | 
| (Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 | 
| (Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) Source # | Since: base-4.14.0.0 | 
| Monad ((->) r) Source # | Since: base-2.1 | 
| Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 | 
class Monad m => MonadFail (m :: Type -> Type) where Source #
When a value is bound in do-notation, the pattern on the left
 hand side of <- might not match. In this case, this class
 provides a function to recover.
A Monad without a MonadFail instance may only be used in conjunction
 with pattern that always match, such as newtypes, tuples, data types with
 only a single data constructor, and irrefutable patterns (~pat).
Instances of MonadFail should satisfy the following law: fail s should
 be a left zero for >>=,
fail s >>= f = fail s
If your Monad is also MonadPlus, a popular definition is
fail _ = mzero
fail s should be an action that runs in the monad itself, not an
 exception (except in instances of MonadIO).  In particular,
 fail should not be implemented in terms of error.
Since: base-4.9.0.0
Instances
| MonadFail ReadP Source # | Since: base-4.9.0.0 | 
| MonadFail ReadPrec Source # | Since: base-4.9.0.0 | 
| MonadFail IO Source # | Since: base-4.9.0.0 | 
| MonadFail Maybe Source # | Since: base-4.9.0.0 | 
| MonadFail [] Source # | Since: base-4.9.0.0 | 
| Defined in GHC.Internal.Control.Monad.Fail | |
| MonadFail f => MonadFail (Ap f) Source # | Since: base-4.12.0.0 | 
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where Source #
Monads that also support choice and failure.
Minimal complete definition
Nothing
Methods
The identity of mplus.  It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
mplus :: m a -> m a -> m a Source #
An associative operation. The default definition is
mplus = (<|>)
Instances
| MonadPlus STM Source # | Takes the first non- Since: base-4.3.0.0 | 
| MonadPlus ReadP Source # | Since: base-2.1 | 
| MonadPlus ReadPrec Source # | Since: base-2.1 | 
| MonadPlus IO Source # | Takes the first non-throwing  Since: base-4.9.0.0 | 
| MonadPlus Maybe Source # | Picks the leftmost  Since: base-2.1 | 
| MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | 
| (ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) Source # | Since: base-4.6.0.0 | 
| Defined in GHC.Internal.Control.Arrow Methods mzero :: ArrowMonad a a0 Source # mplus :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 Source # | |
| MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| MonadPlus (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| MonadPlus m => MonadPlus (Kleisli m a) Source # | Since: base-4.14.0.0 | 
| MonadPlus f => MonadPlus (Ap f) Source # | Since: base-4.12.0.0 | 
| MonadPlus f => MonadPlus (Alt f) Source # | Since: base-4.8.0.0 | 
| MonadPlus f => MonadPlus (Rec1 f) Source # | Since: base-4.9.0.0 | 
| (MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source # | Since: base-4.9.0.0 | 
| MonadPlus f => MonadPlus (M1 i c f) Source # | Since: base-4.9.0.0 | 
Functions
Naming conventions
Basic Monad functions
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) Source #
Map each element of a structure to a monadic action, evaluate
 these actions from left to right, and collect the results. For
 a version that ignores the results see mapM_.
Examples
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) Source #
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) Source #
Evaluate each monadic action in the structure from left to
 right, and collect the results. For a version that ignores the
 results see sequence_.
Examples
Basic usage:
The first two examples are instances where the input and
 and output of sequence are isomorphic.
>>>sequence $ Right [1,2,3,4][Right 1,Right 2,Right 3,Right 4]
>>>sequence $ [Right 1,Right 2,Right 3,Right 4]Right [1,2,3,4]
The following examples demonstrate short circuit behavior
 for sequence.
>>>sequence $ Left [1,2,3,4]Left [1,2,3,4]
>>>sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]Left 0
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () Source #
Evaluate each monadic action in the structure from left to right,
 and ignore the results.  For a version that doesn't ignore the
 results see sequence.
sequence_ is just like sequenceA_, but specialised to monadic
 actions.
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 Source #
Same as >>=, but with the arguments interchanged.
as >>= f == f =<< as
forever :: Applicative f => f a -> f b Source #
Repeat an action indefinitely.
Examples
A common use of forever is to process input from network sockets,
 Handles, and channels
 (e.g. MVar and
 Chan).
For example, here is how we might implement an echo
 server, using
 forever both to listen for client connections on a network socket
 and to echo client input on client connection handles:
echoServer :: Socket -> IO () echoServer socket =forever$ do client <- accept socketforkFinally(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever$ hGetLine client >>= hPutStrLn client
Note that "forever" isn't necessarily non-terminating.
 If the action is in a MonadPlusforevermzero, effectively short-circuiting its caller.
void :: Functor f => f a -> f () Source #
void valueIO action.
Examples
Replace the contents of a Maybe Int
>>>void NothingNothing
>>>void (Just 3)Just ()
Replace the contents of an Either Int IntEither Int ()
>>>void (Left 8675309)Left 8675309
>>>void (Right 8675309)Right ()
Replace every element of a list with unit:
>>>void [1,2,3][(),(),()]
Replace the second element of a pair with unit:
>>>void (1,2)(1,())
Discard the result of an IO action:
>>>mapM print [1,2]1 2 [(),()]
>>>void $ mapM print [1,2]1 2
Generalisations of list functions
join :: Monad 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.
'join bssdo expression
do bs <- bss bs
Examples
>>>join [[1, 2, 3], [4, 5, 6], [7, 8, 9]][1,2,3,4,5,6,7,8,9]
>>>join (Just (Just 3))Just 3
A common use of join is to run an IO computation returned from
 an STM transaction, since STM transactions
 can't perform IO directly. Recall that
atomically :: STM a -> IO a
is used to run STM transactions atomically. So, by
 specializing the types of atomically and join to
atomically:: STM (IO b) -> IO (IO b)join:: IO (IO b) -> IO b
we can compose them as
join.atomically:: STM (IO b) -> IO b
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] Source #
This generalizes the list-based filter function.
runIdentity (filterM (Identity . p) xs) == filter p xs
Examples
>>>filterM (\x -> doputStrLn ("Keep: " ++ show x ++ "?") answer <- getLine pure (answer == "y")) [1, 2, 3] Keep: 1? y Keep: 2? n Keep: 3? y [1,3]
>>>filterM (\x -> doputStr (show x) x' <- readLn pure (x == x')) [1, 2, 3] 12 22 33 [2,3]
mapAndUnzipM :: Applicative 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 monad.
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] Source #
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () Source #
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b 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_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () Source #
Like foldM, but discards the result.
replicateM :: Applicative m => Int -> m a -> m [a] Source #
replicateM n actact n times,
 and then returns the list of results.
replicateM n (pure x) == replicate n xExamples
>>>replicateM 3 getLinehi heya hiya ["hi","heya","hiya"]
>>>import Control.Monad.State>>>runState (replicateM 3 $ state $ \s -> (s, s + 1)) 1([1,2,3],4)
replicateM_ :: Applicative m => Int -> m a -> m () Source #
Conditional execution of monadic expressions
guard :: Alternative f => Bool -> f () Source #
Conditional failure of Alternative computations. Defined by
guard True =pure() guard False =empty
Examples
Common uses of guard include conditionally signalling an error in
 an error monad and conditionally rejecting the current choice in an
 Alternative-based parser.
As an example of signalling an error in the error monad Maybe,
 consider a safe division function safeDiv x y that returns
 Nothing when the denominator y is zero and Just (x `div`
 y)
>>>safeDiv 4 0Nothing
>>>safeDiv 4 2Just 2
A definition of safeDiv using guards, but not guard:
safeDiv :: Int -> Int -> Maybe Int
safeDiv x y | y /= 0    = Just (x `div` y)
            | otherwise = Nothing
A definition of safeDiv using guard and Monad do-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
when :: Applicative f => Bool -> f () -> f () Source #
Conditional execution of Applicative expressions. For example,
Examples
when debug (putStrLn "Debugging")
will output the string Debugging if the Boolean value debug
 is True, and otherwise do nothing.
>>>putStr "pi:" >> when False (print 3.14159)pi:
unless :: Applicative f => Bool -> f () -> f () Source #
The reverse of when.
Examples
>>>do x <- getLineunless (x == "hi") (putStrLn "hi!") comingupwithexamplesisdifficult hi!
>>>unless (pi > exp 1) NothingJust ()
Monadic lifting operators
liftM :: Monad m => (a1 -> r) -> m a1 -> m r Source #
Promote a function to a monad.
 This is equivalent to fmap but specialised to Monads.
liftM2 :: Monad 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.
Examples
>>>liftM2 (+) [0,1] [0,2][0,2,1,3]
>>>liftM2 (+) (Just 1) NothingNothing
>>>liftM2 (+) (+ 3) (* 2) 518
liftM3 :: Monad 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).
liftM4 :: Monad 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).
liftM5 :: Monad 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).