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 |
- class Functor f where
- class Applicative m => Monad m where
- class (Alternative m, Monad m) => MonadPlus m 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 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.
class Applicative m => 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.
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.
(>>=) :: forall 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.
(>>) :: forall 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.
Inject a value into the monadic type.
fail :: String -> 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.
As part of the MonadFail proposal (MFP), this function is moved
to its own class MonadFail
(see Control.Monad.Fail for more
details). The definition here will be removed in a future
release.
Monad [] # | |
Monad Maybe # | |
Monad IO # | |
Monad U1 # | |
Monad Par1 # | |
Monad ReadP # | |
Monad ReadPrec # | |
Monad Last # | |
Monad First # | |
Monad Product # | |
Monad Sum # | |
Monad Dual # | |
Monad STM # | |
Monad Complex # | |
Monad NonEmpty # | |
Monad Option # | |
Monad Last # | |
Monad First # | |
Monad Max # | |
Monad Min # | |
Monad Identity # | |
Monad ((->) r) # | |
Monad (Either e) # | |
Monad f => Monad (Rec1 f) # | |
Monoid a => Monad ((,) a) # | |
Monad (ST s) # | |
Monad (Proxy *) # | |
ArrowApply a => Monad (ArrowMonad a) # | |
Monad m => Monad (WrappedMonad m) # | |
Monad (ST s) # | |
(Monad f, Monad g) => Monad ((:*:) f g) # | |
Monad f => Monad (Alt * f) # | |
Monad f => Monad (M1 i c f) # | |
(Monad f, Monad g) => Monad (Product * f g) # | |
class (Alternative m, Monad m) => MonadPlus m where Source #
Monads that also support choice and failure.
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
MonadPlus [] # | |
MonadPlus Maybe # | |
MonadPlus IO # | |
MonadPlus U1 # | |
MonadPlus ReadP # | |
MonadPlus ReadPrec # | |
MonadPlus STM # | |
MonadPlus Option # | |
MonadPlus f => MonadPlus (Rec1 f) # | |
MonadPlus (Proxy *) # | |
(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) # | |
(MonadPlus f, MonadPlus g) => MonadPlus ((:*:) f g) # | |
MonadPlus f => MonadPlus (Alt * f) # | |
MonadPlus f => MonadPlus (M1 i c f) # | |
(MonadPlus f, MonadPlus g) => MonadPlus (Product * f g) # | |
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 constructorm
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
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_
.
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_
.
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
.
As of base 4.8.0.0, sequence_
is just sequenceA_
, specialized
to Monad
.
(=<<) :: 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.
forever :: Applicative f => f a -> f b Source #
repeats the action infinitely.forever
act
void :: Functor f => f a -> f () Source #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit,
resulting in an Either
Int
Int
:Either
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.
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] Source #
This generalizes the list-based filter
function.
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-transforming 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 #
performs the action replicateM
n actn
times,
gathering the results.
replicateM_ :: Applicative m => Int -> m a -> m () Source #
Like replicateM
, but discards the result.
Conditional execution of monadic expressions
guard :: Alternative f => Bool -> f () Source #
when :: Applicative f => Bool -> f () -> f () Source #
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.
Monadic lifting operators
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. 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 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
).