Skip to content

Commit 8a5ea73

Browse files
committed
Remove MIN_VERSION_ghc(9,5,0)
1 parent 1fb8830 commit 8a5ea73

File tree

26 files changed

+30
-426
lines changed

26 files changed

+30
-426
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -888,11 +888,7 @@ newComponentCache recorder exts _cfp hsc_env old_cis new_cis = do
888888
ideErrorWithSource
889889
(Just "cradle") (Just DiagnosticSeverity_Warning) _cfp
890890
(T.pack (Compat.printWithoutUniques (singleMessage err)))
891-
#if MIN_VERSION_ghc(9,5,0)
892891
(Just (fmap GhcDriverMessage err))
893-
#else
894-
Nothing
895-
#endif
896892
multi_errs = map closure_err_to_multi_err closure_errs
897893
bad_units = OS.fromList $ concat $ do
898894
x <- map errMsgDiagnostic closure_errs

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

Lines changed: 2 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,8 @@ import System.IO.Extra (fixIO,
112112
import qualified Data.Set as Set
113113
import qualified GHC as G
114114
import qualified GHC.Runtime.Loader as Loader
115+
import GHC.Driver.Config.CoreToStg.Prep
116+
import GHC.Core.Lint.Interactive
115117
import GHC.Tc.Gen.Splice
116118
import GHC.Types.Error
117119
import GHC.Types.ForeignStubs
@@ -120,12 +122,6 @@ import GHC.Types.TypeEnv
120122

121123
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
122124

123-
124-
#if MIN_VERSION_ghc(9,5,0)
125-
import GHC.Core.Lint.Interactive
126-
import GHC.Driver.Config.CoreToStg.Prep
127-
#endif
128-
129125
#if MIN_VERSION_ghc(9,7,0)
130126
import Data.Foldable (toList)
131127
import GHC.Unit.Module.Warnings
@@ -470,9 +466,7 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
470466
pure (details, guts)
471467

472468
let !partial_iface = force $ mkPartialIface session
473-
#if MIN_VERSION_ghc(9,5,0)
474469
(cg_binds guts)
475-
#endif
476470
details
477471
ms
478472
#if MIN_VERSION_ghc(9,11,0)
@@ -522,17 +516,9 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
522516
mod = ms_mod ms
523517
data_tycons = filter isDataTyCon tycons
524518
CgGuts{cg_binds = unprep_binds'} <- coreFileToCgGuts session final_iface details core
525-
526-
#if MIN_VERSION_ghc(9,5,0)
527519
cp_cfg <- initCorePrepConfig session
528-
#endif
529-
530520
let corePrep = corePrepPgm
531-
#if MIN_VERSION_ghc(9,5,0)
532521
(hsc_logger session) cp_cfg (initCorePrepPgmConfig (hsc_dflags session) (interactiveInScope $ hsc_IC session))
533-
#else
534-
session
535-
#endif
536522
mod (ms_location ms)
537523

538524
-- Run corePrep first as we want to test the final version of the program that will
@@ -1167,11 +1153,7 @@ parseHeader
11671153
=> DynFlags -- ^ flags to use
11681154
-> FilePath -- ^ the filename (for source locations)
11691155
-> Util.StringBuffer -- ^ Haskell module source text (full Unicode is supported)
1170-
#if MIN_VERSION_ghc(9,5,0)
11711156
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located (HsModule GhcPs))
1172-
#else
1173-
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located HsModule)
1174-
#endif
11751157
parseHeader dflags filename contents = do
11761158
let loc = mkRealSrcLoc (Util.mkFastString filename) 1 1
11771159
case unP Compat.parseHeader (initParserState (initParserOpts dflags) contents loc) of
@@ -1517,16 +1499,12 @@ coreFileToCgGuts session iface details core_file = do
15171499
-- Implicit binds aren't saved, so we need to regenerate them ourselves.
15181500
let _implicit_binds = concatMap getImplicitBinds tyCons -- only used if GHC < 9.6
15191501
tyCons = typeEnvTyCons (md_types details)
1520-
#if MIN_VERSION_ghc(9,5,0)
15211502
-- In GHC 9.6, the implicit binds are tidied and part of core_binds
15221503
pure $ CgGuts this_mod tyCons core_binds [] NoStubs [] mempty
15231504
#if !MIN_VERSION_ghc(9,11,0)
15241505
(emptyHpcInfo False)
15251506
#endif
15261507
Nothing []
1527-
#else
1528-
pure $ CgGuts this_mod tyCons (_implicit_binds ++ core_binds) [] NoStubs [] mempty (emptyHpcInfo False) Nothing []
1529-
#endif
15301508

