ghc-7.2.2: The GHC API

MonadUtils

Description

Utilities related to Monad and Applicative classes Mostly for backwards compatability.

Synopsis

Documentation

class Functor f => Applicative f whereSource

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

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:

      u *> v = pure (const id) <*> u <*> v
      u <* v = pure const <*> u <*> v

As a consequence of these laws, the Functor instance for f will satisfy

      fmap f x = pure f <*> x

If f is also a Monad, it should satisfy pure = return and (<*>) = ap (which implies that pure and <*> satisfy the applicative functor laws).

Methods

pure :: a -> f aSource

Lift a value.

(<*>) :: f (a -> b) -> f a -> f bSource

Sequential application.

(*>) :: f a -> f b -> f bSource

Sequence actions, discarding the value of the first argument.

(<*) :: f a -> f b -> f aSource

Sequence actions, discarding the value of the second argument.

(<$>) :: Functor f => (a -> b) -> f a -> f bSource

An infix synonym for fmap.

class Monad m => MonadFix m whereSource

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 aSource

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.

class Monad m => MonadIO m whereSource

Methods

liftIO :: IO a -> m aSource

data ID a Source

Instances

runID :: ID a -> aSource

liftIO1 :: MonadIO m => (a -> IO b) -> a -> m bSource

Lift an IO operation with 1 argument into another monad

liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m cSource

Lift an IO operation with 2 arguments into another monad

liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m dSource

Lift an IO operation with 3 arguments into another monad

liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m eSource

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

mapAccumLMSource

Arguments

:: 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

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]Source

Monadic version of mapMaybe

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 BoolSource

Monadic version of any, aborts the computation at the first True value

allM :: Monad m => (a -> m Bool) -> [a] -> m BoolSource

Monad version of all, aborts the computation at the first False value

foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m aSource

Monadic version of foldl

foldlM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m ()Source

Monadic version of foldl that discards its result

foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m aSource

Monadic version of foldr

maybeMapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b)Source

Monadic version of fmap specialised for Maybe