Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
- class Applicative m => Monad m where
- class (Alternative m, Monad m) => MonadPlus m where
- (=<<) :: 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
- (>>) :: Monad m => forall a b. m a -> m b -> m b
- forever :: Applicative f => f a -> f b
- join :: Monad m => m (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 ()
- concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
- 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
- liftM' :: Monad m => (a -> b) -> m a -> m b
- liftM2' :: Monad m => (a -> b -> c) -> m a -> m b -> m c
- ap :: Monad m => m (a -> b) -> m a -> m b
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
Documentation
class Applicative m => Monad m where #
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 laws:
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 lists, Maybe
and IO
defined in the Prelude satisfy these laws.
Monad [] | |
Monad Maybe | |
Monad IO | |
Monad U1 | |
Monad Par1 | |
Monad Identity | |
Monad Min | |
Monad Max | |
Monad First | |
Monad Last | |
Monad Option | |
Monad NonEmpty | |
Monad Complex | |
Monad STM | |
Monad Dual | |
Monad Sum | |
Monad Product | |
Monad First | |
Monad Last | |
Monad Put | |
Monad Seq | |
Monad ((->) r) | |
Monad (Either e) | |
Monad f => Monad (Rec1 f) | |
Monoid a => Monad ((,) a) | |
Monad m => Monad (WrappedMonad m) | |
ArrowApply a => Monad (ArrowMonad a) | |
Monad (Proxy *) | |
Monad (State s) | |
Monad m => Monad (ListT m) | |
Monad m => Monad (MaybeT m) | |
(Monad f, Monad g) => Monad ((:*:) f g) | |
Monad f => Monad (Alt * f) | |
Monad m => Monad (ExceptT e m) | |
(Monad m, Error e) => Monad (ErrorT e m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (StateT s m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
Monad m => Monad (IdentityT * m) | |
Monad f => Monad (M1 i c f) | |
Monad m => Monad (ReaderT * r m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
class (Alternative m, Monad m) => MonadPlus m where #
Monads that also support choice and failure.
Nothing
MonadPlus [] | |
MonadPlus Maybe | |
MonadPlus IO | |
MonadPlus U1 | |
MonadPlus Option | |
MonadPlus STM | |
MonadPlus Seq | |
MonadPlus f => MonadPlus (Rec1 f) | |
(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) | |
MonadPlus (Proxy *) | |
Monad m => MonadPlus (ListT m) | |
Monad m => MonadPlus (MaybeT m) | |
(MonadPlus f, MonadPlus g) => MonadPlus ((:*:) f g) | |
MonadPlus f => MonadPlus (Alt * f) | |
(Monad m, Monoid e) => MonadPlus (ExceptT e m) | |
(Monad m, Error e) => MonadPlus (ErrorT e m) | |
MonadPlus m => MonadPlus (StateT s m) | |
MonadPlus m => MonadPlus (StateT s m) | |
(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) | |
(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) | |
MonadPlus m => MonadPlus (IdentityT * m) | |
MonadPlus f => MonadPlus (M1 i c f) | |
MonadPlus m => MonadPlus (ReaderT * r m) | |
(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right Kleisli composition of monads.
(>>) :: Monad m => forall a b. m a -> m b -> m b #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
forever :: Applicative f => f a -> f b #
repeats the action infinitely.forever
act
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.
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
mapAndUnzipM :: Applicative 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 :: 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 #
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 () #
Like foldM
, but discards the result.
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM
n actn
times,
gathering the results.
replicateM_ :: Applicative m => Int -> m a -> m () #
Like replicateM
, but discards the result.
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source #
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative
expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
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
).
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).