Skip to content
Snippets Groups Projects
Commit c01e413f authored by Nathan Collins's avatar Nathan Collins Committed by Ben Gamari
Browse files

Improve Control.Monad.guard and Control.Monad.MonadPlus docs

This fixes Issue #12372: documentation for Control.Monad.guard not
useful after AMP.

Reviewers: hvr, bgamari

Reviewed By: bgamari

Subscribers: rwbarton, thomie, carter

Differential Revision: https://phabricator.haskell.org/D4258

(cherry picked from commit 6847c6bf)
parent c384029a
No related branches found
No related tags found
No related merge requests found
......@@ -86,8 +86,47 @@ 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
......
......@@ -880,15 +880,24 @@ instance Alternative Maybe where
-- | Monads that also support choice and failure.
class (Alternative m, Monad m) => MonadPlus m where
-- | the identity of 'mplus'. It should also satisfy the equations
-- | The identity of 'mplus'. It should also satisfy the equations
--
-- > mzero >>= f = mzero
-- > v >> mzero = mzero
--
-- The default definition is
--
-- @
-- mzero = 'empty'
-- @
mzero :: m a
mzero = empty
-- | an associative operation
-- | An associative operation. The default definition is
--
-- @
-- mplus = ('<|>')
-- @
mplus :: m a -> m a -> m a
mplus = (<|>)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment