Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Utilities related to Monad and Applicative classes Mostly for backwards compatability.
- class Functor f => Applicative f where
- (<$>) :: 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]
- fmapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b)
- fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d)
- 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
class Functor f => Applicative f where Source
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying 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
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 Source
Sequential application.
(*>) :: f a -> f b -> f b infixl 4 Source
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4 Source
Sequence actions, discarding the value of the second argument.
class Monad m => MonadFix m where Source
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
, for strictmfix
(liftM
h . f) =liftM
h (mfix
(f . h))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.
liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b Source
Lift an IO
operation with 1 argument into another monad
liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c Source
Lift an IO
operation with 2 arguments into another monad
liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d Source
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
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
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source
Monadic version of concatMap
fmapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) Source
Monadic version of fmap
fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d) Source
Monadic version of fmap
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source
Monadic version of any
, aborts the computation at the first True
value
allM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source
Monad version of all
, aborts the computation at the first False
value