Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module exports functions which allow to process instances of
Container
type class in monadic way.
Synopsis
- concatMapM :: (Applicative f, Monoid m, Container (l m), Element (l m) ~ m, Traversable l) => (a -> f m) -> l a -> f m
- concatForM :: (Applicative f, Monoid m, Container (l m), Element (l m) ~ m, Traversable l) => l a -> (a -> f m) -> f m
- allM :: (Container f, Monad m) => (Element f -> m Bool) -> f -> m Bool
- anyM :: (Container f, Monad m) => (Element f -> m Bool) -> f -> m Bool
- andM :: (Container f, Element f ~ m Bool, Monad m) => f -> m Bool
- orM :: (Container f, Element f ~ m Bool, Monad m) => f -> m Bool
Documentation
concatMapM :: (Applicative f, Monoid m, Container (l m), Element (l m) ~ m, Traversable l) => (a -> f m) -> l a -> f m Source #
Lifting bind into a monad. Generalized version of concatMap
that works with a monadic predicate. Old and simpler specialized to list
version had next type:
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
Side note: previously it had type
concatMapM :: (Applicative q, Monad m, Traversable m) => (a -> q (m b)) -> m a -> q (m b)
Such signature didn't allow to use this function when traversed container type and type of returned by function-argument differed. Now you can use it like e.g.
concatMapM readFile files >>= putTextLn
concatForM :: (Applicative f, Monoid m, Container (l m), Element (l m) ~ m, Traversable l) => l a -> (a -> f m) -> f m Source #
Like concatMapM
, but has its arguments flipped, so can be used
instead of the common fmap concat $ forM
pattern.
andM :: (Container f, Element f ~ m Bool, Monad m) => f -> m Bool Source #
Monadic and constrained to Container
version of and
.
>>>
andM [Just True, Just False]
Just False>>>
andM [Just True]
Just True>>>
andM [Just True, Just False, Nothing]
Just False>>>
andM [Just True, Nothing]
Nothing>>>
andM [putTextLn "1" >> pure True, putTextLn "2" >> pure False, putTextLn "3" >> pure True]
1 2 False