15311509
coreFileToLinkable :: LinkableType -> HscEnv -> ModSummary -> ModIface -> ModDetails -> CoreFile -> UTCTime -> IO ([FileDiagnostic], Maybe HomeModInfo)
15321510
coreFileToLinkable linkableType session ms iface details core_file t = do

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

Lines changed: 6 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -19,16 +19,10 @@ import Development.IDE.GHC.Compat as Compat
1919
import Development.IDE.GHC.Compat.Util
2020
import GHC
2121
import GHC.Settings
22+
import qualified GHC.SysTools.Cpp as Pipeline
2223

2324
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
2425

25-
#if !MIN_VERSION_ghc(9,5,0)
26-
import qualified GHC.Driver.Pipeline.Execute as Pipeline
27-
#endif
28-
29-
#if MIN_VERSION_ghc(9,5,0)
30-
import qualified GHC.SysTools.Cpp as Pipeline
31-
#endif
3226

3327
#if MIN_VERSION_ghc(9,10,2)
3428
import qualified GHC.SysTools.Tasks as Pipeline
@@ -49,24 +43,21 @@ addOptP f = alterToolSettings $ \s -> s
4943

5044
doCpp :: HscEnv -> FilePath -> FilePath -> IO ()
5145
doCpp env input_fn output_fn =
52-
-- See GHC commit a2f53ac8d968723417baadfab5be36a020ea6850
53-
-- this function/Pipeline.doCpp previously had a raw parameter
54-
-- always set to True that corresponded to these settings
55-
56-
#if MIN_VERSION_ghc(9,5,0)
46+
-- See GHC commit a2f53ac8d968723417baadfab5be36a020ea6850
47+
-- this function/Pipeline.doCpp previously had a raw parameter
48+
-- always set to True that corresponded to these settings
5749
let cpp_opts = Pipeline.CppOpts
5850
{ cppLinePragmas = True
51+
5952
#if MIN_VERSION_ghc(9,10,2)
6053
, sourceCodePreprocessor = Pipeline.SCPHsCpp
6154
#elif MIN_VERSION_ghc(9,10,0)
6255
, useHsCpp = True
6356
#else
6457
, cppUseCc = False
6558
#endif
59+
6660
} in
67-
#else
68-
let cpp_opts = True in
69-
#endif
7061

7162
Pipeline.doCpp (hsc_logger env) (hsc_tmpfs env) (hsc_dflags env) (hsc_unit_env env) cpp_opts input_fn output_fn
7263

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

Lines changed: 6 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -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

168166
import GHC.Builtin.Uniques
169167
import GHC.ByteCode.Types
168+
import GHC.Core.Lint.Interactive (interactiveInScope)
170169
import GHC.CoreToStg
171170
import 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)
172175
import GHC.Driver.Config.Stg.Pipeline
173176
import GHC.Driver.Env as Env
174177
import 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)
204195
import 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]
291270
getDependentMods = map (gwib_mod . snd) . S.toList . dep_direct_mods . mi_deps
292271

293272
simplifyExpr :: DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
294-
#if MIN_VERSION_ghc(9,5,0)
295273
simplifyExpr _ 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

300275
corePrepExpr :: DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
301-
#if MIN_VERSION_ghc(9,5,0)
302276
corePrepExpr _ 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

309280
renderMessages :: PsMessages -> (Bag WarnMsg, Bag ErrMsg)
310281
renderMessages 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)
320285
pattern 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
324286
pattern 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

332290
hieExportNames :: HieFile -> [(SrcSpan, Name)]
@@ -508,14 +466,8 @@ loadModulesHome mod_infos e =
508466

509467
recDotDot :: HsRecFields (GhcPass p) arg -> Maybe Int
510468
recDotDot 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]
518473
extract_cons (DataTypeCons _ xs) = xs
519-
#else
520-
extract_cons = id
521-
#endif

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

