Skip to content

Commit 2012170

Browse files
authored
Merge branch 'master' into wip/clear_mi_globals
2 parents 3395615 + ff28990 commit 2012170

File tree

9 files changed

+146
-86
lines changed

9 files changed

+146
-86
lines changed

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 22 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -171,11 +171,11 @@ typecheckModule :: IdeDefer
171171
typecheckModule (IdeDefer defer) hsc tc_helpers pm = do
172172
let modSummary = pm_mod_summary pm
173173
dflags = ms_hspp_opts modSummary
174-
mmodSummary' <- catchSrcErrors (hsc_dflags hsc) "typecheck (initialize plugins)"
174+
initialized <- catchSrcErrors (hsc_dflags hsc) "typecheck (initialize plugins)"
175175
(initPlugins hsc modSummary)
176-
case mmodSummary' of
176+
case initialized of
177177
Left errs -> return (errs, Nothing)
178-
Right modSummary' -> do
178+
Right (modSummary', hsc) -> do
179179
(warnings, etcm) <- withWarnings "typecheck" $ \tweak ->
180180
let
181181
session = tweak (hscSetFlags dflags hsc)
@@ -482,7 +482,7 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
482482
Nothing
483483
#endif
484484

485-
#else
485+
#else
486486
let !partial_iface = force (mkPartialIface session details simplified_guts)
487487
final_iface' <- mkFullIface session partial_iface
488488
#endif
@@ -574,11 +574,6 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
574574
. (("Error during " ++ T.unpack source) ++) . show @SomeException
575575
]
576576

577-
initPlugins :: HscEnv -> ModSummary -> IO ModSummary
578-
initPlugins session modSummary = do
579-
session1 <- liftIO $ initializePlugins (hscSetFlags (ms_hspp_opts modSummary) session)
580-
return modSummary{ms_hspp_opts = hsc_dflags session1}
581-
582577
-- | Whether we should run the -O0 simplifier when generating core.
583578
--
584579
-- This is required for template Haskell to work but we disable this in DAML.
@@ -1106,7 +1101,9 @@ getModSummaryFromImports
11061101
-> Maybe Util.StringBuffer
11071102
-> ExceptT [FileDiagnostic] IO ModSummaryResult
11081103
getModSummaryFromImports env fp modTime contents = do
1109-
(contents, opts, dflags) <- preprocessor env fp contents
1104+
(contents, opts, env) <- preprocessor env fp contents
1105+
1106+
let dflags = hsc_dflags env
11101107

11111108
-- The warns will hopefully be reported when we actually parse the module
11121109
(_warns, L main_loc hsmod) <- parseHeader dflags fp contents
@@ -1165,9 +1162,9 @@ getModSummaryFromImports env fp modTime contents = do
11651162
then mkHomeModLocation dflags (pathToModuleName fp) fp
11661163
else mkHomeModLocation dflags mod fp
11671164

1168-
let modl = mkHomeModule (hscHomeUnit (hscSetFlags dflags env)) mod
1165+
let modl = mkHomeModule (hscHomeUnit env) mod
11691166
sourceType = if "-boot" `isSuffixOf` takeExtension fp then HsBootFile else HsSrcFile
1170-
msrModSummary =
1167+
msrModSummary2 =
11711168
ModSummary
11721169
{ ms_mod = modl
11731170
, ms_hie_date = Nothing
@@ -1192,7 +1189,8 @@ getModSummaryFromImports env fp modTime contents = do
11921189
, ms_textual_imps = textualImports
11931190
}
11941191

1195-
msrFingerprint <- liftIO $ computeFingerprint opts msrModSummary
1192+
msrFingerprint <- liftIO $ computeFingerprint opts msrModSummary2
1193+
(msrModSummary, msrHscEnv) <- liftIO $ initPlugins env msrModSummary2
11961194
return ModSummaryResult{..}
11971195
where
11981196
-- Compute a fingerprint from the contents of `ModSummary`,
@@ -1233,7 +1231,7 @@ parseHeader dflags filename contents = do
12331231
PFailedWithErrorMessages msgs ->
12341232
throwE $ diagFromErrMsgs "parser" dflags $ msgs dflags
12351233
POk pst rdr_module -> do
1236-
let (warns, errs) = getMessages' pst dflags
1234+
let (warns, errs) = renderMessages $ getPsMessages pst dflags
12371235

