summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlfredo Di Napoli <alfredo@well-typed.com>2021-06-30 15:17:46 +0200
committerAlfredo Di Napoli <alfredo@well-typed.com>2021-07-08 08:13:23 +0200
commit56eb57a6b348d44370fc84f6a35caabd1c548b5e (patch)
treebe873cadaa3f9ec47c41546d2577d61810038313
parent5a31abe3544c21d0b45d264ea68f89bbb108251d (diff)
downloadhaskell-wip/adinapoli-issue-19920.tar.gz
Rename getErrorMessages and getMessages function in parser codewip/adinapoli-issue-19920
This commit renames the `getErrorMessages` and `getMessages` function in the parser code to `getPsErrorMessages` and `getPsMessages`, to avoid import conflicts, as we have already `getErrorMessages` and `getMessages` defined in `GHC.Types.Error`. Fixes #19920. Update haddock submodule
-rw-r--r--compiler/GHC.hs10
-rw-r--r--compiler/GHC/Cmm/Parser.y4
-rw-r--r--compiler/GHC/Driver/Backpack.hs2
-rw-r--r--compiler/GHC/Driver/Main.hs13
-rw-r--r--compiler/GHC/Parser/Header.hs6
-rw-r--r--compiler/GHC/Parser/Lexer.x20
-rw-r--r--utils/check-exact/Main.hs2
-rw-r--r--utils/check-exact/Parsers.hs8
-rw-r--r--utils/check-exact/Preprocess.hs4
m---------utils/haddock0
10 files changed, 34 insertions, 35 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs
index 2b5f3e06d5..ea1293f2a8 100644
--- a/compiler/GHC.hs
+++ b/compiler/GHC.hs
@@ -381,7 +381,7 @@ import GHC.Types.Name.Set
import GHC.Types.Name.Reader
import GHC.Types.SourceError
import GHC.Types.SafeHaskell
-import GHC.Types.Error hiding ( getMessages, getErrorMessages )
+import GHC.Types.Error
import GHC.Types.Fixity
import GHC.Types.Target
import GHC.Types.Basic
@@ -1583,7 +1583,7 @@ getTokenStream mod = do
let startLoc = mkRealSrcLoc (mkFastString sourceFile) 1 1
case lexTokenStream (initParserOpts dflags) source startLoc of
POk _ ts -> return ts
- PFailed pst -> throwErrors (GhcPsMessage <$> getErrorMessages pst)
+ PFailed pst -> throwErrors (GhcPsMessage <$> getPsErrorMessages pst)
-- | Give even more information on the source than 'getTokenStream'
-- This function allows reconstructing the source completely with
@@ -1594,7 +1594,7 @@ getRichTokenStream mod = do
let startLoc = mkRealSrcLoc (mkFastString sourceFile) 1 1
case lexTokenStream (initParserOpts dflags) source startLoc of
POk _ ts -> return $ addSourceToTokens startLoc source ts
- PFailed pst -> throwErrors (GhcPsMessage <$> getErrorMessages pst)
+ PFailed pst -> throwErrors (GhcPsMessage <$> getPsErrorMessages pst)
-- | Given a source location and a StringBuffer corresponding to this
-- location, return a rich token stream with the source associated to the
@@ -1773,11 +1773,11 @@ parser str dflags filename =
case unP Parser.parseModule (initParserState (initParserOpts dflags) buf loc) of
PFailed pst ->
- let (warns,errs) = getMessages pst in
+ let (warns,errs) = getPsMessages pst in
(GhcPsMessage <$> warns, Left $ GhcPsMessage <$> errs)
POk pst rdr_module ->
- let (warns,_) = getMessages pst in
+ let (warns,_) = getPsMessages pst in
(GhcPsMessage <$> warns, Right rdr_module)
-- -----------------------------------------------------------------------------
diff --git a/compiler/GHC/Cmm/Parser.y b/compiler/GHC/Cmm/Parser.y
index a26fb4edba..712a7a5e8a 100644
--- a/compiler/GHC/Cmm/Parser.y
+++ b/compiler/GHC/Cmm/Parser.y
@@ -1509,7 +1509,7 @@ parseCmmFile dflags this_mod home_unit filename = do
-- in there we don't want.
case unPD cmmParse dflags home_unit init_state of
PFailed pst -> do
- let (warnings,errors) = getMessages pst
+ let (warnings,errors) = getPsMessages pst
return (warnings, errors, Nothing)
POk pst code -> do
st <- initC
@@ -1520,7 +1520,7 @@ parseCmmFile dflags this_mod home_unit filename = do
((), cmm2) <- getCmm $ mapM_ emitInfoTableProv used_info
return (cmm ++ cmm2, used_info)
(cmm, _) = runC dflags no_module st fcode
- (warnings,errors) = getMessages pst
+ (warnings,errors) = getPsMessages pst
if not (isEmptyMessages errors)
then return (warnings, errors, Nothing)
else return (warnings, errors, Just cmm)
diff --git a/compiler/GHC/Driver/Backpack.hs b/compiler/GHC/Driver/Backpack.hs
index d366d7f904..2190bdd753 100644
--- a/compiler/GHC/Driver/Backpack.hs
+++ b/compiler/GHC/Driver/Backpack.hs
@@ -107,7 +107,7 @@ doBackpack [src_filename] = do
buf <- liftIO $ hGetStringBuffer src_filename
let loc = mkRealSrcLoc (mkFastString src_filename) 1 1 -- TODO: not great
case unP parseBackpack (initParserState (initParserOpts dflags) buf loc) of
- PFailed pst -> throwErrors (GhcPsMessage <$> getErrorMessages pst)
+ PFailed pst -> throwErrors (GhcPsMessage <$> getPsErrorMessages pst)
POk _ pkgname_bkp -> do
-- OK, so we have an LHsUnit PackageName, but we want an
-- LHsUnit HsComponentId. So let's rename it.
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index 3d55e77191..0ee84f7ca8 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -193,8 +193,7 @@ import GHC.Types.SourceError
import GHC.Types.SafeHaskell
import GHC.Types.ForeignStubs
import GHC.Types.Var.Env ( emptyTidyEnv )
-import GHC.Types.Error hiding ( getMessages )
-import qualified GHC.Types.Error as Error.Types
+import GHC.Types.Error
import GHC.Types.Fixity.Env
import GHC.Types.CostCentre
import GHC.Types.IPE
@@ -413,9 +412,9 @@ hscParse' mod_summary
case unP parseMod (initParserState (initParserOpts dflags) buf loc) of
PFailed pst ->
- handleWarningsThrowErrors (getMessages pst)
+ handleWarningsThrowErrors (getPsMessages pst)
POk pst rdr_module -> do
- let (warns, errs) = getMessages pst
+ let (warns, errs) = getPsMessages pst
logDiagnostics (GhcPsMessage <$> warns)
liftIO $ putDumpFileMaybe logger Opt_D_dump_parsed "Parser"
FormatHaskell (ppr rdr_module)
@@ -1478,7 +1477,7 @@ markUnsafeInfer tcg_env whyUnsafe = do
whyUnsafe' df = vcat [ quotes pprMod <+> text "has been inferred as unsafe!"
, text "Reason:"
, nest 4 $ (vcat $ badFlags df) $+$
- (vcat $ pprMsgEnvelopeBagWithLoc (Error.Types.getMessages whyUnsafe)) $+$
+ (vcat $ pprMsgEnvelopeBagWithLoc (getMessages whyUnsafe)) $+$
(vcat $ badInsts $ tcg_insts tcg_env)
]
badFlags df = concatMap (badFlag df) unsafeFlagsForInfer
@@ -2129,9 +2128,9 @@ hscParseThingWithLocation source linenumber parser str = do
case unP parser (initParserState (initParserOpts dflags) buf loc) of
PFailed pst ->
- handleWarningsThrowErrors (getMessages pst)
+ handleWarningsThrowErrors (getPsMessages pst)
POk pst thing -> do
- logWarningsReportErrors (getMessages pst)
+ logWarningsReportErrors (getPsMessages pst)
liftIO $ putDumpFileMaybe logger Opt_D_dump_parsed "Parser"
FormatHaskell (ppr thing)
liftIO $ putDumpFileMaybe logger Opt_D_dump_parsed_ast "Parser AST"
diff --git a/compiler/GHC/Parser/Header.hs b/compiler/GHC/Parser/Header.hs
index 2037f6bc48..65e09bfeff 100644
--- a/compiler/GHC/Parser/Header.hs
+++ b/compiler/GHC/Parser/Header.hs
@@ -33,7 +33,7 @@ import GHC.Hs
import GHC.Unit.Module
import GHC.Builtin.Names
-import GHC.Types.Error hiding ( getErrorMessages, getWarningMessages, getMessages )
+import GHC.Types.Error
import GHC.Types.SrcLoc
import GHC.Types.SourceError
import GHC.Types.SourceText
@@ -83,9 +83,9 @@ getImports popts implicit_prelude buf filename source_filename = do
case unP parseHeader (initParserState popts buf loc) of
PFailed pst ->
-- assuming we're not logging warnings here as per below
- return $ Left $ getErrorMessages pst
+ return $ Left $ getPsErrorMessages pst
POk pst rdr_module -> fmap Right $ do
- let (_warns, errs) = getMessages pst
+ let (_warns, errs) = getPsMessages pst
-- don't log warnings: they'll be reported when we parse the file
-- for real. See #2500.
if not (isEmptyMessages errs)
diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x
index 8771b4ecf4..6c7a12395a 100644
--- a/compiler/GHC/Parser/Lexer.x
+++ b/compiler/GHC/Parser/Lexer.x
@@ -62,7 +62,7 @@ module GHC.Parser.Lexer (
MonadP(..),
getRealSrcLoc, getPState,
failMsgP, failLocMsgP, srcParseFail,
- getErrorMessages, getMessages,
+ getPsErrorMessages, getPsMessages,
popContext, pushModuleContext, setLastToken, setSrcLoc,
activeContext, nextIsEOF,
getLexState, popLexState, pushLexState,
@@ -109,7 +109,7 @@ import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Data.StringBuffer
import GHC.Data.FastString
-import GHC.Types.Error hiding ( getErrorMessages, getMessages )
+import GHC.Types.Error
import GHC.Types.Unique.FM
import GHC.Data.Maybe
import GHC.Data.OrdList
@@ -2296,7 +2296,7 @@ data LayoutContext
newtype ParseResult a = PR (# (# PState, a #) | PState #)
-- | The parser has consumed a (possibly empty) prefix of the input and produced
--- a result. Use 'getMessages' to check for accumulated warnings and non-fatal
+-- a result. Use 'getPsMessages' to check for accumulated warnings and non-fatal
-- errors.
--
-- The carried parsing state can be used to resume parsing.
@@ -2306,8 +2306,8 @@ pattern POk s a = PR (# (# s , a #) | #)
-- | The parser has consumed a (possibly empty) prefix of the input and failed.
--
-- The carried parsing state can be used to resume parsing. It is the state
--- right before failure, including the fatal parse error. 'getMessages' and
--- 'getErrorMessages' must return a non-empty bag of errors.
+-- right before failure, including the fatal parse error. 'getPsMessages' and
+-- 'getPsErrorMessages' must return a non-empty bag of errors.
pattern PFailed :: PState -> ParseResult a
pattern PFailed s = PR (# | s #)
@@ -2922,7 +2922,7 @@ class Monad m => MonadP m where
addError :: MsgEnvelope PsMessage -> m ()
-- | Add a warning to the accumulator.
- -- Use 'getMessages' to get the accumulated warnings.
+ -- Use 'getPsMessages' to get the accumulated warnings.
addWarning :: MsgEnvelope PsMessage -> m ()
-- | Add a fatal error. This will be the last error reported by the parser, and
@@ -3008,13 +3008,13 @@ addTabWarning srcspan
-- | Get a bag of the errors that have been accumulated so far.
-- Does not take -Werror into account.
-getErrorMessages :: PState -> Messages PsMessage
-getErrorMessages p = errors p
+getPsErrorMessages :: PState -> Messages PsMessage
+getPsErrorMessages p = errors p
-- | Get the warnings and errors accumulated so far.
-- Does not take -Werror into account.
-getMessages :: PState -> (Messages PsMessage, Messages PsMessage)
-getMessages p =
+getPsMessages :: PState -> (Messages PsMessage, Messages PsMessage)
+getPsMessages p =
let ws = warnings p
diag_opts = pDiagOpts (options p)
-- we add the tabulation warning on the fly because
diff --git a/utils/check-exact/Main.hs b/utils/check-exact/Main.hs
index 2034808362..0d79249398 100644
--- a/utils/check-exact/Main.hs
+++ b/utils/check-exact/Main.hs
@@ -30,7 +30,7 @@ import ExactPrint
import Transform
import Parsers
-import GHC.Parser.Lexer hiding (getMessages)
+import GHC.Parser.Lexer
import GHC.Data.FastString
import GHC.Types.SrcLoc
diff --git a/utils/check-exact/Parsers.hs b/utils/check-exact/Parsers.hs
index a42bba42cd..cff37bf309 100644
--- a/utils/check-exact/Parsers.hs
+++ b/utils/check-exact/Parsers.hs
@@ -76,7 +76,7 @@ parseWith :: GHC.DynFlags
parseWith dflags fileName parser s =
case runParser parser dflags fileName s of
GHC.PFailed pst
- -> Left (GHC.GhcPsMessage <$> GHC.getErrorMessages pst)
+ -> Left (GHC.GhcPsMessage <$> GHC.getPsErrorMessages pst)
GHC.POk _ pmod
-> Right pmod
@@ -90,7 +90,7 @@ parseWithECP :: (GHC.DisambECP w)
parseWithECP dflags fileName parser s =
case runParser (parser >>= \p -> GHC.runPV $ GHC.unECP p) dflags fileName s of
GHC.PFailed pst
- -> Left (GHC.GhcPsMessage <$> GHC.getErrorMessages pst)
+ -> Left (GHC.GhcPsMessage <$> GHC.getPsErrorMessages pst)
GHC.POk _ pmod
-> Right pmod
@@ -185,7 +185,7 @@ parseModuleFromStringInternal dflags fileName str =
let (str1, lp) = stripLinePragmas str
res = case runParser GHC.parseModule dflags fileName str1 of
GHC.PFailed pst
- -> Left (GHC.GhcPsMessage <$> GHC.getErrorMessages pst)
+ -> Left (GHC.GhcPsMessage <$> GHC.getPsErrorMessages pst)
GHC.POk _ pmod
-> Right (lp, dflags, pmod)
in postParseTransform res
@@ -258,7 +258,7 @@ parseModuleEpAnnsWithCppInternal cppOptions dflags file = do
return $
case parseFile dflags' file fileContents of
GHC.PFailed pst
- -> Left (GHC.GhcPsMessage <$> GHC.getErrorMessages pst)
+ -> Left (GHC.GhcPsMessage <$> GHC.getPsErrorMessages pst)
GHC.POk _ pmod
-> Right $ (injectedComments, dflags', fixModuleTrailingComments pmod)
diff --git a/utils/check-exact/Preprocess.hs b/utils/check-exact/Preprocess.hs
index 9d7e883aad..f95668141c 100644
--- a/utils/check-exact/Preprocess.hs
+++ b/utils/check-exact/Preprocess.hs
@@ -24,7 +24,7 @@ import qualified GHC.Driver.Errors.Types as GHC
import qualified GHC.Driver.Phases as GHC
import qualified GHC.Driver.Pipeline as GHC
import qualified GHC.Fingerprint.Type as GHC
-import qualified GHC.Parser.Lexer as GHC hiding (getMessages)
+import qualified GHC.Parser.Lexer as GHC
import qualified GHC.Settings as GHC
import qualified GHC.Types.Error as GHC (getMessages)
import qualified GHC.Types.SourceError as GHC
@@ -283,7 +283,7 @@ parseError pst = do
let
-- (warns,errs) = GHC.getMessages pst dflags
-- throw $ GHC.mkSrcErr (GHC.unitBag $ GHC.mkPlainErrMsg dflags sspan err)
- GHC.throwErrors $ (GHC.GhcPsMessage <$> GHC.getErrorMessages pst)
+ GHC.throwErrors $ (GHC.GhcPsMessage <$> GHC.getPsErrorMessages pst)
-- ---------------------------------------------------------------------
diff --git a/utils/haddock b/utils/haddock
-Subproject f7059f84687a6aac37405c428a97190662de1da
+Subproject 32d280f30d73bb38769700be6ddaf26b9a69c77