Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- guard :: Alternative f => Bool -> f ()
- join :: Monad m => m (m a) -> m a
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Monad m => MonadFail (m :: Type -> Type) where
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- unless :: Applicative f => Bool -> f () -> f ()
- replicateM_ :: Applicative m => Int -> m a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- forever :: Applicative f => f a -> f b
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- void :: Functor f => f a -> f ()
- ap :: Monad m => m (a -> b) -> m a -> m b
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- when :: Applicative f => Bool -> f () -> f ()
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- class Applicative m => Monad (m :: Type -> Type)
- class Monad m => MonadFail (m :: Type -> Type)
- fail :: MonadFail m => String -> m a
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
Documentation
guard :: Alternative f => Bool -> f () #
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
otherwise. For example:Just
(x `div`
y)
>>> 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)
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.
'
' can be understood as the join
bssdo
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
class Applicative m => Monad (m :: Type -> Type) 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:
- 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.
(>>=) :: m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
'as
' can be understood as the >>=
bsdo
expression
do a <- as bs a
(>>) :: m a -> m b -> m b infixl 1 #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
'as
' can be understood as the >>
bsdo
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 Complex | Since: base-4.9.0.0 |
Monad Min | Since: base-4.9.0.0 |
Monad Max | Since: base-4.9.0.0 |
Monad First | Since: base-4.9.0.0 |
Monad Last | Since: base-4.9.0.0 |
Monad Option | Since: base-4.9.0.0 |
Monad Identity | Since: base-4.8.0.0 |
Monad STM | Since: base-4.3.0.0 |
Monad First | Since: base-4.8.0.0 |
Monad Last | Since: base-4.8.0.0 |
Monad Dual | Since: base-4.8.0.0 |
Monad Sum | Since: base-4.8.0.0 |
Monad Product | Since: base-4.8.0.0 |
Monad ReadPrec | Since: base-2.1 |
Monad ReadP | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad P | Since: base-2.1 |
Monad (Either e) | Since: base-4.4.0.0 |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad (ST s) | Since: base-2.1 |
Monad (ST s) | Since: base-2.1 |
Monad m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # return :: a -> WrappedMonad m a # | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
(Monoid a, Monoid b) => Monad ((,,) a b) | Since: base-4.14.0.0 |
Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
Monad ((->) r :: Type -> Type) | Since: base-2.1 |
(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 |
class Functor (f :: Type -> Type) where #
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.
fmap :: (a -> b) -> f a -> f b #
Using ApplicativeDo
: '
' can be understood as
the fmap
f asdo
expression
do a <- as pure (f 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 Complex | Since: base-4.9.0.0 |
Functor Min | Since: base-4.9.0.0 |
Functor Max | Since: base-4.9.0.0 |
Functor First | Since: base-4.9.0.0 |
Functor Last | Since: base-4.9.0.0 |
Functor Option | Since: base-4.9.0.0 |
Functor ZipList | Since: base-2.1 |
Functor Identity | Since: base-4.8.0.0 |
Functor Handler | Since: base-4.6.0.0 |
Functor STM | Since: base-4.3.0.0 |
Functor First | Since: base-4.8.0.0 |
Functor Last | Since: base-4.8.0.0 |
Functor Dual | Since: base-4.8.0.0 |
Functor Sum | Since: base-4.8.0.0 |
Functor Product | Since: base-4.8.0.0 |
Functor ReadPrec | Since: base-2.1 |
Functor ReadP | Since: base-2.1 |
Functor NonEmpty | Since: base-4.9.0.0 |
Functor P | Since: base-4.8.0.0 |
Defined in Text.ParserCombinators.ReadP | |
Functor (Either a) | Since: base-3.0 |
Functor ((,) a) | Since: base-2.1 |
Functor (ST s) | Since: base-2.1 |
Functor (Arg a) | Since: base-4.9.0.0 |
Functor (ST s) | Since: base-2.1 |
Monad m => Functor (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b # (<$) :: a -> WrappedMonad m b -> WrappedMonad m a # | |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor ((,,) a b) | Since: base-4.14.0.0 |
Arrow a => Functor (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Functor f => Functor (Ap f) | Since: base-4.12.0.0 |
Functor f => Functor (Alt f) | Since: base-4.8.0.0 |
Functor ((->) r :: Type -> Type) | Since: base-2.1 |
Functor ((,,,) a b c) | Since: base-4.14.0.0 |
(Functor f, Functor g) => Functor (Product f g) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Sum f g) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Compose f g) | Since: base-4.9.0.0 |
class Monad m => MonadFail (m :: Type -> Type) where #
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 ReadPrec | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadPrec | |
MonadFail ReadP | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadP | |
MonadFail P | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadP | |
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 |
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
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_
.
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
replicateM_ :: Applicative m => Int -> m a -> m () #
Like replicateM
, but discards the result.
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM
n actn
times,
gathering the results.
Using ApplicativeDo
: '
' can be understood as
the replicateM
5 asdo
expression
do a1 <- as a2 <- as a3 <- as a4 <- as a5 <- as pure [a1,a2,a3,a4,a5]
Note the Applicative
constraint.
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #
Like foldM
, but discards the result.
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.
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () #
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] #
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 monad.
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
Using ApplicativeDo
: '
' can be understood as the
pseudo-forever
asdo
expression
do as as ..
with as
repeating.
Examples
A common use of forever
is to process input from network sockets,
Handle
s, 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 socketforkFinally
(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever
$ hGetLine client >>= hPutStrLn client
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
'(bs
' can be understood as the >=>
cs) ado
expression
do b <- bs a cs b
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
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
.
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Using ApplicativeDo
: '
' can be understood as the
void
asdo
expression
do as pure ()
with an inferred Functor
constraint.
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
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
).
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
).
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
).
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
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.
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
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 Option | Since: base-4.9.0.0 |
MonadPlus STM | Since: base-4.3.0.0 |
MonadPlus ReadPrec | Since: base-2.1 |
MonadPlus ReadP | Since: base-2.1 |
MonadPlus P | Since: base-2.1 |
Defined in Text.ParserCombinators.ReadP | |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 |
MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (Product f g) | Since: base-4.9.0.0 |
class Applicative m => Monad (m :: Type -> Type) #
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.
Instances
Monad [] | Since: base-2.1 |
Monad Maybe | Since: base-2.1 |
Monad IO | Since: base-2.1 |
Monad Complex | Since: base-4.9.0.0 |
Monad Min | Since: base-4.9.0.0 |
Monad Max | Since: base-4.9.0.0 |
Monad First | Since: base-4.9.0.0 |
Monad Last | Since: base-4.9.0.0 |
Monad Option | Since: base-4.9.0.0 |
Monad Identity | Since: base-4.8.0.0 |
Monad STM | Since: base-4.3.0.0 |
Monad First | Since: base-4.8.0.0 |
Monad Last | Since: base-4.8.0.0 |
Monad Dual | Since: base-4.8.0.0 |
Monad Sum | Since: base-4.8.0.0 |
Monad Product | Since: base-4.8.0.0 |
Monad ReadPrec | Since: base-2.1 |
Monad ReadP | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad P | Since: base-2.1 |
Monad (Either e) | Since: base-4.4.0.0 |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad (ST s) | Since: base-2.1 |
Monad (ST s) | Since: base-2.1 |
Monad m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # return :: a -> WrappedMonad m a # | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
(Monoid a, Monoid b) => Monad ((,,) a b) | Since: base-4.14.0.0 |
Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
Monad ((->) r :: Type -> Type) | Since: base-2.1 |
(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 |
class Monad m => MonadFail (m :: Type -> Type) #
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 ReadPrec | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadPrec | |
MonadFail ReadP | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadP | |
MonadFail P | Since: base-4.9.0.0 |
Defined in Text.ParserCombinators.ReadP | |
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 :: Type -> Type) where #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
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 Option | Since: base-4.9.0.0 |
MonadPlus STM | Since: base-4.3.0.0 |
MonadPlus ReadPrec | Since: base-2.1 |
MonadPlus ReadP | Since: base-2.1 |
MonadPlus P | Since: base-2.1 |
Defined in Text.ParserCombinators.ReadP | |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 |
MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (Product f g) | Since: base-4.9.0.0 |