Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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]
- zipWith3M_ :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m ()
- zipWith4M :: Monad m => (a -> b -> c -> d -> m e) -> [a] -> [b] -> [c] -> [d] -> m [e]
- zipWithAndUnzipM :: Monad m => (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d])
- mapAndUnzipM :: Applicative 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])
- mapAndUnzip5M :: Monad m => (a -> m (b, c, d, e, f)) -> [a] -> m ([b], [c], [d], [e], [f])
- 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
- orM :: Monad m => m Bool -> m Bool -> 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)
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
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).
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
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.
MonadFix [] | |
MonadFix Maybe | |
MonadFix IO | |
MonadFix Par1 | |
MonadFix Identity | |
MonadFix Min | |
MonadFix Max | |
MonadFix First | |
MonadFix Last | |
MonadFix Option | |
MonadFix NonEmpty | |
MonadFix Dual | |
MonadFix Sum | |
MonadFix Product | |
MonadFix First | |
MonadFix Last | |
MonadFix UniqSM # | |
MonadFix Ghc # | |
MonadFix ((->) r) | |
MonadFix (Either e) | |
MonadFix f => MonadFix (Rec1 f) | |
MonadFix (ST s) | |
MonadFix (ST s) | |
MonadFix m => MonadFix (MaybeT m) | |
(MonadFix f, MonadFix g) => MonadFix ((:*:) f g) | |
MonadFix f => MonadFix (Alt * f) | |
(Monoid w, MonadFix m) => MonadFix (WriterT w m) | |
MonadFix m => MonadFix (StateT s m) | |
MonadFix m => MonadFix (StateT s m) | |
MonadFix m => MonadFix (ExceptT e m) | |
MonadFix f => MonadFix (M1 i c f) | |
MonadFix m => MonadFix (ReaderT * r m) | |
class Monad m => MonadIO m where Source #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
MonadIO IO | |
MonadIO Hsc # | |
MonadIO Ghc # | |
MonadIO CompPipeline # | |
MonadIO CoreM # | |
MonadIO VM # | |
MonadIO SimplM # | |
MonadIO m => MonadIO (MaybeT m) | |
MonadIO (IOEnv env) # | |
(Applicative m, MonadIO m) => MonadIO (GhcT m) # | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (ExceptT e m) | |
MonadIO m => MonadIO (ReaderT * r m) | |
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
zipWith3M_ :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m () Source #
zipWithAndUnzipM :: Monad m => (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d]) Source #
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-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 #
mapAndUnzip5M :: Monad m => (a -> m (b, c, d, e, f)) -> [a] -> m ([b], [c], [d], [e], [f]) 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
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
foldlM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () Source #
Monadic version of foldl that discards its result
maybeMapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) Source #
Monadic version of fmap specialised for Maybe