extra-1.4.11: Extra functions I use.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Extra

Contents

Description

Extra functions for Control.Monad. These functions provide looping, list operations and booleans. If you need a wider selection of monad loops and list generalisations, see monad-loops.

Synopsis

Documentation

whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m () Source #

Perform some operation on Just, given the field inside the Just.

whenJust Nothing  print == return ()
whenJust (Just 1) print == print 1

whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () Source #

Like whenJust, but where the test can be monadic.

unit :: m () -> m () Source #

The identity function which requires the inner argument to be (). Useful for functions with overloaded return types.

\(x :: Maybe ()) -> unit x == x

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

Monadic generalisation of maybe.

eitherM :: Monad m => (a -> m c) -> (b -> m c) -> m (Either a b) -> m c Source #

Monadic generalisation of either.

Loops

loopM :: Monad m => (a -> m (Either a b)) -> a -> m b Source #

A looping operation, where the predicate returns Left as a seed for the next loop or Right to abort the loop.

whileM :: Monad m => m Bool -> m () Source #

Keep running an operation until it becomes False. As an example:

whileM $ do sleep 0.1; notM $ doesFileExist "foo.txt"
readFile "foo.txt"

If you need some state persisted between each test, use loopM.

Lists

partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a]) Source #

A version of partition that works with a monadic predicate.

partitionM (Just . even) [1,2,3] == Just ([2], [1,3])
partitionM (const Nothing) [1,2,3] == Nothing

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

A version of concatMap that works with a monadic predicate.

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

Like concatMapM, but has its arguments flipped, so can be used instead of the common fmap concat $ forM pattern.

mconcatMapM :: (Monad m, Monoid b) => (a -> m b) -> [a] -> m b Source #

A version of mconcatMap that works with a monadic predicate.

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

A version of mapMaybe that works with a monadic predicate.

findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a) Source #

Like find, but where the test can be monadic.

findM (Just . isUpper) "teST"             == Just (Just 'S')
findM (Just . isUpper) "test"             == Just Nothing
findM (Just . const True) ["x",undefined] == Just (Just "x")

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

Like findM, but also allows you to compute some additional information in the predicate.

Booleans

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

Like when, but where the test can be monadic.

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

Like unless, but where the test can be monadic.

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

Like if, but where the test can be monadic.

notM :: Functor m => m Bool -> m Bool Source #

Like not, but where the test can be monadic.

(||^) :: Monad m => m Bool -> m Bool -> m Bool Source #

The lazy || operator lifted to a monad. If the first argument evaluates to True the second argument will not be evaluated.

Just True  ||^ undefined  == Just True
Just False ||^ Just True  == Just True
Just False ||^ Just False == Just False

(&&^) :: Monad m => m Bool -> m Bool -> m Bool Source #

The lazy && operator lifted to a monad. If the first argument evaluates to False the second argument will not be evaluated.

Just False &&^ undefined  == Just False
Just True  &&^ Just True  == Just True
Just True  &&^ Just False == Just False

orM :: Monad m => [m Bool] -> m Bool Source #

A version of or lifted to a monad. Retains the short-circuiting behaviour.

orM [Just False,Just True ,undefined] == Just True
orM [Just False,Just False,undefined] == undefined
\xs -> Just (or xs) == orM (map Just xs)

andM :: Monad m => [m Bool] -> m Bool Source #

A version of and lifted to a monad. Retains the short-circuiting behaviour.

andM [Just True,Just False,undefined] == Just False
andM [Just True,Just True ,undefined] == undefined
\xs -> Just (and xs) == andM (map Just xs)

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

A version of any lifted to a monad. Retains the short-circuiting behaviour.

anyM Just [False,True ,undefined] == Just True
anyM Just [False,False,undefined] == undefined
\(f :: Int -> Maybe Bool) xs -> anyM f xs == orM (map f xs)

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

A version of all lifted to a monad. Retains the short-circuiting behaviour.

allM Just [True,False,undefined] == Just False
allM Just [True,True ,undefined] == undefined
\(f :: Int -> Maybe Bool) xs -> anyM f xs == orM (map f xs)