|
|
|
Description |
Utilities related to Monad and Applicative classes
Mostly for backwards compatability.
|
|
Synopsis |
|
class Functor f => Applicative f where | pure :: a -> f a | (<*>) :: f (a -> b) -> f a -> f b | (*>) :: f a -> f b -> f b | (<*) :: f a -> f b -> f a |
| | (<$>) :: Functor f => (a -> b) -> f a -> f b | | class Monad m => MonadFix m where | mfix :: (a -> m a) -> m a |
| | class Monad m => MonadIO m where | | | liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b | | liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c | | liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d | | liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e | | zipWith3M :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d] | | mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c]) | | mapAndUnzip3M :: Monad m => (a -> m (b, c, d)) -> [a] -> m ([b], [c], [d]) | | mapAndUnzip4M :: Monad m => (a -> m (b, c, d, e)) -> [a] -> m ([b], [c], [d], [e]) | | mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y]) | | mapSndM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)] | | concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] | | mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] | | anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool | | allM :: Monad m => (a -> m Bool) -> [a] -> m Bool | | foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a | | foldlM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () | | foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m a | | maybeMapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) |
|
|
Documentation |
|
|
A functor with application.
Instances should satisfy the following laws:
- identity
-
pure id <*> v = v
- composition
-
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
- homomorphism
-
pure f <*> pure x = pure (f x)
- interchange
-
u <*> pure y = pure ($ y) <*> u
- ignore left value
-
u *> v = pure (const id) <*> u <*> v
- ignore right value
-
u <* v = pure const <*> u <*> v
The Functor instance should satisfy
fmap f x = pure f <*> x
If f is also a Monad, define pure = return and (<*>) = ap.
Minimal complete definition: pure and <*>.
| | Methods | | Lift a value.
| | (<*>) :: f (a -> b) -> f a -> f b | Source |
| Sequential application.
| | (*>) :: f a -> f b -> f b | Source |
| Sequence actions, discarding the value of the first argument.
| | (<*) :: f a -> f b -> f a | Source |
| Sequence actions, discarding the value of the second argument.
|
| | Instances | |
|
|
|
An infix synonym for fmap.
|
|
|
Monads having fixed points with a 'knot-tying' semantics.
Instances of MonadFix should satisfy the following laws:
- purity
-
mfix (return . h) = return (fix h)
- left shrinking (or tightening)
-
mfix (\x -> a >>= \y -> f x y) = a >>= \y -> mfix (\x -> f x y)
- sliding
-
mfix (Control.Monad.liftM h . f) = Control.Monad.liftM h (mfix (f . h)),
for strict h.
- nesting
-
mfix (\x -> mfix (\y -> f x y)) = mfix (\x -> f x x)
This class is used in the translation of the recursive do notation
supported by GHC and Hugs.
| | Methods | mfix :: (a -> m a) -> m a | Source |
| The fixed point of a monadic computation.
mfix f executes the action f only once, with the eventual
output fed back as the input. Hence f should not be strict,
for then mfix f would diverge.
|
| | Instances | |
|
|
|
| Methods | | | Instances | |
|
|
|
Lift an IO operation with 1 argument into another monad
|
|
|
Lift an IO operation with 2 arguments into another monad
|
|
|
Lift an IO operation with 3 arguments into another monad
|
|
liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e | Source |
|
Lift an IO operation with 4 arguments into another monad
|
|
zipWith3M :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d] | Source |
|
|
mapAndUnzipM :: Monad 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.
|
|
mapAndUnzip3M :: Monad m => (a -> m (b, c, d)) -> [a] -> m ([b], [c], [d]) | Source |
|
mapAndUnzipM for triples
|
|
mapAndUnzip4M :: Monad m => (a -> m (b, c, d, e)) -> [a] -> m ([b], [c], [d], [e]) | Source |
|
|
|
:: Monad m | | => acc -> x -> m (acc, y) | combining funcction
| -> acc | initial state
| -> [x] | inputs
| -> m (acc, [y]) | final state, outputs
| Monadic version of mapAccumL
|
|
|
mapSndM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)] | Source |
|
Monadic version of mapSnd
|
|
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] | Source |
|
Monadic version of concatMap
|
|
|
Monadic version of mapMaybe
|
|
|
Monadic version of any, aborts the computation at the first True value
|
|
|
Monad version of all, aborts the computation at the first False value
|
|
foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a | Source |
|
Monadic version of foldl
|
|
|
Monadic version of foldl that discards its result
|
|
foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m a | Source |
|
Monadic version of foldr
|
|
|
Monadic version of fmap specialised for Maybe
|
|
Produced by Haddock version 2.6.1 |