Control.Monad
| Copyright | (c) The University of Glasgow 2001 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | [email protected] |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Functor and monad classes
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.
Minimal complete definition
Methods
fmap :: (a -> b) -> f a -> f b Source
Using ApplicativeDo: 'fmap f as' can be understood as the do expression
do a <- as pure (f a)
with an inferred Functor constraint.
(<$) :: a -> f b -> f a infixl 4 Source
Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.
Using ApplicativeDo: 'a <$ bs' can be understood as the do expression
do bs pure a
with an inferred Functor constraint.
Instances
| Functor [] | Since: base-2.1 |
| Functor Maybe | Since: base-2.1 |
| Functor IO | Since: base-2.1 |
| Functor Par1 | Since: base-4.9.0.0 |
| Functor NonEmpty | Since: base-4.9.0.0 |
| Functor NoIO | Since: base-4.8.0.0 |
| Functor ReadP | Since: base-2.1 |
| Functor ReadPrec | Since: base-2.1 |
| Functor Down | Since: base-4.11.0.0 |
| Functor Product | Since: base-4.8.0.0 |
| Functor Sum | Since: base-4.8.0.0 |
| Functor Dual | Since: base-4.8.0.0 |
| Functor Last | Since: base-4.8.0.0 |
| Functor First | Since: base-4.8.0.0 |
| Functor STM | Since: base-4.3.0.0 |
| Functor Handler | Since: base-4.6.0.0 |
| Functor Identity | Since: base-4.8.0.0 |
| Functor ZipList | Since: base-2.1 |
| Functor ArgDescr | Since: base-4.6.0.0 |
| Functor OptDescr | Since: base-4.6.0.0 |
| Functor ArgOrder | Since: base-4.6.0.0 |
| Functor Option | Since: base-4.9.0.0 |
| Functor Last | Since: base-4.9.0.0 |
| Functor First | Since: base-4.9.0.0 |
| Functor Max | Since: base-4.9.0.0 |
| Functor Min | Since: base-4.9.0.0 |
| Functor Complex | Since: base-4.9.0.0 |
| Functor (Either a) | Since: base-3.0 |
| Functor (V1 :: Type -> Type) | Since: base-4.9.0.0 |
| Functor (U1 :: Type -> Type) | Since: base-4.9.0.0 |
| Functor ((,) a) | Since: base-2.1 |
| Functor (ST s) | Since: base-2.1 |
| Functor (Array i) | Since: base-2.1 |
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Arrow a => Functor (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow Methodsfmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 Source | |
| Monad m => Functor (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative Methodsfmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source (<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source | |
| Functor (ST s) | Since: base-2.1 |
| Functor (Arg a) | Since: base-4.9.0.0 |
| Functor f => Functor (Rec1 f) | Since: base-4.9.0.0 |
| Functor (URec Char :: Type -> Type) | Since: base-4.9.0.0 |
| Functor (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
| Functor (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
| Functor (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
| Functor (URec Word :: Type -> Type) | Since: base-4.9.0.0 |
| Functor (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
| Functor ((,,) a b) | Since: base-4.14.0.0 |
| Functor f => Functor (Alt f) | Since: base-4.8.0.0 |
| Functor f => Functor (Ap f) | Since: base-4.12.0.0 |
| Functor (Const m :: Type -> Type) | Since: base-2.1 |
| Functor m => Functor (Kleisli m a) | Since: base-4.14.0.0 |
| Arrow a => Functor (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methodsfmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source | |
| Functor ((->) r :: Type -> Type) | Since: base-2.1 |
| Functor (K1 i c :: Type -> Type) | Since: base-4.9.0.0 |
| (Functor f, Functor g) => Functor (f :+: g) | Since: base-4.9.0.0 |
| (Functor f, Functor g) => Functor (f :*: g) | Since: base-4.9.0.0 |
| Functor ((,,,) a b c) | Since: base-4.14.0.0 |
| (Functor f, Functor g) => Functor (Sum f g) | Since: base-4.9.0.0 |
| (Functor f, Functor g) => Functor (Product f g) | Since: base-4.9.0.0 |
| Functor f => Functor (M1 i c f) | Since: base-4.9.0.0 |
| (Functor f, Functor g) => Functor (f :.: g) | Since: base-4.9.0.0 |
| (Functor f, Functor g) => Functor (Compose f g) | Since: base-4.9.0.0 |
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:
- Left identity
return a >>= 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 lists, Maybe and IO defined in the Prelude satisfy these laws.
Minimal complete definition
Methods
(>>=) :: 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.
'as >>= bs' can be understood as the do expression
do a <- as bs a
(>>) :: 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.
'as >> bs' can be understood as the do expression
do as bs
Inject a value into the monadic type.
Instances
| Monad [] | Since: base-2.1 |
| Monad Maybe | Since: base-2.1 |
| Monad IO | Since: base-2.1 |
| Monad Par1 | Since: base-4.9.0.0 |
| Monad NonEmpty | Since: base-4.9.0.0 |
| Monad NoIO | Since: base-4.4.0.0 |
| Monad ReadP | Since: base-2.1 |
| Monad ReadPrec | Since: base-2.1 |
| Monad Down | Since: base-4.11.0.0 |
| Monad Product | Since: base-4.8.0.0 |
| Monad Sum | Since: base-4.8.0.0 |
| Monad Dual | Since: base-4.8.0.0 |
| Monad Last | Since: base-4.8.0.0 |
| Monad First | Since: base-4.8.0.0 |
| Monad STM | Since: base-4.3.0.0 |
| Monad Identity | Since: base-4.8.0.0 |
| Monad Option | Since: base-4.9.0.0 |
| Monad Last | Since: base-4.9.0.0 |
| Monad First | Since: base-4.9.0.0 |
| Monad Max | Since: base-4.9.0.0 |
| Monad Min | Since: base-4.9.0.0 |
| Monad Complex | Since: base-4.9.0.0 |
| Monad (Either e) | Since: base-4.4.0.0 |
| Monad (U1 :: Type -> Type) | Since: base-4.9.0.0 |
| Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
| Monad (ST s) | Since: base-2.1 |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| ArrowApply a => Monad (ArrowMonad a) | Since: base-2.1 |
Defined in 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 m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative Methods(>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b Source (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b Source return :: a -> WrappedMonad m a Source | |
| Monad (ST s) | Since: base-2.1 |
| Monad f => Monad (Rec1 f) | Since: base-4.9.0.0 |
| (Monoid a, Monoid b) => Monad ((,,) a b) | Since: base-4.14.0.0 |
| Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
| Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
| Monad m => Monad (Kleisli m a) | Since: base-4.14.0.0 |
| Monad ((->) r :: Type -> Type) | Since: base-2.1 |
| (Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
| (Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) | Since: base-4.14.0.0 |
| (Monad f, Monad g) => Monad (Product f g) | Since: base-4.9.0.0 |
| Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
class Monad m => MonadFail m 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
Since: base-4.9.0.0
Instances
| MonadFail [] | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
| MonadFail Maybe | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
| MonadFail IO | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
| MonadFail ReadP | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadP | |
| MonadFail ReadPrec | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadPrec | |
| MonadFail (ST s) | Since: base-4.11.0.0 |
| MonadFail (ST s) | Since: base-4.10 |
Defined in Control.Monad.ST.Lazy.Imp | |
| MonadFail f => MonadFail (Ap f) | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
class (Alternative m, Monad m) => MonadPlus m 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 [] | Since: base-2.1 |
| MonadPlus Maybe | Since: base-2.1 |
| MonadPlus IO | Since: base-4.9.0.0 |
| MonadPlus ReadP | Since: base-2.1 |
| MonadPlus ReadPrec | Since: base-2.1 |
| MonadPlus STM | Since: base-4.3.0.0 |
| MonadPlus Option | Since: base-4.9.0.0 |
| MonadPlus (U1 :: Type -> Type) | Since: base-4.9.0.0 |
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| (ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow Methodsmzero :: ArrowMonad a a0 Source mplus :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 Source | |
| MonadPlus f => MonadPlus (Rec1 f) | Since: base-4.9.0.0 |
| MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 |
| MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 |
| MonadPlus m => MonadPlus (Kleisli m a) | Since: base-4.14.0.0 |
| (MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) | Since: base-4.9.0.0 |
| (MonadPlus f, MonadPlus g) => MonadPlus (Product f g) | Since: base-4.9.0.0 |
| MonadPlus f => MonadPlus (M1 i c f) | Since: base-4.9.0.0 |
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 constructormis 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:
filter :: (a -> Bool) -> [a] -> [a] mfilter :: MonadPlus m => (a -> Bool) -> 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_.
mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () Source
Map each element of a structure to a monadic action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see mapM.
As of base 4.8.0.0, mapM_ is just traverse_, specialized to Monad.
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) Source
forM is mapM with its arguments flipped. For a version that ignores the results see forM_.
forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () Source
forM_ is mapM_ with its arguments flipped. For a version that doesn't ignore the results see forM.
As of base 4.8.0.0, forM_ is just for_, specialized to Monad.
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 composition of Kleisli arrows.
'(bs >=> cs) a' can be understood as the do expression
do b <- bs a cs b
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 Source
Right-to-left composition of Kleisli arrows. (>=>), with the arguments flipped.
Note how this operator resembles function composition (.):
(.) :: (b -> c) -> (a -> b) -> a -> c (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
forever :: Applicative f => f a -> f b Source
Repeat an action indefinitely.
Using ApplicativeDo: 'forever as' can be understood as the pseudo-do expression
do as as ..
with as repeating.
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 socket forkFinally (echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client = forever $ hGetLine client >>= hPutStrLn client
void :: Functor f => f a -> f () Source
void value discards or ignores the result of evaluation, such as the return value of an IO action.
Using ApplicativeDo: 'void as' can be understood as the do expression
do as pure ()
with an inferred Functor constraint.
Examples
Replace the contents of a Maybe Int with unit:
>>> void Nothing Nothing >>> void (Just 3) Just ()
Replace the contents of an Either Int Int with unit, resulting in an 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.
'join bss' can be understood as the do expression
do bs <- bss bs
Examples
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
msum :: (Foldable t, MonadPlus m) => t (m a) -> m a Source
The sum of a collection of actions, generalizing concat. As of base 4.8.0.0, msum is just asum, specialized to MonadPlus.
mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a Source
Direct MonadPlus equivalent of filter.
Examples
The filter function is just mfilter specialized to the list monad:
filter = ( mfilter :: (a -> Bool) -> [a] -> [a] )
An example using mfilter with the Maybe monad:
>>> mfilter odd (Just 1) Just 1 >>> mfilter odd (Just 2) Nothing
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 monad.
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] Source
The zipWithM function generalizes zipWith to arbitrary applicative functors.
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () Source
zipWithM_ is the extension of zipWithM which ignores the final result.
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.
Note: foldM is the same as foldlM
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 act performs the action n times, gathering the results.
Using ApplicativeDo: 'replicateM 5 as' can be understood as the do expression
do a1 <- as a2 <- as a3 <- as a4 <- as a5 <- as pure [a1,a2,a3,a4,a5]
Note the Applicative constraint.
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
Conditional failure of Alternative computations. Defined by
guard True = pure () guard False = empty
Examples
Common uses of guard include conditionally signaling an error in an error monad and conditionally rejecting the current choice in an Alternative-based parser.
As an example of signaling 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) otherwise. For example:
>>> safeDiv 4 0 Nothing >>> safeDiv 4 2 Just 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,
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 () Source
The reverse of when.
Monadic lifting operators
liftM :: Monad m => (a1 -> r) -> m a1 -> m r Source
Promote a function to a monad.
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).
ap :: Monad m => m (a -> b) -> m a -> m b Source
In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.
return f `ap` x1 `ap` ... `ap` xn
is equivalent to
liftMn f x1 x2 ... xn
Strict monadic functions
(<$!>) :: Monad m => (a -> b) -> m a -> m b infixl 4 Source
Strict version of <$>.
Since: base-4.8.0.0
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.10.2/docs/html/libraries/base-4.14.1.0/Control-Monad.html