All rights reserved.
Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met:
- Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS AS IS AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
monad-param Maintainer : Edward Kmett ekmett@gmail.com Bind.Marshal Maintainer : Corey O'Connor coreyoconnor@gmail.com Stability : experimental Portability : non-portable (requires the kitchen sink)
Implements a notion of parameterized monad by varying the monad itself, this lets us avoid having
to carry a parameter around for monads that do not need it, and we can rederive the normal notion
of a parameterized monad from this variation for those that do. The signature of >>=
costs us
type inference for the types of return
and mzero
, so we restore that by defining return
as
the unit of the Identity
monad and mzero
as the unit of the trivial bottom monad, and
appealing to the monad laws to allow these to combine with all other monads satisfying the monad
laws through >>=
This imports and defines the correct instances for a good portion of the monads-tf
, primarily
because it is so awkward to import them all otherwise due to the fact that most of them re-export
the Control.Monad.Monad
syntax. Does not export Control.Monad.ST or Control.Monad.Writer
since it is unclear if you want strict or lazy versions in scope
- class Return m where
- returnM :: a -> m a
- class Fail m where
- class (Functor m, Functor m', Functor m'') => Bind m m' m'' | m m' -> m'' where
- (=<<) :: Bind m m' m'' => (a -> m' b) -> m a -> m'' b
- class MPlus m m' m'' | m m' -> m'' where
- mplus :: m a -> m' a -> m'' a
- class MonadZero m where
- mzeroM :: m a
- data MZero a
- class (Fail m, Return m, Bind m m m) => Monad m
- class (MPlus m m m, MonadZero m) => MonadPlus m
- class Go n m where
- go :: n a -> m a
- return :: a -> Identity a
- mzero :: MZero a
- module Control.Concurrent.STM
- module Control.Monad.Cont
- module Control.Monad.Cont.Class
- module Control.Monad.Error
- module Control.Monad.Error.Class
- module Control.Monad.Fix
- module Control.Monad.Identity
- module Control.Monad.List
- module Control.Monad.Reader
- module Control.Monad.State
- module Control.Monad.Writer.Class
- mapM :: Monad m => (a -> m b) -> [a] -> m [b]
- mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
- forM :: Monad m => [a] -> (a -> m b) -> m [b]
- forM_ :: Monad m => [a] -> (a -> m b) -> m ()
- sequence :: Monad m => [m a] -> m [a]
- sequence_ :: Monad m => [m a] -> m ()
- 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
Rebound Monad
The traditional return
, note this probably has lost its type inference where you want to use it.
Return [] | |
Return IO | |
Return STM | |
Return Maybe | |
Return Identity | |
Return MZero | |
Return (ST s) | |
Return (ST s) | |
Return (Cont r) | |
Monad m => Return (ListT m) | |
Return (Reader e) | |
Return (State s) | |
Monoid w => Return (Writer w) | |
Monoid w => Return (Writer w) | |
Monad m => Return (ContT r m) | |
(Monad m, Error e) => Return (ErrorT e m) | |
Monad m => Return (ReaderT e m) | |
Monad m => Return (StateT s m) | |
(Monad m, Monoid w) => Return (WriterT w m) | |
(Monad m, Monoid w) => Return (WriterT w m) | |
m ~ D0 => Return (StaticMemAction tag m) | The static memory action monad is constructed via the parameterized monad Return and Bind instances. |
BufferDelegate bd => Return (DynAction Sealed Sealed Sealed bd tag) |
Restrict the cases where we allow pattern matching to fail
. You have to explicitly supply this for your Monad
Fail [] | |
Fail IO | |
Fail STM | |
Fail Maybe | |
Fail (ST s) | |
Fail (ST s) | |
Fail (Cont r) | |
Monad m => Fail (ListT m) | |
Fail (Reader e) | |
Fail (State s) | |
Monoid w => Fail (Writer w) | |
Monoid w => Fail (Writer w) | |
Monad m => Fail (ContT r m) | |
(Monad m, Error e) => Fail (ErrorT e m) | |
Monad m => Fail (ReaderT e m) | |
Monad m => Fail (StateT s m) | |
(Monad m, Monoid w) => Fail (WriterT w m) | |
(Monad m, Monoid w) => Fail (WriterT w m) | |
Fail (StaticMemAction tag m) | possibly-failing pattern matches require a Fail instance. |
BufferDelegate bd => Fail (DynAction Sealed (Open post_sa_0) (Open post_s_0) bd tag) | |
BufferDelegate bd => Fail (DynAction Sealed Sealed Sealed bd tag) |
class (Functor m, Functor m', Functor m'') => Bind m m' m'' | m m' -> m'' whereSource
Implement parameterized monads like Oleg's restricted monads, but vary the monad itself rather than restrict its parameters
Bind [] [] [] | |
Bind [] Maybe [] | |
Bind IO IO IO | |
Bind IO STM IO | |
Functor a => Bind a Identity a | |
Bind STM IO IO | |
Bind STM STM STM | |
Bind Maybe [] [] | |
Bind Maybe Maybe Maybe | |
Functor a => Bind Identity a a | |
Bind Identity Identity Identity | |
Bind Identity MZero MZero | |
Functor a => Bind MZero a MZero | |
Bind MZero Identity MZero | |
Bind MZero MZero MZero | |
Bind [] IO (ListT IO) | |
Bind (ST s) (ST s) (ST s) | |
Bind (ST s) (ST s) (ST s) | |
Bind (Cont r) (Cont r) (Cont r) | |
(Functor m, Monad m) => Bind (ListT m) (ListT m) (ListT m) | |
Bind (Reader e) (Reader e) (Reader e) | |
Bind (State s) (State s) (State s) | |
Monoid w => Bind (Writer w) (Writer w) (Writer w) | |
Monoid w => Bind (Writer w) (Writer w) (Writer w) | |
(Functor m, Monad m) => Bind (ContT r m) (ContT r m) (ContT r m) | |
(Functor m, Monad m, Error e) => Bind (ErrorT e m) (ErrorT e m) (ErrorT e m) | |
(Functor m, Monad m) => Bind (ReaderT e m) (ReaderT e m) (ReaderT e m) | |
(Functor m, Monad m) => Bind (StateT s m) (StateT s m) (StateT s m) | |
(Functor m, Monad m, Monoid w) => Bind (WriterT w m) (WriterT w m) (WriterT w m) | |
(Functor m, Monad m, Monoid w) => Bind (WriterT w m) (WriterT w m) (WriterT w m) | |
(size_2 ~ Add size_0 size_1, buffer_0 ~ buffer_1, buffer_0 ~ buffer_2) => Bind (StaticMemAction buffer_0 size_0) (StaticMemAction buffer_1 size_1) (StaticMemAction buffer_2 size_2) | The static memory action monad is constructed via the parameterized monad Return and Bind instances. |
(pre_s_2 ~ Add static_size pre_s_1, post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, tag_0 ~ tag_1, tag_1 ~ tag_2, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (StaticMemAction tag_0 static_size) (DynAction (Open pre_s_1) (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ Add static_size pre_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (StaticMemAction tag_0 static_size) (DynAction (Open pre_s_1) Sealed Sealed bd_1 tag_1) (DynAction (Open pre_s_2) Sealed Sealed bd_1 tag_1) | |
(pre_s_2 ~ static_size, post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (StaticMemAction tag_0 static_size) (DynAction Sealed (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ static_size, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (StaticMemAction tag_0 static_size) (DynAction Sealed Sealed Sealed bd_1 tag_1) (DynAction (Open pre_s_2) Sealed Sealed bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_sa_2 ~ Add post_sa_0 static_size, post_s_0 ~ post_s_2, tag_0 ~ tag_1, tag_1 ~ tag_2, bd_2 ~ bd_0, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (StaticMemAction tag_1 static_size) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_sa_2 ~ static_size, tag_0 ~ tag_1, tag_1 ~ tag_2, bd_2 ~ bd_0, Nat post_s_2, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) Sealed Sealed bd_0 tag_0) (StaticMemAction tag_1 static_size) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(post_sa_2 ~ Add post_sa_0 static_size, post_s_0 ~ post_s_2, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, BufferDelegate bd_2) => Bind (DynAction Sealed (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (StaticMemAction tag_1 static_size) (DynAction Sealed (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(post_sa_2 ~ static_size, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, Nat post_s_2, BufferDelegate bd_2) => Bind (DynAction Sealed Sealed Sealed bd_0 tag_0) (StaticMemAction tag_1 static_size) (DynAction Sealed (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, post_s_0 ~ Add post_sa_0 pre_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction (Open pre_s_1) (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, Nat pre_s_1, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) Sealed Sealed bd_0 tag_0) (DynAction (Open pre_s_1) (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_s_0 ~ Add post_sa_0 pre_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction (Open pre_s_1) Sealed Sealed bd_1 tag_1) (DynAction (Open pre_s_2) Sealed Sealed bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, Nat pre_s_1, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) Sealed Sealed bd_0 tag_0) (DynAction (Open pre_s_1) Sealed Sealed bd_1 tag_1) (DynAction (Open pre_s_2) Sealed Sealed bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, post_s_0 ~ post_sa_0, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction Sealed (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction (Open pre_s_0) Sealed Sealed bd_0 tag_0) (DynAction Sealed (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction (Open pre_s_2) (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, post_s_0 ~ post_sa_0, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1) => Bind (DynAction (Open pre_s_0) (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction Sealed Sealed Sealed bd_1 tag_1) (DynAction (Open pre_s_2) Sealed Sealed bd_2 tag_2) | |
(pre_s_2 ~ pre_s_0, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1) => Bind (DynAction (Open pre_s_0) Sealed Sealed bd_0 tag_0) (DynAction Sealed Sealed Sealed bd_1 tag_1) (DynAction (Open pre_s_2) Sealed Sealed bd_2 tag_2) | |
(post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, post_s_0 ~ Add post_sa_0 pre_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction Sealed (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction (Open pre_s_1) (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction Sealed (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(post_s_0 ~ Add post_sa_0 pre_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction Sealed (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction (Open pre_s_1) Sealed Sealed bd_1 tag_1) (DynAction Sealed Sealed Sealed bd_2 tag_2) | |
(post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, post_s_0 ~ post_sa_0, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction Sealed (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction Sealed (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction Sealed (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(post_s_0 ~ post_sa_0, bd_2 ~ bd_0, bd_2 ~ bd_1, tag_2 ~ tag_0, tag_2 ~ tag_1, BufferDelegate bd_2) => Bind (DynAction Sealed (Open post_sa_0) (Open post_s_0) bd_0 tag_0) (DynAction Sealed Sealed Sealed bd_1 tag_1) (DynAction Sealed Sealed Sealed bd_2 tag_2) | |
(post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, Nat pre_s_1, BufferDelegate bd_2) => Bind (DynAction Sealed Sealed Sealed bd_0 tag_0) (DynAction (Open pre_s_1) (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction Sealed (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, Nat pre_s_1, BufferDelegate bd_2) => Bind (DynAction Sealed Sealed Sealed bd_0 tag_0) (DynAction (Open pre_s_1) Sealed Sealed bd_1 tag_1) (DynAction Sealed Sealed Sealed bd_2 tag_2) | |
(post_sa_2 ~ post_sa_1, post_s_2 ~ post_s_1, tag_2 ~ tag_0, tag_2 ~ tag_1, bd_2 ~ bd_0, bd_2 ~ bd_1, BufferDelegate bd_2) => Bind (DynAction Sealed Sealed Sealed bd_0 tag_0) (DynAction Sealed (Open post_sa_1) (Open post_s_1) bd_1 tag_1) (DynAction Sealed (Open post_sa_2) (Open post_s_2) bd_2 tag_2) | |
(bd_2 ~ bd_0, bd_2 ~ bd_1, tag_2 ~ tag_0, tag_2 ~ tag_1) => Bind (DynAction Sealed Sealed Sealed bd_0 tag_0) (DynAction Sealed Sealed Sealed bd_1 tag_1) (DynAction Sealed Sealed Sealed bd_2 tag_2) |
Rebound MonadPlus
Traditional Control.Monad.mzero
, note this probably has lost its type inference.
You probably want mzero
.
A bottom monad
Same trick using with Identity
to build a canonical return
, here we exploit the MonadPlus
laws to make a canonical mzero
. Has no members except bottom.
Functor MZero | its trivial to map a function over nothing |
Return MZero | |
MonadZero a => Go MZero a | |
MPlus a MZero a | |
MPlus MZero a a | We we losing type inference for MonadZero anyways, plumb around the special cases |
MPlus MZero MZero MZero | |
Bind Identity MZero MZero | |
Functor a => Bind MZero a MZero | |
Bind MZero Identity MZero | |
Bind MZero MZero MZero |
Convenient class aliases
class (Fail m, Return m, Bind m m m) => Monad m Source
When a parameterized monad can be used without varying its parameter, we can get the ease of use of the original Monad
class.
class (MPlus m m m, MonadZero m) => MonadPlus m Source
Class alias to get back an approximation of the original, easy-to-specify MonadPlus
class where available
Traditional interfaces
Export common monads in this sugar
module Control.Concurrent.STM
module Control.Monad.Cont
module Control.Monad.Cont.Class
module Control.Monad.Error
module Control.Monad.Error.Class
module Control.Monad.Fix
module Control.Monad.Identity
module Control.Monad.List
module Control.Monad.Reader
module Control.Monad.State
module Control.Monad.Writer.Class
sequence :: Monad m => [m a] -> m [a]
Evaluate each action in the sequence from left to right, and collect the results.
sequence_ :: Monad m => [m a] -> m ()
Evaluate each action in the sequence from left to right, and ignore the results.
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.
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.
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.
replicateM :: Monad m => Int -> m a -> m [a]
performs the action replicateM
n actn
times,
gathering the results.
replicateM_ :: Monad m => Int -> m a -> m ()
Like replicateM
, but discards the result.
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.
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
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
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
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
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).