Portability | non-portable (requires the kitchen sink) |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
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 >>=
Caveat: Do-notation works in a recent GHC, see also http:hackage.haskell.orgtracghcticket1537
This imports and defines the correct instances for a good portion of the MTL
, 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) |
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) |
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
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 | it's 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 | |
Functor a => Bind a 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
).