Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- module Control.Monad
- whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m ()
- whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
- pureIf :: Alternative m => Bool -> a -> m a
- whenMaybe :: Applicative m => Bool -> m a -> m (Maybe a)
- whenMaybeM :: Monad m => m Bool -> m a -> m (Maybe a)
- unit :: m () -> m ()
- maybeM :: Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b
- fromMaybeM :: Monad m => m a -> m (Maybe a) -> m a
- eitherM :: Monad m => (a -> m c) -> (b -> m c) -> m (Either a b) -> m c
- loop :: (a -> Either a b) -> a -> b
- loopM :: Monad m => (a -> m (Either a b)) -> a -> m b
- whileM :: Monad m => m Bool -> m ()
- whileJustM :: (Monad m, Monoid a) => m (Maybe a) -> m a
- untilJustM :: Monad m => m (Maybe a) -> m a
- partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])
- concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
- concatForM :: Monad m => [a] -> (a -> m [b]) -> m [b]
- mconcatMapM :: (Monad m, Monoid b) => (a -> m b) -> [a] -> m b
- mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
- findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
- firstJustM :: Monad m => (a -> m (Maybe b)) -> [a] -> m (Maybe b)
- fold1M :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m a
- fold1M_ :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m ()
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- notM :: Functor m => m Bool -> m Bool
- (||^) :: Monad m => m Bool -> m Bool -> m Bool
- (&&^) :: Monad m => m Bool -> m Bool -> m Bool
- orM :: Monad m => [m Bool] -> m Bool
- andM :: Monad m => [m Bool] -> m Bool
- anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
- allM :: Monad m => (a -> m Bool) -> [a] -> m Bool
Documentation
module Control.Monad
whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m () Source #
whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () Source #
Like whenJust
, but where the test can be monadic.
pureIf :: Alternative m => Bool -> a -> m a Source #
whenMaybeM :: Monad m => m Bool -> m a -> m (Maybe a) Source #
Like whenMaybe
, but where the test can be monadic.
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
untilJustM :: Monad m => m (Maybe a) -> m a Source #
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.
fold1M :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m a Source #
A variant of foldM
that has no base case, and thus may only be applied to non-empty lists.
fold1M (\x y -> Just x) [] == undefined fold1M (\x y -> Just $ x + y) [1, 2, 3] == Just 6
fold1M_ :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m () Source #
Like fold1M
but discards the result.
Booleans
unlessM :: Monad m => m Bool -> m () -> m () Source #
Like unless
, but where the test can be monadic.
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)