[Git][ghc/ghc][master] Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Jun 17 14:03:04 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)
Use runHsc' in runHsc so that both functions can't fall out of sync
We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.
- - - - -
2 changed files:
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Main.hs
Changes:
=====================================
compiler/GHC/Driver/Env.hs
=====================================
@@ -86,8 +86,8 @@ import qualified Data.Set as Set
import GHC.Unit.Module.Graph
runHsc :: HscEnv -> Hsc a -> IO a
-runHsc hsc_env (Hsc hsc) = do
- (a, w) <- hsc hsc_env emptyMessages
+runHsc hsc_env hsc = do
+ (a, w) <- runHsc' hsc_env hsc
let dflags = hsc_dflags hsc_env
let !diag_opts = initDiagOpts dflags
!print_config = initPrintConfig dflags
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -64,6 +64,7 @@ module GHC.Driver.Main
, hscRecompStatus
, hscParse
, hscTypecheckRename
+ , hscTypecheckRenameWithDiagnostics
, hscTypecheckAndGetWarnings
, hscDesugar
, makeSimpleDetails
@@ -642,7 +643,14 @@ extract_renamed_stuff mod_summary tc_result = do
-- | Rename and typecheck a module, additionally returning the renamed syntax
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule
-> IO (TcGblEnv, RenamedStuff)
-hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $
+hscTypecheckRename hsc_env mod_summary rdr_module =
+ fst <$> hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module
+
+-- | Rename and typecheck a module, additionally returning the renamed syntax
+-- and the diagnostics produced.
+hscTypecheckRenameWithDiagnostics :: HscEnv -> ModSummary -> HsParsedModule
+ -> IO ((TcGblEnv, RenamedStuff), Messages GhcMessage)
+hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module = runHsc' hsc_env $
hsc_typecheck True mod_summary (Just rdr_module)
-- | Do Typechecking without throwing SourceError exception with -Werror
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e7a956623b7d71e50fa86fee83459d2611c423b8
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e7a956623b7d71e50fa86fee83459d2611c423b8
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/20240617/0ceff0e0/attachment-0001.html>
More information about the ghc-commits
mailing list