diff options
Diffstat (limited to 'libraries/base/Control/Monad.hs')
-rw-r--r-- | libraries/base/Control/Monad.hs | 134 |
1 files changed, 105 insertions, 29 deletions
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index 6a474037c0..96d8938101 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -86,13 +86,52 @@ import GHC.Num ( (-) ) -- ----------------------------------------------------------------------------- -- Functions mandated by the Prelude --- | @'guard' b@ is @'pure' ()@ if @b@ is 'True', --- and 'empty' if @b@ is 'False'. +-- | Conditional failure of 'Alternative' computations. Defined by +-- +-- @ +-- guard True = 'pure' () +-- guard False = 'empty' +-- @ +-- +-- ==== __Examples__ +-- +-- Common uses of 'guard' include conditionally signaling an error in +-- an error monad and conditionally rejecting the current choice in an +-- 'Alternative'-based parser. +-- +-- As an example of signaling an error in the error monad 'Maybe', +-- consider a safe division function @safeDiv x y@ that returns +-- 'Nothing' when the denominator @y@ is zero and @'Just' (x \`div\` +-- y)@ otherwise. For example: +-- +-- @ +-- >>> safeDiv 4 0 +-- Nothing +-- >>> safeDiv 4 2 +-- Just 2 +-- @ +-- +-- A definition of @safeDiv@ using guards, but not 'guard': +-- +-- @ +-- safeDiv :: Int -> Int -> Maybe Int +-- safeDiv x y | y /= 0 = Just (x \`div\` y) +-- | otherwise = Nothing +-- @ +-- +-- A definition of @safeDiv@ using 'guard' and 'Monad' @do@-notation: +-- +-- @ +-- safeDiv :: Int -> Int -> Maybe Int +-- safeDiv x y = do +-- guard (y /= 0) +-- return (x \`div\` y) +-- @ guard :: (Alternative f) => Bool -> f () guard True = pure () guard False = empty --- | This generalizes the list-based 'filter' function. +-- | This generalizes the list-based 'Data.List.filter' function. {-# INLINE filterM #-} filterM :: (Applicative m) => (a -> m Bool) -> [a] -> m [a] @@ -100,11 +139,12 @@ filterM p = foldr (\ x -> liftA2 (\ flg -> if flg then (x:) else id) (p x infixr 1 <=<, >=> --- | Left-to-right Kleisli composition of monads. +-- | Left-to-right composition of Kleisli arrows. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) f >=> g = \x -> f x >>= g --- | Right-to-left Kleisli composition of monads. @('>=>')@, with the arguments flipped. +-- | Right-to-left composition of Kleisli arrows. @('>=>')@, with the arguments +-- flipped. -- -- Note how this operator resembles function composition @('.')@: -- @@ -113,7 +153,30 @@ f >=> g = \x -> f x >>= g (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) (<=<) = flip (>=>) --- | @'forever' act@ repeats the action infinitely. +-- | Repeat an action indefinitely. +-- +-- ==== __Examples__ +-- +-- A common use of 'forever' is to process input from network sockets, +-- 'System.IO.Handle's, and channels +-- (e.g. 'Control.Concurrent.MVar.MVar' and +-- 'Control.Concurrent.Chan.Chan'). +-- +-- For example, here is how we might implement an [echo +-- server](https://en.wikipedia.org/wiki/Echo_Protocol), using +-- 'forever' both to listen for client connections on a network socket +-- and to echo client input on client connection handles: +-- +-- @ +-- echoServer :: Socket -> IO () +-- echoServer socket = 'forever' $ do +-- client <- accept socket +-- 'Control.Concurrent.forkFinally' (echo client) (\\_ -> hClose client) +-- where +-- echo :: Handle -> IO () +-- echo client = 'forever' $ +-- hGetLine client >>= hPutStrLn client +-- @ forever :: (Applicative f) => f a -> f b {-# INLINE forever #-} forever a = let a' = a *> a' in a' @@ -125,7 +188,7 @@ forever a = let a' = a *> a' in a' -- | The 'mapAndUnzipM' function maps its first argument over a list, returning -- the result as a pair of lists. This function is mainly used with complicated --- data structures or a state-transforming monad. +-- data structures or a state monad. mapAndUnzipM :: (Applicative m) => (a -> m (b,c)) -> [a] -> m ([b], [c]) {-# INLINE mapAndUnzipM #-} mapAndUnzipM f xs = unzip <$> traverse f xs @@ -140,21 +203,21 @@ zipWithM_ :: (Applicative m) => (a -> b -> m c) -> [a] -> [b] -> m () {-# INLINE zipWithM_ #-} zipWithM_ f xs ys = sequenceA_ (zipWith f xs ys) -{- | The 'foldM' function is analogous to 'foldl', except that its result is +{- | The 'foldM' function is analogous to 'Data.Foldable.foldl', except that its result is encapsulated in a monad. Note that 'foldM' works from left-to-right over the list arguments. This could be an issue where @('>>')@ and the `folded function' are not commutative. -> foldM f a1 [x1, x2, ..., xm] - -== - -> do -> a2 <- f a1 x1 -> a3 <- f a2 x2 -> ... -> f am xm +> foldM f a1 [x1, x2, ..., xm] +> +> == +> +> do +> a2 <- f a1 x1 +> a3 <- f a2 x2 +> ... +> f am xm If right-to-left evaluation is required, the input list should be reversed. @@ -244,12 +307,25 @@ f <$!> m = do -- ----------------------------------------------------------------------------- -- Other MonadPlus functions --- | Direct 'MonadPlus' equivalent of 'filter' --- @'filter'@ = @(mfilter:: (a -> Bool) -> [a] -> [a]@ --- applicable to any 'MonadPlus', for example --- @mfilter odd (Just 1) == Just 1@ --- @mfilter odd (Just 2) == Nothing@ - +-- | Direct 'MonadPlus' equivalent of 'Data.List.filter'. +-- +-- ==== __Examples__ +-- +-- The 'Data.List.filter' function is just 'mfilter' specialized to +-- the list monad: +-- +-- @ +-- 'Data.List.filter' = ( 'mfilter' :: (a -> Bool) -> [a] -> [a] ) +-- @ +-- +-- An example using 'mfilter' with the 'Maybe' monad: +-- +-- @ +-- >>> mfilter odd (Just 1) +-- Just 1 +-- >>> mfilter odd (Just 2) +-- Nothing +-- @ mfilter :: (MonadPlus m) => (a -> Bool) -> m a -> m a {-# INLINABLE mfilter #-} mfilter p ma = do @@ -264,19 +340,19 @@ The functions in this library use the following naming conventions: 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] +> 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 () +> 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 +> filter :: (a -> Bool) -> [a] -> [a] +> mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a -} |