Skip to content
Snippets Groups Projects
Commit a514d52d authored by Dylan Thinnes's avatar Dylan Thinnes
Browse files

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.
parent bd95553a
No related merge requests found
Pipeline #96855 passed
......@@ -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
......
......@@ -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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment