Agda-2.5.1: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.Utils.Monad

Synopsis

Documentation

(==<<) :: Monad m => (a -> b -> m c) -> (m a, m b) -> m c Source

Binary bind.

when_ :: Monad m => Bool -> m a -> m () Source

when_ is just Control.Monad.when with a more general type.

unless_ :: Monad m => Bool -> m a -> m () Source

unless_ is just Control.Monad.unless with a more general type.

whenM :: Monad m => m Bool -> m a -> m () Source

unlessM :: Monad m => m Bool -> m a -> m () Source

ifM :: Monad m => m Bool -> m a -> m a -> m a Source

Monadic if-then-else.

ifNotM :: Monad m => m Bool -> m a -> m a -> m a Source

ifNotM mc = ifM (not $ mc)

and2M :: Monad m => m Bool -> m Bool -> m Bool Source

Lazy monadic conjunction.

andM :: (Foldable f, Monad m) => f (m Bool) -> m Bool Source

allM :: (Functor f, Foldable f, Monad m) => f a -> (a -> m Bool) -> m Bool Source

or2M :: Monad m => m Bool -> m Bool -> m Bool Source

Lazy monadic disjunction.

orM :: (Foldable f, Monad m) => f (m Bool) -> m Bool Source

anyM :: (Functor f, Foldable f, Monad m) => f a -> (a -> m Bool) -> m Bool Source

altM1 :: Monad m => (a -> m (Either err b)) -> [a] -> m (Either err b) Source

Lazy monadic disjunction with Either truth values.

mapM' :: (Foldable t, Monad m, Monoid b) => (a -> m b) -> t a -> m b Source

Generalized version of mapM_ :: Monad m => (a -> m ()) -> [a] -> m () Executes effects and collects results in left-to-right order. Works best with left-associative monoids.

Note that there is an alternative

mapM' f t = foldr mappend mempty $ mapM f t

that collects results in right-to-left order (effects still left-to-right). It might be preferable for right associative monoids.

forM' :: (Foldable t, Monad m, Monoid b) => t a -> (a -> m b) -> m b Source

Generalized version of forM_ :: Monad m => [a] -> (a -> m ()) -> m ()

type Cont r a = (a -> r) -> r Source

thread :: (a -> Cont r b) -> [a] -> Cont r [b] Source

mapM for the continuation monad. Terribly useful.

zipWithM' :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m [c] Source

Requires both lists to have the same lengths.

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

A monadic version of mapMaybe :: (a -> Maybe b) -> [a] -> [b].

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

The for version of mapMaybeM.

dropWhileM :: Monad m => (a -> m Bool) -> [a] -> m [a] Source

A monadic version of dropWhile :: (a -> Bool) -> [a] -> [a].

finally :: MonadError e m => m a -> m b -> m a Source

Finally for the Error class. Errors in the finally part take precedence over prior errors.

bracket_ Source

Arguments

:: Monad m 
=> m a

Acquires resource. Run first.

-> (a -> m c)

Releases resource. Run last.

-> m b

Computes result. Run in-between.

-> m b 

Bracket without failure. Typically used to preserve state.

localState :: MonadState s m => m a -> m a Source

Restore state after computation.

readM :: (Error e, MonadError e m, Read a) => String -> m a Source

when :: Applicative f => Bool -> f () -> f ()

Conditional execution of Applicative expressions. For example,

when debug (putStrLn "Debugging")

will output the string Debugging if the Boolean value debug is True, and otherwise do nothing.

unless :: Applicative f => Bool -> f () -> f ()

The reverse of when.

class (Alternative m, Monad m) => MonadPlus m where

Monads that also support choice and failure.

Minimal complete definition

Nothing

Methods

mzero :: m a

the identity of mplus. It should also satisfy the equations

mzero >>= f  =  mzero
v >> mzero   =  mzero

mplus :: m a -> m a -> m a

an associative operation

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

An infix synonym for fmap.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an 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)

(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b

Sequential application.

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

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

modify' :: MonadState s m => (s -> s) -> m ()