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

Safe HaskellNone
LanguageHaskell2010

Control.Super.Monad.Constrained.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 [b], Bind m n n, BindCts m n n b [b], FunctorCts n [b] [b]) => (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 [b], Bind m n n, BindCts m n n b [b], FunctorCts n [b] (), FunctorCts n [b] [b]) => (a -> m b) -> [a] -> n () Source #

mapM ignoring the result.

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

flipped version of mapM.

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

forM ignoring the result.

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

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

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

sequence ignoring the result.

(=<<) :: (Bind m n p, BindCts m n p a b) => (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 b c) => (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 c) => (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 a b) => m a -> n b Source #

Execute the given computation repeatedly forever.

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

Ignore the result of a computation.

voidM :: (Bind m n n, BindCts m n n a (), 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 (n a) a) => m (n a) -> p a Source #

Monadic join operation.

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

Like filter but with a monadic predicate and result.

mapAndUnzipM :: (Return n, ReturnCts n [(b, c)], Bind m n n, BindCts m n n (b, c) [(b, c)], FunctorCts n [(b, c)] ([b], [c]), FunctorCts n [(b, c)] [(b, c)]) => (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 [c], Bind m n n, BindCts m n n c [c], FunctorCts n [c] [c]) => (a -> b -> m c) -> [a] -> [b] -> n [c] Source #

Zip together two list using a monadic function.

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

Same as zipWithM, but ignores the results.

foldM :: (Foldable t, Return m, ReturnCts m b, Bind m n m, BindCts m n m b b) => (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 b, Bind m n m, BindCts m n m b b, FunctorCts m b ()) => (b -> a -> n b) -> b -> t a -> m () Source #

Same as foldM, but ignores the result.

replicateM :: (Return n, ReturnCts n [a], Bind m n n, BindCts m n n a [a], FunctorCts n [a] [a]) => 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 [a], Bind m n n, BindCts m n n a [a], FunctorCts n [a] (), FunctorCts n [a] [a]) => 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, FunctorCts m a b) => (a -> b) -> m a -> m b Source #

Make arguments and result of a pure function monadic.

liftM' :: (Return n, ReturnCts n b, Bind m n n, BindCts m n n a b) => (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 c, FunctorCts n b c) => (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 a d, Bind n p q, BindCts n p q b d, FunctorCts p c d) => (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 (a -> b) b, FunctorCts n a b) => m (a -> b) -> n a -> p b Source #

Make the resulting function a monadic function.

Strict monadic functions

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

Strict version of <$>.

Additional generalized supermonad functions

(<$>) :: (Return n, ReturnCts n b, Bind m n n, BindCts m n n a b) => (a -> b) -> m a -> n b infixl 4 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.

Functions based on applicatives

liftA3 :: (Applicative m n p, ApplicativeCts m n p b (c -> d), Applicative p p q, ApplicativeCts p p q c d, FunctorCts m a (b -> c -> d)) => (a -> b -> c -> d) -> m a -> n b -> p c -> q d Source #

Make arguments and result of a pure function applicative.

liftA2 :: (Applicative m n p, ApplicativeCts m n p b c, FunctorCts m a (b -> c)) => (a -> b -> c) -> m a -> n b -> p c Source #

Make arguments and result of a pure function applicative.

liftA :: (Return m, ReturnCts m (a -> b), Applicative m m n, ApplicativeCts m m n a b) => (a -> b) -> m a -> n b Source #

Lift a function to actions. Does what fmap does with applicative operations.

voidA :: (Applicative m n n, ApplicativeCtsR m n n a (), Return n, ReturnCts n ()) => m a -> n () Source #

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

(<**>) :: (Applicative m n p, ApplicativeCts m n p (a -> b) b, FunctorCts m a ((a -> b) -> b)) => m a -> n (a -> b) -> p b Source #

A variant of <*> with the arguments reversed.