12381236
-- Just because we got a `POk`, it doesn't mean there
12391237
-- weren't errors! To clarify, the GHC parser
@@ -1268,9 +1266,18 @@ parseFileContents env customPreprocessor filename ms = do
12681266
POk pst rdr_module ->
12691267
let
12701268
hpm_annotations = mkApiAnns pst
1271-
(warns, errs) = getMessages' pst dflags
1269+
psMessages = getPsMessages pst dflags
12721270
in
12731271
do
1272+
let IdePreprocessedSource preproc_warns errs parsed = customPreprocessor rdr_module
1273+
1274+
unless (null errs) $
1275+
throwE $ diagFromStrings "parser" DsError errs
1276+
1277+
let preproc_warnings = diagFromStrings "parser" DsWarning preproc_warns
1278+
(parsed', msgs) <- liftIO $ applyPluginsParsedResultAction env dflags ms hpm_annotations parsed psMessages
1279+
let (warns, errs) = renderMessages msgs
1280+
12741281
-- Just because we got a `POk`, it doesn't mean there
12751282
-- weren't errors! To clarify, the GHC parser
12761283
-- distinguishes between fatal and non-fatal
@@ -1283,14 +1290,6 @@ parseFileContents env customPreprocessor filename ms = do
12831290
unless (null errs) $
12841291
throwE $ diagFromErrMsgs "parser" dflags errs
12851292

1286-
-- Ok, we got here. It's safe to continue.
1287-
let IdePreprocessedSource preproc_warns errs parsed = customPreprocessor rdr_module
1288-
1289-
unless (null errs) $
1290-
throwE $ diagFromStrings "parser" DsError errs
1291-
1292-
let preproc_warnings = diagFromStrings "parser" DsWarning preproc_warns
1293-
parsed' <- liftIO $ applyPluginsParsedResultAction env dflags ms hpm_annotations parsed
12941293

12951294
-- To get the list of extra source files, we take the list
12961295
-- that the parser gave us,

ghcide/src/Development/IDE/Core/Preprocessor.hs

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -36,30 +36,30 @@ import GHC.Utils.Outputable (renderWithContext)
3636

3737
-- | Given a file and some contents, apply any necessary preprocessors,
3838
-- e.g. unlit/cpp. Return the resulting buffer and the DynFlags it implies.
39-
preprocessor :: HscEnv -> FilePath -> Maybe Util.StringBuffer -> ExceptT [FileDiagnostic] IO (Util.StringBuffer, [String], DynFlags)
40-
preprocessor env0 filename mbContents = do
39+
preprocessor :: HscEnv -> FilePath -> Maybe Util.StringBuffer -> ExceptT [FileDiagnostic] IO (Util.StringBuffer, [String], HscEnv)
40+
preprocessor env filename mbContents = do
4141
-- Perform unlit
4242
(isOnDisk, contents) <-
4343
if isLiterate filename then do
44-
newcontent <- liftIO $ runLhs env0 filename mbContents
44+
newcontent <- liftIO $ runLhs env filename mbContents
4545
return (False, newcontent)
4646
else do
4747
contents <- liftIO $ maybe (Util.hGetStringBuffer filename) return mbContents
4848
let isOnDisk = isNothing mbContents
4949
return (isOnDisk, contents)
5050

5151
-- Perform cpp
52-
(opts, dflags) <- ExceptT $ parsePragmasIntoDynFlags env0 filename contents
53-
let env1 = hscSetFlags dflags env0
54-
let logger = hsc_logger env1
55-
(isOnDisk, contents, opts, dflags) <-
52+
(opts, env) <- ExceptT $ parsePragmasIntoHscEnv env filename contents
53+
let dflags = hsc_dflags env
54+
let logger = hsc_logger env
55+
(isOnDisk, contents, opts, env) <-
5656
if not $ xopt LangExt.Cpp dflags then
57-
return (isOnDisk, contents, opts, dflags)
57+
return (isOnDisk, contents, opts, env)
5858
else do
5959
cppLogs <- liftIO $ newIORef []
6060
let newLogger = pushLogHook (const (logActionCompat $ logAction cppLogs)) logger
6161
contents <- ExceptT
62-
$ (Right <$> (runCpp (putLogHook newLogger env1) filename
62+
$ (Right <$> (runCpp (putLogHook newLogger env) filename
6363
$ if isOnDisk then Nothing else Just contents))
6464
`catch`
6565
( \(e :: Util.GhcException) -> do
@@ -68,16 +68,16 @@ preprocessor env0 filename mbContents = do
6868
[] -> throw e
6969
diags -> return $ Left diags
7070
)
71-
(opts, dflags) <- ExceptT $ parsePragmasIntoDynFlags env1 filename contents
72-
return (False, contents, opts, dflags)
71+
(opts, env) <- ExceptT $ parsePragmasIntoHscEnv env filename contents
72+
return (False, contents, opts, env)
7373

7474
-- Perform preprocessor
7575
if not $ gopt Opt_Pp dflags then
76-
return (contents, opts, dflags)
76+
return (contents, opts, env)
7777
else do
78-
contents <- liftIO $ runPreprocessor env1 filename $ if isOnDisk then Nothing else Just contents
79-
(opts, dflags) <- ExceptT $ parsePragmasIntoDynFlags env1 filename contents
80-
return (contents, opts, dflags)
78+
contents <- liftIO $ runPreprocessor env filename $ if isOnDisk then Nothing else Just contents
79+
(opts, env) <- ExceptT $ parsePragmasIntoHscEnv env filename contents
80+
return (contents, opts, env)
8181
where
8282
logAction :: IORef [CPPLog] -> LogActionCompat
8383
logAction cppLogs dflags _reason severity srcSpan _style msg = do
@@ -137,12 +137,12 @@ isLiterate x = takeExtension x `elem` [".lhs",".lhs-boot"]
137137

138138

139139
-- | This reads the pragma information directly from the provided buffer.
140-
parsePragmasIntoDynFlags
140+
parsePragmasIntoHscEnv
141141
:: HscEnv
142142
-> FilePath
143143
-> Util.StringBuffer
144-
-> IO (Either [FileDiagnostic] ([String], DynFlags))
145-
parsePragmasIntoDynFlags env fp contents = catchSrcErrors dflags0 "pragmas" $ do
144+
-> IO (Either [FileDiagnostic] ([String], HscEnv))
145+
parsePragmasIntoHscEnv env fp contents = catchSrcErrors dflags0 "pragmas" $ do
146146
#if MIN_VERSION_ghc(9,3,0)
147147
let (_warns,opts) = getOptions (initParserOpts dflags0) contents fp
148148
#else
@@ -154,7 +154,7 @@ parsePragmasIntoDynFlags env fp contents = catchSrcErrors dflags0 "pragmas" $ do
154154

155155
(dflags, _, _) <- parseDynamicFilePragma dflags0 opts
156156
hsc_env' <- initializePlugins (hscSetFlags dflags env)
157-
return (map unLoc opts, disableWarningsAsErrors (hsc_dflags hsc_env'))
157+
return (map unLoc opts, hscSetFlags (disableWarningsAsErrors $ hsc_dflags hsc_env') hsc_env')
158158
where dflags0 = hsc_dflags env
159159

160160
-- | Run (unlit) literate haskell preprocessor on a file, or buffer if set

ghcide/src/Development/IDE/Core/RuleTypes.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -155,7 +155,7 @@ data TcModuleResult = TcModuleResult
155155
, tmrTypechecked :: TcGblEnv
156156
, tmrTopLevelSplices :: Splices
157157
-- ^ Typechecked splice information
158-
, tmrDeferredError :: !Bool
158+
, tmrDeferredError :: !Bool
159159
-- ^ Did we defer any type errors for this module?
160160
, tmrRuntimeModules :: !(ModuleEnv ByteString)
161161
-- ^ Which modules did we need at runtime while compiling this file?
@@ -357,6 +357,12 @@ data ModSummaryResult = ModSummaryResult
357357
{ msrModSummary :: !ModSummary
358358
, msrImports :: [LImportDecl GhcPs]
359359
, msrFingerprint :: !Fingerprint
360+
, msrHscEnv :: !HscEnv
361+
-- ^ HscEnv for this particular ModSummary.
362+
-- Contains initialised plugins, parsed options, etc...
363+
--
364+
-- Implicit assumption: DynFlags in 'msrModSummary' are the same as
365+
-- the DynFlags in 'msrHscEnv'.
360366
}
361367

362368
instance Show ModSummaryResult where

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -253,9 +253,7 @@ getParsedModuleRule :: Recorder (WithPriority Log) -> Rules ()
253253
getParsedModuleRule recorder =
254254
-- this rule does not have early cutoff since all its dependencies already have it
255255
define (cmapWithPrio LogShake recorder) $ \GetParsedModule file -> do
256-
ModSummaryResult{msrModSummary = ms'} <- use_ GetModSummary file
257-
sess <- use_ GhcSession file
258-
let hsc = hscEnv sess
256+
ModSummaryResult{msrModSummary = ms', msrHscEnv = hsc} <- use_ GetModSummary file
259257
opt <- getIdeOptions
260258
modify_dflags <- getModifyDynFlags dynFlagsModifyParser
261259
let ms = ms' { ms_hspp_opts = modify_dflags $ ms_hspp_opts ms' }
@@ -327,16 +325,15 @@ getParsedModuleWithCommentsRule recorder =
327325
-- The parse diagnostics are owned by the GetParsedModule rule
328326
-- For this reason, this rule does not produce any diagnostics
329327
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetParsedModuleWithComments file -> do
330-
ModSummaryResult{msrModSummary = ms} <- use_ GetModSummary file
331-
sess <- use_ GhcSession file
328+
ModSummaryResult{msrModSummary = ms, msrHscEnv = hsc} <- use_ GetModSummary file
332329
opt <- getIdeOptions
333330

334331
let ms' = withoutOption Opt_Haddock $ withOption Opt_KeepRawTokenStream ms
335332
modify_dflags <- getModifyDynFlags dynFlagsModifyParser
336333
let ms = ms' { ms_hspp_opts = modify_dflags $ ms_hspp_opts ms' }
337334
reset_ms pm = pm { pm_mod_summary = ms' }
338335

339-
liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition (hscEnv sess) opt file ms
336+
liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition hsc opt file ms
340337

341338
getModifyDynFlags :: (DynFlagsModifications -> a) -> Action a
342339
getModifyDynFlags f = do

ghcide/src/Development/IDE/GHC/Compat.hs

Lines changed: 8 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,8 @@ module Development.IDE.GHC.Compat(
2626
disableWarningsAsErrors,
2727
reLoc,
2828
reLocA,
29-
getMessages',
29+
getPsMessages,
30+
renderMessages,
3031
pattern PFailedWithErrorMessages,
3132
isObjectLinkable,
3233

@@ -268,6 +269,7 @@ import GHC.Types.IPE
268269
#if MIN_VERSION_ghc(9,3,0)
269270
import GHC.Types.Error
270271
import GHC.Driver.Config.Stg.Pipeline
272+
import GHC.Driver.Plugins (PsMessages (..))
271273
#endif
272274

273275
#if !MIN_VERSION_ghc(9,3,0)
@@ -383,25 +385,13 @@ corePrepExpr _ = GHC.corePrepExpr
383385
simplifyExpr df _ = GHC.simplifyExpr df
384386
#endif
385387

386-
#if MIN_VERSION_ghc(9,2,0)
387-
type ErrMsg = MsgEnvelope DecoratedSDoc
388-
#endif
389-
#if MIN_VERSION_ghc(9,3,0)
390-
type WarnMsg = MsgEnvelope DecoratedSDoc
391-
#endif
392-
393-
getMessages' :: PState -> DynFlags -> (Bag WarnMsg, Bag ErrMsg)
394-
getMessages' pst dflags =
388+
renderMessages :: PsMessages -> (Bag WarnMsg, Bag ErrMsg)
389+
renderMessages msgs =
395390
#if MIN_VERSION_ghc(9,3,0)
396-
bimap (fmap (fmap renderDiagnosticMessageWithHints) . getMessages) (fmap (fmap renderDiagnosticMessageWithHints) . getMessages) $ getPsMessages pst
391+
let renderMsgs extractor = (fmap . fmap) renderDiagnosticMessageWithHints . getMessages $ extractor msgs
392+
in (renderMsgs psWarnings, renderMsgs psErrors)
397393
#else
398-
#if MIN_VERSION_ghc(9,2,0)
399-
bimap (fmap pprWarning) (fmap pprError) $
400-
#endif
401-
getMessages pst
402-
#if !MIN_VERSION_ghc(9,2,0)
403-
dflags
404-
#endif
394+
msgs
405395
#endif
406396

407397
#if MIN_VERSION_ghc(9,2,0)

ghcide/src/Development/IDE/GHC/Compat/Core.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -589,7 +589,7 @@ import GHC.Parser.Header hiding (getImports)
589589
#if MIN_VERSION_ghc(9,2,0)
590590
import qualified GHC.Linker.Loader as Linker
591591
import GHC.Linker.Types
592-
import GHC.Parser.Lexer hiding (initParserState)
592+
import GHC.Parser.Lexer hiding (initParserState, getPsMessages)
593593
import GHC.Parser.Annotation (EpAnn (..))
594594
import GHC.Platform.Ways
595595
import GHC.Runtime.Context (InteractiveImport (..))

ghcide/src/Development/IDE/GHC/Compat/Outputable.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,8 @@ module Development.IDE.GHC.Compat.Outputable (
2727
-- * Error infrastructure
2828
DecoratedSDoc,
2929
MsgEnvelope,
30+
ErrMsg,
31+
WarnMsg,
3032
errMsgSpan,
3133
errMsgSeverity,
3234
formatErrorWithQual,
@@ -192,6 +194,13 @@ type PsWarning = ErrMsg
192194
type PsError = ErrMsg
193195
#endif
194196

197+
#if MIN_VERSION_ghc(9,2,0)
198+
type ErrMsg = MsgEnvelope DecoratedSDoc
199+
#endif
200+
#if MIN_VERSION_ghc(9,3,0)
201+
type WarnMsg = MsgEnvelope DecoratedSDoc
202+
#endif
203+
195204
mkPrintUnqualifiedDefault :: HscEnv -> GlobalRdrEnv -> PrintUnqualified
196205
mkPrintUnqualifiedDefault env =
197206
#if MIN_VERSION_ghc(9,2,0)

0 commit comments

Comments
 (0)