@@ -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
0 commit comments