@@ -102,9 +102,7 @@ module Development.IDE.GHC.Compat(
102102 Dependencies (dep_direct_mods ),
103103 NameCacheUpdater ,
104104
105- #if MIN_VERSION_ghc(9,5,0)
106105 XModulePs (.. ),
107- #endif
108106
109107#if !MIN_VERSION_ghc(9,7,0)
110108 liftZonkM ,
@@ -167,8 +165,13 @@ import GHC.Types.Var.Env
167165
168166import GHC.Builtin.Uniques
169167import GHC.ByteCode.Types
168+ import GHC.Core.Lint.Interactive (interactiveInScope )
170169import GHC.CoreToStg
171170import GHC.Data.Maybe
171+ import GHC.Driver.Config.Core.Lint.Interactive (lintInteractiveExpr )
172+ import GHC.Driver.Config.Core.Opt.Simplify (initSimplifyExprOpts )
173+ import GHC.Driver.Config.CoreToStg (initCoreToStgOpts )
174+ import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig )
172175import GHC.Driver.Config.Stg.Pipeline
173176import GHC.Driver.Env as Env
174177import GHC.Iface.Env
@@ -188,18 +191,6 @@ import GHC.Unit.Module.ModIface
188191
189192-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
190193
191- #if !MIN_VERSION_ghc(9,5,0)
192- import GHC.Core.Lint (lintInteractiveExpr )
193- #endif
194-
195- #if MIN_VERSION_ghc(9,5,0)
196- import GHC.Core.Lint.Interactive (interactiveInScope )
197- import GHC.Driver.Config.Core.Lint.Interactive (lintInteractiveExpr )
198- import GHC.Driver.Config.Core.Opt.Simplify (initSimplifyExprOpts )
199- import GHC.Driver.Config.CoreToStg (initCoreToStgOpts )
200- import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig )
201- #endif
202-
203194#if MIN_VERSION_ghc(9,7,0)
204195import GHC.Tc.Zonk.TcType (tcInitTidyEnv )
205196#endif
@@ -230,11 +221,7 @@ myCoreToStgExpr logger dflags ictxt
230221 binding for the stg2stg step) -}
231222 let bco_tmp_id = mkSysLocal (fsLit " BCO_toplevel" )
232223 (mkPseudoUniqueE 0 )
233- #if MIN_VERSION_ghc(9,5,0)
234224 ManyTy
235- #else
236- Many
237- #endif
238225 (exprType prepd_expr)
239226 (stg_binds, prov_map, collected_ccs) <-
240227 myCoreToStg logger
@@ -258,11 +245,7 @@ myCoreToStg logger dflags ictxt
258245 let (stg_binds, denv, cost_centre_info)
259246 = {-# SCC "Core2Stg" #-}
260247 coreToStg
261- #if MIN_VERSION_ghc(9,5,0)
262248 (initCoreToStgOpts dflags)
263- #else
264- dflags
265- #endif
266249 this_mod ml prepd_binds
267250
268251#if MIN_VERSION_ghc(9,8,0)
@@ -272,11 +255,7 @@ myCoreToStg logger dflags ictxt
272255#endif
273256 <- {-# SCC "Stg2Stg" #-}
274257 stg2stg logger
275- #if MIN_VERSION_ghc(9,5,0)
276258 (interactiveInScope ictxt)
277- #else
278- ictxt
279- #endif
280259 (initStgPipelineOpts dflags for_bytecode) this_mod stg_binds
281260
282261 return (stg_binds2, denv, cost_centre_info)
@@ -291,42 +270,21 @@ getDependentMods :: ModIface -> [ModuleName]
291270getDependentMods = map (gwib_mod . snd ) . S. toList . dep_direct_mods . mi_deps
292271
293272simplifyExpr :: DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
294- #if MIN_VERSION_ghc(9,5,0)
295273simplifyExpr _ env = GHC. simplifyExpr (Development.IDE.GHC.Compat.Env. hsc_logger env) (ue_eps (Development.IDE.GHC.Compat.Env. hsc_unit_env env)) (initSimplifyExprOpts (hsc_dflags env) (hsc_IC env))
296- #else
297- simplifyExpr _ = GHC. simplifyExpr
298- #endif
299274
300275corePrepExpr :: DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
301- #if MIN_VERSION_ghc(9,5,0)
302276corePrepExpr _ env expr = do
303277 cfg <- initCorePrepConfig env
304278 GHC. corePrepExpr (Development.IDE.GHC.Compat.Env. hsc_logger env) cfg expr
305- #else
306- corePrepExpr _ = GHC. corePrepExpr
307- #endif
308279
309280renderMessages :: PsMessages -> (Bag WarnMsg , Bag ErrMsg )
310281renderMessages msgs =
311- #if MIN_VERSION_ghc(9,5,0)
312282 let renderMsgs extractor = (fmap . fmap ) GhcPsMessage . getMessages $ extractor msgs
313283 in (renderMsgs psWarnings, renderMsgs psErrors)
314- #else
315- let renderMsgs extractor = (fmap . fmap ) renderDiagnosticMessageWithHints . getMessages $ extractor msgs
316- in (renderMsgs psWarnings, renderMsgs psErrors)
317- #endif
318284
319- #if MIN_VERSION_ghc(9,5,0)
320285pattern PFailedWithErrorMessages :: forall a b . (b -> Bag (MsgEnvelope GhcMessage )) -> ParseResult a
321- #else
322- pattern PFailedWithErrorMessages :: forall a b . (b -> Bag (MsgEnvelope DecoratedSDoc )) -> ParseResult a
323- #endif
324286pattern PFailedWithErrorMessages msgs
325- #if MIN_VERSION_ghc(9,5,0)
326287 <- PFailed (const . fmap (fmap GhcPsMessage ) . getMessages . getPsErrorMessages -> msgs)
327- #else
328- <- PFailed (const . fmap (fmap renderDiagnosticMessageWithHints) . getMessages . getPsErrorMessages -> msgs)
329- #endif
330288{-# COMPLETE POk, PFailedWithErrorMessages #-}
331289
332290hieExportNames :: HieFile -> [(SrcSpan , Name )]
@@ -508,14 +466,8 @@ loadModulesHome mod_infos e =
508466
509467recDotDot :: HsRecFields (GhcPass p ) arg -> Maybe Int
510468recDotDot x =
511- #if MIN_VERSION_ghc(9,5,0)
512469 unRecFieldsDotDot <$>
513- #endif
514470 unLoc <$> rec_dotdot x
515471
516- #if MIN_VERSION_ghc(9,5,0)
517- extract_cons (NewTypeCon x) = [x]
472+ extract_cons (NewTypeCon x) = [x]
518473extract_cons (DataTypeCons _ xs) = xs
519- #else
520- extract_cons = id
521- #endif
0 commit comments