supermonad-0.1: Plugin and base library to support supermonads in Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Supermonad.Functions

Contents

Description

Collection of the ported monad-based functions for supermonads. For a more detailed description of these functions refer to the Monad module.

Most functions are generalized to suite the setting of supermonads better.

This module is thought as a replacement for the Control.Monad module.

Synopsis

Control.Monad replacements

Basic supermonad functions

mapM :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> m b) -> [a] -> n [b] Source #

Map the given function on each element of the list and collect the results.

mapM_ :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> m b) -> [a] -> n () Source #

mapM ignoring the result.

forM :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => [a] -> (a -> m b) -> n [b] Source #

flipped version of mapM.

forM_ :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => [a] -> (a -> m b) -> n () Source #

forM ignoring the result.

sequence :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => [m b] -> n [b] Source #

Execute all computations in the list in order and returns the list of results.

sequence_ :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => [m b] -> n () Source #

sequence ignoring the result.

(=<<) :: (Bind m n p, BindCts m n p) => (a -> n b) -> m a -> p b infixr 1 Source #

Same as >>=, but with the arguments interchanged.

(>=>) :: (Bind m n p, BindCts m n p) => (a -> m b) -> (b -> n c) -> a -> p c infixr 1 Source #

Left-to-right Kleisli composition.

(<=<) :: (Bind m n p, BindCts m n p) => (b -> n c) -> (a -> m b) -> a -> p c infixr 1 Source #

Right-to-left Kleisli composition.

forever :: (Bind m n n, BindCts m n n) => m a -> n b Source #

Execute the given computation repeatedly forever.

void :: Functor m => m a -> m () Source #

Ignore the result of a computation.

void' :: (Bind m n n, BindCts m n n, Return n, ReturnCts n) => m a -> n () Source #

Ignore the result of a computation, but allow morphing the computational type.

Generalizations of list functions

join :: (Bind m n p, BindCts m n p) => m (n a) -> p a Source #

Monadic join operation.

filterM :: (Bind m n n, BindCts m n n, Return n, ReturnCts n) => (a -> m Bool) -> [a] -> n [a] Source #

Like filter but with a monadic predicate and result.

mapAndUnzipM :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> m (b, c)) -> [a] -> n ([b], [c]) Source #

Map a given monadic function on the list and the unzip the results.

zipWithM :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> b -> m c) -> [a] -> [b] -> n [c] Source #

Zip together two list using a monadic function.

zipWithM_ :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> b -> m c) -> [a] -> [b] -> n () Source #

Same as zipWithM, but ignores the results.

foldM :: (Foldable t, Return m, ReturnCts m, Bind m n m, BindCts m n m) => (b -> a -> n b) -> b -> t a -> m b Source #

Fold the given foldable using a monadic function. See foldl.

foldM_ :: (Foldable t, Return m, ReturnCts m, Bind m n m, BindCts m n m) => (b -> a -> n b) -> b -> t a -> m () Source #

Same as foldM, but ignores the result.

replicateM :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => Int -> m a -> n [a] Source #

Repeats the given monadic operation for the given amount of times and returns the accumulated results.

replicateM_ :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => Int -> m a -> n () Source #

Same as replicateM, but ignores the results.

Conditional execution of monadic expressions

when :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => Bool -> m () -> n () Source #

When the condition is true do the given action.

unless :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => Bool -> m () -> n () Source #

When the condition is false do the given action.

Monadic lifting operators

liftM :: Functor m => (a -> b) -> m a -> m b Source #

Make arguments and result of a pure function monadic.

liftM' :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> b) -> m a -> n b Source #

Make arguments and result of a pure function monadic with allowed morphing

liftM2 :: (Bind m n p, BindCts m n p) => (a -> b -> c) -> m a -> n b -> p c Source #

Make arguments and result of a pure function monadic.

liftM3 :: (Bind m q q, BindCts m q q, Bind n p q, BindCts n p q) => (a -> b -> c -> d) -> m a -> n b -> p c -> q d Source #

Make arguments and result of a pure function monadic.

ap :: (Bind m n p, BindCts m n p) => m (a -> b) -> n a -> p b Source #

Make the resulting function a monadic function.

Strict monadic functions

(<$!>) :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> b) -> m a -> n b Source #

Strict version of <$>.

Additional generalized supermonad functions

(<$>) :: (Return n, ReturnCts n, Bind m n n, BindCts m n n) => (a -> b) -> m a -> n b Source #

Apply the given function to the result of a computation.

Addition due to RebindableSyntax

ifThenElse :: Bool -> a -> a -> a Source #

Standard implementation of if-then-else. Necessary because we are going to use RebindableSyntax together with this prelude.