{-# LANGUAGE NoImplicitPrelude #-} module Precursor.Control.Monad (-- * Monad class Monad -- * Functions -- ** Naming conventions -- $naming -- ** Basic @Monad@ functions , (>>=) , (=<<) , (>=>) , (<=<) , join -- ** Generalisations of list functions , foldlM , foldlM_ , foldrM , foldrM_ -- ** Strict monadic functions , (<$!>) -- ** Avoid , (>>) , fail , return ) where import Precursor.Control.Category import Control.Monad import Data.Foldable hiding (foldlM) import qualified Data.Foldable as Foldable {- | The 'foldlM' function is analogous to 'Precursor.Structure.Foldable.foldl', except that its result is encapsulated in a monad. > foldlM f a1 [x1, x2, ..., xm] == > do > a2 <- f a1 x1 > a3 <- f a2 x2 > ... > f am xm -} foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b foldlM = Foldable.foldlM -- | Like 'foldlM', but discards the result. foldlM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () foldlM_ = foldM_ -- | Like 'foldrM', but discards the result. foldrM_ :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m () foldrM_ f b = void . foldrM f b {- $naming The functions in this library use the following naming conventions: * A postfix \'@M@\' always stands for a function in the Kleisli category: The monad type constructor @m@ is added to function results (modulo currying) and nowhere else. So, for example, > filter :: (a -> Bool) -> [a] -> [a] > filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] * A postfix \'@_@\' changes the result type from @(m a)@ to @(m ())@. Thus, for example: > sequence :: Monad m => [m a] -> m [a] > sequence_ :: Monad m => [m a] -> m () * A prefix \'@m@\' generalizes an existing function to a monadic form. Thus, for example: > sum :: Num a => [a] -> a > msum :: MonadPlus m => [m a] -> m a -}