mapA :: (Return n, ReturnCts n [b], Applicative m n n, ApplicativeCts m n n [b] [b], FunctorCts m b ([b] -> [b])) => (a -> m b) -> [a] -> n [b] Source #

Applicative version of mapM

mapA_ :: (Return n, ReturnCts n [b], Applicative m n n, ApplicativeCts m n n [b] [b], FunctorCts m b ([b] -> [b]), FunctorCts n [b] ()) => (a -> m b) -> [a] -> n () Source #

mapA ignoring the result.

forA :: (Return n, ReturnCts n [b], Applicative m n n, ApplicativeCts m n n [b] [b], FunctorCts m b ([b] -> [b])) => [a] -> (a -> m b) -> n [b] Source #

flipped version of mapA.

forA_ :: (Return n, ReturnCts n [b], Applicative m n n, ApplicativeCts m n n [b] [b], FunctorCts m b ([b] -> [b]), FunctorCts n [b] ()) => [a] -> (a -> m b) -> n () Source #

forA ignoring the result.

filterA :: (Applicative m n n, ApplicativeCts m n n [a] [a], Return n, ReturnCts n [a], FunctorCts m Bool ([a] -> [a])) => (a -> m Bool) -> [a] -> n [a] Source #

Like filterM but with an applicative predicate and result.

sequenceA :: (Return n, ReturnCts n [a], Applicative m n n, ApplicativeCts m n n [a] [a], FunctorCts m a ([a] -> [a])) => [m a] -> n [a] Source #

Specialization of the Traversable variant for list and applicatives.

sequenceA_ :: (Return n, ReturnCts n [a], Applicative m n n, ApplicativeCts m n n [a] [a], FunctorCts m a ([a] -> [a]), FunctorCts n [a] ()) => [m a] -> n () Source #

sequenceA ignoring the result.

traverse :: (Return n, ReturnCts n [b], Applicative m n n, ApplicativeCts m n n [b] [b], FunctorCts m b ([b] -> [b])) => (a -> m b) -> [a] -> n [b] Source #

Specialization of the Traversable variant for list and applicatives.

zipWithA :: (Return n, ReturnCts n [c], Applicative m n n, ApplicativeCts m n n [c] [c], FunctorCts m c ([c] -> [c])) => (a -> b -> m c) -> [a] -> [b] -> n [c] Source #

Like zipWithM but with an applicative predicate and result.

zipWithA_ :: (Return n, ReturnCts n [c], Applicative m n n, ApplicativeCts m n n [c] [c], FunctorCts m c ([c] -> [c]), FunctorCts n [c] ()) => (a -> b -> m c) -> [a] -> [b] -> n () Source #

Like zipWithM_ but with an applicative predicate and result.

mapAndUnzipA :: (Return n, ReturnCts n [(b, c)], Applicative m n n, ApplicativeCts m n n [(b, c)] [(b, c)], FunctorCts m (b, c) ([(b, c)] -> [(b, c)]), FunctorCts n [(b, c)] ([b], [c])) => (a -> m (b, c)) -> [a] -> n ([b], [c]) Source #

Like mapAndUnzipM but with an applicative predicate and result.

replicateA :: (Return n, ReturnCts n [a], Applicative m n n, ApplicativeCts m n n [a] [a], FunctorCts m a ([a] -> [a])) => Int -> m a -> n [a] Source #

Like replicateM but with applicatves.

replicateA_ :: (Return n, ReturnCts n [a], Applicative m n n, ApplicativeCts m n n [a] [a], FunctorCts m a ([a] -> [a]), FunctorCts n [a] ()) => Int -> m a -> n () Source #

Like replicateA, but discards the result.

whenA :: (Return n, ReturnCts n (), Applicative m n n, ApplicativeCtsR m n n () ()) => Bool -> m () -> n () Source #

When the condition is true do the given action.

unlessA :: (Return n, ReturnCts n (), Applicative m n n, ApplicativeCtsR m n n () ()) => Bool -> m () -> n () Source #

When the condition is false do the given action.