| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
MonadUtils
Description
Utilities related to Monad and Applicative classes Mostly for backwards compatibility.
- class Functor f => Applicative (f :: * -> *) where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- class Monad m => MonadFix (m :: * -> *) where
- 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 #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*> or liftA2. If it defines both, then they must behave
the same as their default definitions:
(
<*>) = liftA2 idliftA2 f x y = f <$> x <*> y
Further, any definition must satisfy the following:
- identity
pureid<*>v = v- composition
pure(.)<*>u<*>v<*>w = u<*>(v<*>w)- homomorphism
puref<*>purex =pure(f x)- interchange
u
<*>purey =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
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2p (liftA2q u v) =liftA2f u .liftA2g v
If f is also a Monad, it should satisfy
(which implies that pure and <*> satisfy the applicative functor laws).
Methods
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*> that is more
efficient than the default one.
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Instances
| Applicative [] | Since: 2.1 |
| Applicative Maybe | Since: 2.1 |
| Applicative IO | Since: 2.1 |
| Applicative Par1 | Since: 4.9.0.0 |
| Applicative Q | |
| Applicative P | Since: 4.5.0.0 |
| Applicative Complex | Since: 4.9.0.0 |
| Applicative Min | Since: 4.9.0.0 |
| Applicative Max | Since: 4.9.0.0 |
| Applicative First | Since: 4.9.0.0 |
| Applicative Last | Since: 4.9.0.0 |
| Applicative Option | Since: 4.9.0.0 |
| Applicative NonEmpty | Since: 4.9.0.0 |
| Applicative ZipList | f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN
|
| Applicative Identity | Since: 4.8.0.0 |
| Applicative STM | Since: 4.8.0.0 |
| Applicative Dual | Since: 4.8.0.0 |
| Applicative Sum | Since: 4.8.0.0 |
| Applicative Product | Since: 4.8.0.0 |
| Applicative First | |
| Applicative Last | |
| Applicative ReadPrec | Since: 4.6.0.0 |
| Applicative ReadP | Since: 4.6.0.0 |
| Applicative PutM | |
| Applicative Get | |
| Applicative Put | |
| Applicative Tree | |
| Applicative Seq | |
| Applicative VM | |
| Applicative SimpleUniqueMonad | |
| Applicative Capability | |
| Applicative Pair # | |
| Applicative UniqSM # | |
| Applicative P # | |
| Applicative PD # | |
| Applicative UnifyResultM # | |
| Applicative LlvmM # | |
| Applicative FCode # | |
| Applicative CmmParse # | |
| Applicative Hsc # | |
| Applicative TcPluginM # | |
| Applicative CompPipeline # | |
| Applicative Ghc # | |
| Applicative CoreM # | |
| Applicative SimplM # | |
| Applicative CpsRn # | |
| Applicative OccCheckResult # | |
| Applicative TcS # | |
| Applicative VM # | |
| Applicative NatM # | |
| Applicative (Either e) | Since: 3.0 |
| Applicative (U1 *) | Since: 4.9.0.0 |
| Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)Since: 2.1 |
| Applicative (ST s) | Since: 4.4.0.0 |
| Monad m => Applicative (WrappedMonad m) | Since: 2.1 |
| Arrow a => Applicative (ArrowMonad a) | Since: 4.6.0.0 |
| Applicative (Proxy *) | Since: 4.7.0.0 |
| Applicative (SetM s) | |
| Applicative (State s) | |
| Monad m => Applicative (CheckingFuelMonad m) | |
| Monad m => Applicative (InfiniteFuelMonad m) | |
| Monad m => Applicative (UniqueMonadT m) | |
| (Functor m, Monad m) => Applicative (MaybeT m) | |
| Applicative (ListT f) # | |
| Applicative (State s) # | |
| Applicative (MaybeErr err) # | |
| Applicative (CmdLineP s) # | |
| Monad m => Applicative (EwM m) # | |
| Applicative (IOEnv m) # | |
| Applicative (RegM freeRegs) # | |
| Applicative m => Applicative (GhcT m) # | |
| Applicative f => Applicative (Rec1 * f) | Since: 4.9.0.0 |
| Arrow a => Applicative (WrappedArrow a b) | Since: 2.1 |
| Monoid m => Applicative (Const * m) | Since: 2.0.1 |
| Applicative f => Applicative (Alt * f) | |
| (Applicative f, Monad f) => Applicative (WhenMissing f x) | Equivalent to |
| (Monoid w, Applicative m) => Applicative (WriterT w m) | |
| (Functor m, Monad m) => Applicative (StateT s m) | |
| (Functor m, Monad m) => Applicative (StateT s m) | |
| (Functor m, Monad m) => Applicative (ExceptT e m) | |
| Monad m => Applicative (Stream m a) # | |
| Applicative ((->) LiftedRep LiftedRep a) | Since: 2.1 |
| (Applicative f, Applicative g) => Applicative ((:*:) * f g) | Since: 4.9.0.0 |
| (Monad f, Applicative f) => Applicative (WhenMatched f x y) | Equivalent to |
| (Applicative f, Monad f) => Applicative (WhenMissing f k x) | Equivalent to |
| Applicative m => Applicative (ReaderT * r m) | |
| Applicative f => Applicative (M1 * i c f) | Since: 4.9.0.0 |
| (Applicative f, Applicative g) => Applicative ((:.:) * * f g) | Since: 4.9.0.0 |
| (Monad f, Applicative f) => Applicative (WhenMatched f k x y) | Equivalent to |
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
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 Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an to an Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "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 #
Monads having fixed points with a 'knot-tying' semantics.
Instances of MonadFix should satisfy the following laws:
- purity
mfix(return. h) =return(fixh)- left shrinking (or tightening)
mfix(\x -> a >>= \y -> f x y) = a >>= \y ->mfix(\x -> f x y)- sliding
, for strictmfix(liftMh . f) =liftMh (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.
Minimal complete definition
Methods
Instances
| MonadFix [] | Since: 2.1 |
| MonadFix Maybe | Since: 2.1 |
| MonadFix IO | Since: 2.1 |
| MonadFix Par1 | Since: 4.9.0.0 |
| MonadFix Min | Since: 4.9.0.0 |
| MonadFix Max | Since: 4.9.0.0 |
| MonadFix First | Since: 4.9.0.0 |
| MonadFix Last | Since: 4.9.0.0 |
| MonadFix Option | Since: 4.9.0.0 |
| MonadFix NonEmpty | Since: 4.9.0.0 |
| MonadFix Identity | Since: 4.8.0.0 |
| MonadFix Dual | Since: 4.8.0.0 |
| MonadFix Sum | Since: 4.8.0.0 |
| MonadFix Product | Since: 4.8.0.0 |
| MonadFix First | Since: 4.8.0.0 |
| MonadFix Last | Since: 4.8.0.0 |
| MonadFix UniqSM # | |
| MonadFix Ghc # | |
| MonadFix (Either e) | Since: 4.3.0.0 |
| MonadFix (ST s) | Since: 2.1 |
| MonadFix m => MonadFix (MaybeT m) | |
| MonadFix f => MonadFix (Rec1 * f) | Since: 4.9.0.0 |
| MonadFix f => MonadFix (Alt * f) | Since: 4.8.0.0 |
| (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 ((->) LiftedRep LiftedRep r) | Since: 2.1 |
| (MonadFix f, MonadFix g) => MonadFix ((:*:) * f g) | Since: 4.9.0.0 |
| MonadFix m => MonadFix (ReaderT * r m) | |
| MonadFix f => MonadFix (M1 * i c f) | Since: 4.9.0.0 |
class Monad m => MonadIO (m :: * -> *) where #
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:
Minimal complete definition
Instances
| MonadIO IO | Since: 4.9.0.0 |
| MonadIO Hsc # | |
| MonadIO CompPipeline # | |
| MonadIO Ghc # | |
| MonadIO CoreM # | |
| MonadIO SimplM # | |
| MonadIO VM # | |
| MonadIO m => MonadIO (MaybeT m) | |
| MonadIO (IOEnv env) # | |
| 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]) #
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 #
Arguments
| :: Monad m | |
| => (acc -> x -> m (acc, y)) | combining function |
| -> 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