Lines changed: 0 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -382,9 +382,6 @@ module Development.IDE.GHC.Compat.Core (
382382
emptyHomeModInfoLinkable,
383383
homeModInfoByteCode,
384384
homeModInfoObject,
385-
#if !MIN_VERSION_ghc(9,5,0)
386-
field_label,
387-
#endif
388385
groupOrigin,
389386
isVisibleFunArg,
390387
#if MIN_VERSION_ghc(9,8,0)
@@ -739,11 +736,7 @@ makeSimpleDetails hsc_env =
739736

740737
mkIfaceTc :: HscEnv -> GHC.SafeHaskellMode -> ModDetails -> ModSummary -> Maybe CoreProgram -> TcGblEnv -> IO ModIface
741738
mkIfaceTc hscEnv shm md _ms _mcp =
742-
#if MIN_VERSION_ghc(9,5,0)
743739
GHC.mkIfaceTc hscEnv shm md _ms _mcp -- mcp::Maybe CoreProgram is only used in GHC >= 9.6
744-
#else
745-
GHC.mkIfaceTc hscEnv shm md _ms -- ms::ModSummary is only used in GHC >= 9.4
746-
#endif
747740

748741
mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails
749742
mkBootModDetailsTc session = GHC.mkBootModDetailsTc
@@ -757,39 +750,10 @@ initTidyOpts =
757750
driverNoStop :: StopPhase
758751
driverNoStop = NoStop
759752

760-
761753
groupOrigin :: MatchGroup GhcRn body -> Origin
762-
#if MIN_VERSION_ghc(9,5,0)
763754
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b
764755
mapLoc = fmap
765756
groupOrigin = mg_ext
766-
#else
767-
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b
768-
mapLoc = SrcLoc.mapLoc
769-
groupOrigin = mg_origin
770-
#endif
771-
772-
773-
#if !MIN_VERSION_ghc(9,5,0)
774-
mkCgInteractiveGuts :: CgGuts -> CgGuts
775-
mkCgInteractiveGuts = id
776-
777-
emptyHomeModInfoLinkable :: Maybe Linkable
778-
emptyHomeModInfoLinkable = Nothing
779-
780-
justBytecode :: Linkable -> Maybe Linkable
781-
justBytecode = Just
782-
783-
justObjects :: Linkable -> Maybe Linkable
784-
justObjects = Just
785-
786-
homeModInfoByteCode, homeModInfoObject :: HomeModInfo -> Maybe Linkable
787-
homeModInfoByteCode = hm_linkable
788-
homeModInfoObject = hm_linkable
789-
790-
field_label :: a -> a
791-
field_label = id
792-
#endif
793757

794758
mkSimpleTarget :: DynFlags -> FilePath -> Target
795759
mkSimpleTarget df fp = Target (TargetFile fp Nothing) True (homeUnitId_ df) Nothing

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

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -79,11 +79,7 @@ hsc_typecheck keep_rn mod_summary mb_rdr_module = do
7979
tc_result0 <- tcRnModule' mod_summary keep_rn' hpm
8080
if hsc_src == HsigFile
8181
then
82-
#if MIN_VERSION_ghc(9,5,0)
8382
do (iface, _) <- liftIO $ hscSimpleIface hsc_env Nothing tc_result0 mod_summary
84-
#else
85-
do (iface, _) <- liftIO $ hscSimpleIface hsc_env tc_result0 mod_summary
86-
#endif
8783
ioMsgMaybe $ hoistTcRnMessage $
8884
tcRnMergeSignatures hsc_env hpm tc_result0 iface
8985
else return tc_result0
@@ -135,21 +131,12 @@ extract_renamed_stuff mod_summary tc_result = do
135131
-- ============================================================================
136132
-- DO NOT EDIT - Refer to top of file
137133
-- ============================================================================
138-
#if MIN_VERSION_ghc(9,5,0)
139134
hscSimpleIface :: HscEnv
140135
-> Maybe CoreProgram
141136
-> TcGblEnv
142137
-> ModSummary
143138
-> IO (ModIface, ModDetails)
144139
hscSimpleIface hsc_env mb_core_program tc_result summary
145140
= runHsc hsc_env $ hscSimpleIface' mb_core_program tc_result summary
146-
#else
147-
hscSimpleIface :: HscEnv
148-
-> TcGblEnv
149-
-> ModSummary
150-
-> IO (ModIface, ModDetails)
151-
hscSimpleIface hsc_env tc_result summary
152-
= runHsc hsc_env $ hscSimpleIface' tc_result summary
153-
#endif
154141

155142
#endif

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

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -105,22 +105,14 @@ hscHomeUnit =
105105
setBytecodeLinkerOptions :: DynFlags -> DynFlags
106106
setBytecodeLinkerOptions df = df {
107107
ghcLink = LinkInMemory
108-
#if MIN_VERSION_ghc(9,5,0)
109108
, backend = noBackend
110-
#else
111-
, backend = NoBackend
112-
#endif
113109
, ghcMode = CompManager
114110
}
115111

116112
setInterpreterLinkerOptions :: DynFlags -> DynFlags
117113
setInterpreterLinkerOptions df = df {
118114
ghcLink = LinkInMemory
119-
#if MIN_VERSION_ghc(9,5,0)
120115
, backend = interpreterBackend
121-
#else
122-
, backend = Interpreter
123-
#endif
124116
, ghcMode = CompManager
125117
}
126118

0 commit comments

Comments
 (0)