[commit: ghc] wip/final-mfp: base: Remove `Monad(fail)` method and reexport `MonadFail(fail)` instead (957edc8)

git at git.haskell.org git at git.haskell.org
Sun Mar 3 19:56:08 UTC 2019


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

On branch  : wip/final-mfp
Link       : http://ghc.haskell.org/trac/ghc/changeset/957edc8337ccb9d761af393cf61adc80190bc374/ghc

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

commit 957edc8337ccb9d761af393cf61adc80190bc374
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Nov 10 01:12:52 2018 +0100

    base: Remove `Monad(fail)` method and reexport `MonadFail(fail)` instead
    
    As per https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail


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

957edc8337ccb9d761af393cf61adc80190bc374
 libraries/base/Control/Monad.hs                   |  4 +++-
 libraries/base/Control/Monad/ST/Lazy/Imp.hs       |  3 ---
 libraries/base/GHC/Base.hs                        | 16 ----------------
 libraries/base/GHC/Conc/Sync.hs                   |  2 +-
 libraries/base/GHC/TopHandler.hs                  |  2 +-
 libraries/base/Prelude.hs                         |  3 ++-
 libraries/base/System/IO.hs                       |  2 +-
 libraries/base/Text/ParserCombinators/ReadP.hs    |  3 ---
 libraries/base/Text/ParserCombinators/ReadPrec.hs |  1 -
 libraries/base/base.cabal                         |  4 ++--
 10 files changed, 10 insertions(+), 30 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index fbdb99e..a0d4284 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -19,7 +19,8 @@ module Control.Monad
     -- * Functor and monad classes
 
       Functor(fmap)
-    , Monad((>>=), (>>), return, fail)
+    , Monad((>>=), (>>), return)
+    , MonadFail(fail)
     , MonadPlus(mzero, mplus)
     -- * Functions
 
@@ -75,6 +76,7 @@ module Control.Monad
     , (<$!>)
     ) where
 
+import Control.Monad.Fail ( MonadFail(fail) )
 import Data.Foldable ( Foldable, sequence_, sequenceA_, msum, mapM_, foldlM, forM_ )
 import Data.Functor ( void, (<$>) )
 import Data.Traversable ( forM, mapM, traverse, sequence, sequenceA )
diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
index f8d35b9..5bb1a06 100644
--- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
@@ -180,9 +180,6 @@ instance Applicative (ST s) where
 
 -- | @since 2.01
 instance Monad (ST s) where
-
-    fail s   = errorWithoutStackTrace s
-
     (>>) = (*>)
 
     m >>= k = ST $ \ s ->
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 6b606d3..60a485c 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -664,17 +664,6 @@ class Applicative m => Monad m where
     return      :: a -> m a
     return      = pure
 
