[commit: ghc] master: base: Add new Control.Monad.Fail module (re #10751) (8c80dcc)

git at git.haskell.org git at git.haskell.org
Tue Nov 3 21:45:33 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8c80dcc166e4a083086d8b240d84563d0c4c4c50/ghc

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

commit 8c80dcc166e4a083086d8b240d84563d0c4c4c50
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Tue Nov 3 22:40:52 2015 +0100

    base: Add new Control.Monad.Fail module (re #10751)
    
    This is based on David's initial patch augmented by more extensive
    Haddock comments.
    
    This has been broken out of D1248 to reduce its size
    by splitting the patch into smaller logical pieces.
    
    On its own, this new module does nothing interesting yet.
    Later patches will add support for a different desugaring of
    `do`-blocks, at which point the new `MonadFail` class will
    become more useful.
    
    Reviewed By: ekmett, austin
    
    Differential Revision: https://phabricator.haskell.org/D1424


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

8c80dcc166e4a083086d8b240d84563d0c4c4c50
 libraries/base/Control/Monad/Fail.hs | 77 ++++++++++++++++++++++++++++++++++++
 libraries/base/GHC/Base.hs           |  5 +++
 libraries/base/base.cabal            |  1 +
 libraries/base/changelog.md          |  3 ++
 4 files changed, 86 insertions(+)

diff --git a/libraries/base/Control/Monad/Fail.hs b/libraries/base/Control/Monad/Fail.hs
new file mode 100644
index 0000000..0bbe65b
--- /dev/null
+++ b/libraries/base/Control/Monad/Fail.hs
@@ -0,0 +1,77 @@
+{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-- |
+-- Module      :  Control.Monad.Fail
+-- Copyright   :  (C) 2015 David Luposchainsky,
+--                (C) 2015 Herbert Valerio Riedel
+-- License     :  BSD-style (see the file LICENSE)
+--
+-- Maintainer  :  libraries at haskell.org
+-- Stability   :  provisional
+-- Portability :  portable
+--
+-- Transitional module providing the 'MonadFail' class and primitive
+-- instances.
+--
+-- This module can be imported for defining forward compatible
+-- 'MonadFail' instances:
+--
+-- @
+-- import qualified Control.Monad.Fail as Fail
+--
+-- instance Monad Foo where
+--   (>>=) = {- ...bind impl... -}
+--
+--   -- Provide legacy 'fail' implementation for when
+--   -- new-style MonadFail desugaring is not enabled.
+--   fail = Fail.fail
+--
+-- instance Fail.MonadFail Foo where
+--   fail = {- ...fail implementation... -}
+-- @
+--
+-- See <https://wiki.haskell.org/MonadFail_Proposal> for more details.
+--
+-- @since 4.9.0.0
+--
+module Control.Monad.Fail ( MonadFail(fail) ) where
+
+import GHC.Base (String, Monad(), Maybe(Nothing), IO())
+import {-# SOURCE #-} GHC.IO (failIO)
+
+-- | When a value is bound in @do at -notation, the pattern on the left
+-- hand side of @<-@ might not match. In this case, this class
+-- provides a function to recover.
+--
+-- A 'Monad' without a 'MonadFail' instance may only be used in conjunction
+-- with pattern that always match, such as newtypes, tuples, data types with
+-- only a single data constructor, and irrefutable patterns (@~pat@).
+--
+-- Instances of 'MonadFail' should satisfy the following law: @fail s@ should
+-- be a left zero for '>>=',
+--
+-- @
+-- fail s >>= f  =  fail s
+-- @
+--
+-- If your 'Monad' is also 'MonadPlus', a popular definition is
+--
+-- @
+-- fail _ = mzero
+-- @
+--
+-- @since 4.9.0.0
+class Monad m => MonadFail m where
+    fail :: String -> m a
+
+
+instance MonadFail Maybe where
+    fail _ = Nothing
+
+instance MonadFail [] where
+    {-# INLINE fail #-}
+    fail _ = []
+
+instance MonadFail IO where
+    fail = failIO
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 273950b..619acac 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -479,6 +479,11 @@ class Applicative m => Monad m where
     -- | Fail with a message.  This operation is not part of the
     -- mathematical definition of a monad, but is invoked on pattern-match
     -- failure in a @do@ expression.
+    --
+    -- As part of the MonadFail proposal (MFP), this function is moved
+    -- to its own class 'MonadFail' (see "Control.Monad.Fail" for more
+    -- details). The definition here will be removed in a future
+    -- release.
     fail        :: String -> m a
     fail s      = error s
 
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 9354d04..d98e7bf 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -113,6 +113,7 @@ Library
         Control.Exception
         Control.Exception.Base
         Control.Monad
+        Control.Monad.Fail
         Control.Monad.Fix
         Control.Monad.Instances
         Control.Monad.IO.Class
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index de687c6..fe65399 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -62,6 +62,9 @@
   * New module `Control.Monad.IO.Class` (previously provided by `transformers`
     package). (#10773)
 
+  * New module `Control.Monad.Fail` providing new `MonadFail(fail)`
+    class (#10751)
+
   * The `Generic` instance for `Proxy` is now poly-kinded (#10775)
 
   * add `Data.List.NonEmpty` and `Data.Semigroup` (to become



More information about the ghc-commits mailing list