| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Prologue.Control.Monad
Synopsis
- return :: Applicative m => a -> m a
- (<<) :: Monad m => m a -> m b -> m a
- (>>$) :: Monad m => m a -> m b -> m b
- (>>=>) :: Monad m => (t1 -> t2 -> m a) -> (a -> m b) -> t1 -> t2 -> m b
- (>>>=>) :: Monad m => (t1 -> t2 -> t3 -> m a) -> (a -> m b) -> t1 -> t2 -> t3 -> m b
- (>>>>=>) :: Monad m => (t1 -> t2 -> t3 -> t4 -> m a) -> (a -> m b) -> t1 -> t2 -> t3 -> t4 -> m b
- (<=<<) :: Monad m => (a -> m b) -> (t1 -> t2 -> m a) -> t1 -> t2 -> m b
- (<=<<<) :: Monad m => (a -> m b) -> (t1 -> t2 -> t3 -> m a) -> t1 -> t2 -> t3 -> m b
- (<=<<<<) :: Monad m => (a -> m b) -> (t1 -> t2 -> t3 -> t4 -> m a) -> t1 -> t2 -> t3 -> t4 -> m b
- (>>~) :: Monad m => m a -> (a -> m b) -> m a
- (=<<&) :: MonadFix m => (a -> m b) -> m a -> m a
- void :: m a -> m ()
- when :: (Applicative m, Mempty a) => Bool -> m a -> m a
- unless :: (Applicative m, Mempty a) => Bool -> m a -> m a
- when_ :: Applicative m => Bool -> m a -> m ()
- unless_ :: Applicative m => Bool -> m a -> m ()
- whenM :: (Monad m, Mempty a) => m Bool -> m a -> m a
- unlessM :: (Monad m, Mempty a) => m Bool -> m a -> m a
- whenM_ :: Monad m => m Bool -> m a -> m ()
- unlessM_ :: Monad m => m Bool -> m a -> m ()
- guard :: (MonadPlus m, ToBool' cond) => cond -> m ()
- bind :: Monad m => (t1 -> m a) -> m t1 -> m a
- bind2 :: Monad m => (t1 -> t2 -> m a) -> m t1 -> m t2 -> m a
- bind3 :: Monad m => (t1 -> t2 -> t3 -> m a) -> m t1 -> m t2 -> m t3 -> m a
- bind4 :: Monad m => (t1 -> t2 -> t3 -> t4 -> m a) -> m t1 -> m t2 -> m t3 -> m t4 -> m a
- bind5 :: Monad m => (t1 -> t2 -> t3 -> t4 -> t5 -> m a) -> m t1 -> m t2 -> m t3 -> m t4 -> m t5 -> m a
- join :: Monad m => m (m a) -> m a
- class Applicative m => Monad (m :: Type -> Type) where
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- 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]
- 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
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
Documentation
return :: Applicative m => a -> m a Source #
Deprecated: Use pure instead
(>>>=>) :: Monad m => (t1 -> t2 -> t3 -> m a) -> (a -> m b) -> t1 -> t2 -> t3 -> m b infixr 1 Source #
(>>>>=>) :: Monad m => (t1 -> t2 -> t3 -> t4 -> m a) -> (a -> m b) -> t1 -> t2 -> t3 -> t4 -> m b infixr 1 Source #
(<=<<<) :: Monad m => (a -> m b) -> (t1 -> t2 -> t3 -> m a) -> t1 -> t2 -> t3 -> m b infixr 1 Source #
(<=<<<<) :: Monad m => (a -> m b) -> (t1 -> t2 -> t3 -> t4 -> m a) -> t1 -> t2 -> t3 -> t4 -> m b infixr 1 Source #
when_ :: Applicative m => Bool -> m a -> m () Source #
unless_ :: Applicative m => Bool -> m a -> m () Source #
bind5 :: Monad m => (t1 -> t2 -> t3 -> t4 -> t5 -> m a) -> m t1 -> m t2 -> m t3 -> m t4 -> m t5 -> m a Source #
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.
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 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.
Minimal complete definition
Methods
(>>=) :: 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.
(>>) :: 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.
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 Q | |
| 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 Down | Since: base-4.11.0.0 |
| Monad ReadPrec | Since: base-2.1 |
| Monad ReadP | Since: base-2.1 |
| Monad NonEmpty | Since: base-4.9.0.0 |
| Monad Put | |
| Monad Tree | |
| Monad Seq | |
| Monad DList | |
| Monad Vector | |
| Monad SmallArray | |
Defined in Data.Primitive.SmallArray Methods (>>=) :: SmallArray a -> (a -> SmallArray b) -> SmallArray b # (>>) :: SmallArray a -> SmallArray b -> SmallArray b # return :: a -> SmallArray a # fail :: String -> SmallArray a # | |
| Monad Array | |
| Monad P | Since: base-2.1 |
| Monad OneTuple Source # | |
| 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 |
| Representable f => Monad (Co f) | |
| 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 # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # return :: a -> WrappedMonad m a # fail :: String -> WrappedMonad m a # | |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Monad m => Monad (MaybeT m) | |
| Alternative f => Monad (Cofree f) | |
| Functor f => Monad (Free f) | |
| Monad (ImpossibleM1 :: Type -> Type) | |
Defined in Data.Impossible Methods (>>=) :: ImpossibleM1 a -> (a -> ImpossibleM1 b) -> ImpossibleM1 b # (>>) :: ImpossibleM1 a -> ImpossibleM1 b -> ImpossibleM1 b # return :: a -> ImpossibleM1 a # fail :: String -> ImpossibleM1 a # | |
| Monad m => Monad (Yoneda m) | |
| Monad (ReifiedGetter s) | |
Defined in Control.Lens.Reified Methods (>>=) :: ReifiedGetter s a -> (a -> ReifiedGetter s b) -> ReifiedGetter s b # (>>) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b # return :: a -> ReifiedGetter s a # fail :: String -> ReifiedGetter s a # | |
| Monad (ReifiedFold s) | |
Defined in Control.Lens.Reified Methods (>>=) :: ReifiedFold s a -> (a -> ReifiedFold s b) -> ReifiedFold s b # (>>) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b # return :: a -> ReifiedFold s a # fail :: String -> ReifiedFold s a # | |
| (Monad (Rep p), Representable p) => Monad (Prep p) | |
| Monad f => Monad (Rec1 f) | Since: base-4.9.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 m => Monad (IdentityT m) | |
| (Applicative f, Monad f) => Monad (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal Methods (>>=) :: WhenMissing f x a -> (a -> WhenMissing f x b) -> WhenMissing f x b # (>>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # return :: a -> WhenMissing f x a # fail :: String -> WhenMissing f x a # | |
| Monad m => Monad (ExceptT e m) | |
| (Functor f, Monad m) => Monad (FreeT f m) | |
| (Alternative f, Monad w) => Monad (CofreeT f w) | |
| (Monad m, Error e) => Monad (ErrorT e m) | |
| Monad (Indexed i a) | |
| Monad (Tagged s) | |
| Monad ((->) r :: Type -> Type) | Since: base-2.1 |
| (Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
| (Monad f, Monad g) => Monad (Product f g) | Since: base-4.9.0.0 |
| Monad (Cokleisli w a) | |
| (Monad f, Applicative f) => Monad (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal Methods (>>=) :: WhenMatched f x y a -> (a -> WhenMatched f x y b) -> WhenMatched f x y b # (>>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # return :: a -> WhenMatched f x y a # fail :: String -> WhenMatched f x y a # | |
| (Applicative f, Monad f) => Monad (WhenMissing f k x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal Methods (>>=) :: WhenMissing f k x a -> (a -> WhenMissing f k x b) -> WhenMissing f k x b # (>>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # return :: a -> WhenMissing f k x a # fail :: String -> WhenMissing f k x a # | |
| Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
| (Monad f, Applicative f) => Monad (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal Methods (>>=) :: WhenMatched f k x y a -> (a -> WhenMatched f k x y b) -> WhenMatched f k x y b # (>>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # return :: a -> WhenMatched f k x y a # fail :: String -> WhenMatched f k x y a # | |
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
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
An associative operation. The default definition is
mplus = (<|>)
Instances
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM n actn times,
gathering the results.
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] #
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
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 socketforkFinally(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever$ hGetLine client >>= hPutStrLn client