-    -- | 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 'Control.Monad.MonadFail' (see "Control.Monad.Fail" for
-    -- more details). The definition here will be removed in a future
-    -- release.
-    fail        :: String -> m a
-    fail s      = errorWithoutStackTrace s
-
 {- Note [Recursive bindings for Applicative/Monad]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
@@ -855,8 +844,6 @@ instance  Monad Maybe  where
 
     (>>) = (*>)
 
-    fail _              = Nothing
-
 -- -----------------------------------------------------------------------------
 -- The Alternative class definition
 
@@ -984,8 +971,6 @@ instance Monad []  where
     xs >>= f             = [y | x <- xs, y <- f x]
     {-# INLINE (>>) #-}
     (>>) = (*>)
-    {-# INLINE fail #-}
-    fail _              = []
 
 -- | @since 2.01
 instance Alternative [] where
@@ -1365,7 +1350,6 @@ instance  Monad IO  where
     {-# INLINE (>>=)  #-}
     (>>)      = (*>)
     (>>=)     = bindIO
-    fail s    = failIO s
 
 -- | @since 4.9.0.0
 instance Alternative IO where
diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs
index 7038b0d..5c3e63a 100644
--- a/libraries/base/GHC/Conc/Sync.hs
+++ b/libraries/base/GHC/Conc/Sync.hs
@@ -367,7 +367,7 @@ to avoid contention with other processes in the machine.
 -}
 setNumCapabilities :: Int -> IO ()
 setNumCapabilities i
-  | i <= 0    = fail $ "setNumCapabilities: Capability count ("++show i++") must be positive"
+  | i <= 0    = failIO $ "setNumCapabilities: Capability count ("++show i++") must be positive"
   | otherwise = c_setNumCapabilities (fromIntegral i)
 
 foreign import ccall safe "setNumCapabilities"
diff --git a/libraries/base/GHC/TopHandler.hs b/libraries/base/GHC/TopHandler.hs
index d988369..bb358a3 100644
--- a/libraries/base/GHC/TopHandler.hs
+++ b/libraries/base/GHC/TopHandler.hs
@@ -241,7 +241,7 @@ safeExit = exitHelper useSafeExit
 fastExit = exitHelper useFastExit
 
 unreachable :: IO a
-unreachable = fail "If you can read this, shutdownHaskellAndExit did not exit."
+unreachable = failIO "If you can read this, shutdownHaskellAndExit did not exit."
 
 exitHelper :: CInt -> Int -> IO a
 #if defined(mingw32_HOST_OS)
diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs
index 15e392f..f7b2fd9 100644
--- a/libraries/base/Prelude.hs
+++ b/libraries/base/Prelude.hs
@@ -73,7 +73,8 @@ module Prelude (
     -- ** Monads and functors
     Functor(fmap, (<$)), (<$>),
     Applicative(pure, (<*>), (*>), (<*)),
-    Monad((>>=), (>>), return, fail),
+    Monad((>>=), (>>), return),
+    MonadFail(fail),
     mapM_, sequence_, (=<<),
 
     -- ** Folds and traversals
diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs
index 1fc39be..08416ff 100644
--- a/libraries/base/System/IO.hs
+++ b/libraries/base/System/IO.hs
@@ -485,7 +485,7 @@ openTempFile' :: String -> FilePath -> String -> Bool -> CMode
               -> IO (FilePath, Handle)
 openTempFile' loc tmp_dir template binary mode
     | pathSeparator template
-    = fail $ "openTempFile': Template string must not contain path separator characters: "++template
+    = failIO $ "openTempFile': Template string must not contain path separator characters: "++template
     | otherwise = findTempName
   where
     -- We split off the last extension, so we can use .foo.ext files
diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs
index e28f32d..e6dcab5 100644
--- a/libraries/base/Text/ParserCombinators/ReadP.hs
+++ b/libraries/base/Text/ParserCombinators/ReadP.hs
@@ -120,8 +120,6 @@ instance Monad P where
   (Result x p)    >>= k = k x <|> (p >>= k)
   (Final (r:|rs)) >>= k = final [ys' | (x,s) <- (r:rs), ys' <- run (k x) s]
 
-  fail _ = Fail
-
 -- | @since 4.9.0.0
 instance MonadFail P where
   fail _ = Fail
@@ -177,7 +175,6 @@ instance Applicative ReadP where
 
 -- | @since 2.01
 instance Monad ReadP where
-  fail _    = R (\_ -> Fail)
   R m >>= f = R (\k -> m (\a -> let R m' = f a in m' k))
 
 -- | @since 4.9.0.0
diff --git a/libraries/base/Text/ParserCombinators/ReadPrec.hs b/libraries/base/Text/ParserCombinators/ReadPrec.hs
index 2b30fe0..df77045 100644
--- a/libraries/base/Text/ParserCombinators/ReadPrec.hs
+++ b/libraries/base/Text/ParserCombinators/ReadPrec.hs
@@ -85,7 +85,6 @@ instance Applicative ReadPrec where
 
 -- | @since 2.01
 instance Monad ReadPrec where
-  fail s    = P (\_ -> fail s)
   P f >>= k = P (\n -> do a <- f n; let P f' = k a in f' n)
 
 -- | @since 4.9.0.0
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 4e809e7..a2c9164 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -1,6 +1,6 @@
-cabal-version:  2.1
+cabal-version:  2.2
 name:           base
-version:        4.12.0.0
+version:        4.13.0.0
 -- NOTE: Don't forget to update ./changelog.md
 
 license:        BSD-3-Clause



More information about the ghc-commits mailing list