[Git][ghc/ghc][master] Add MonadFail instance for ParserM

Marge Bot gitlab at gitlab.haskell.org
Mon Jun 24 05:12:25 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
581cbc28 by Erik de Castro Lopo at 2019-06-24T05:12:22Z
Add MonadFail instance for ParserM

- - - - -


1 changed file:

- utils/genprimopcode/ParserM.hs


Changes:

=====================================
utils/genprimopcode/ParserM.hs
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
 module ParserM (
     -- Parser Monad
     ParserM(..), AlexInput, run_parser,
@@ -18,7 +19,13 @@ module ParserM (
  ) where
 
 import Control.Applicative
+
+#if __GLASGOW_HASKELL__ >= 806
+import Prelude hiding (fail)
+import Control.Monad.Fail (MonadFail (..))
+#else
 import Prelude
+#endif
 
 import Control.Monad (ap, liftM)
 import Data.Word (Word8)
@@ -42,6 +49,10 @@ instance Monad ParserM where
                                             Left err ->
                                                 Left err
     return a = ParserM $ \i s -> Right (i, s, a)
+
+#if __GLASGOW_HASKELL__ >= 806
+instance MonadFail ParserM where
+#endif
     fail err = ParserM $ \_ _ -> Left err
 
 run_parser :: ParserM a -> (String -> Either String a)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/581cbc28e143a4ed8e7f794ed1618161222a5646

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/581cbc28e143a4ed8e7f794ed1618161222a5646
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190624/58b9cf7e/attachment-0001.html>


More information about the ghc-commits mailing list