[commit: ghc] master: Improve Control.Monad.guard and Control.Monad.MonadPlus docs (6847c6b)

git at git.haskell.org git at git.haskell.org
Mon Dec 11 19:26:45 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6847c6bf5777eaf507f1cef28c1fc75a2c68bdef/ghc

>---------------------------------------------------------------

commit 6847c6bf5777eaf507f1cef28c1fc75a2c68bdef
Author: Nathan Collins <conathan at galois.com>
Date:   Mon Dec 11 12:52:55 2017 -0500

    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


>---------------------------------------------------------------

6847c6bf5777eaf507f1cef28c1fc75a2c68bdef
 libraries/base/Control/Monad.hs | 43 +++++++++++++++++++++++++++++++++++++++--
 libraries/base/GHC/Base.hs      | 13 +++++++++++--
 2 files changed, 52 insertions(+), 4 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 0706c86..3570144 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -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 at -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
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 052f13f..2d6e0e4 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -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 = (<|>)
 



More information about the ghc-commits mailing list