Skip to content

Commit 57a91c3

Browse files
committed
Automatically remove macros for 9.2
1 parent eb56af1 commit 57a91c3

File tree

39 files changed

+47
-1535
lines changed

39 files changed

+47
-1535
lines changed

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

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ import Data.Function
4040
import Data.Hashable hiding (hash)
4141
import qualified Data.HashMap.Strict as HM
4242
import Data.List
43+
import Data.List.NonEmpty (NonEmpty (..))
4344
import qualified Data.List.NonEmpty as NE
44-
import Data.List.NonEmpty (NonEmpty(..))
4545
import qualified Data.Map.Strict as Map
4646
import Data.Maybe
4747
import Data.Proxy
@@ -826,7 +826,7 @@ newComponentCache recorder exts cradlePath cfp hsc_env uids ci = do
826826
#if MIN_VERSION_ghc(9,3,0)
827827
-- Set up a multi component session with the other units on GHC 9.4
828828
Compat.initUnits (map snd uids) (hscSetFlags df hsc_env)
829-
#elif MIN_VERSION_ghc(9,2,0)
829+
#else
830830
-- This initializes the units for GHC 9.2
831831
-- Add the options for the current component to the HscEnv
832832
-- We want to call `setSessionDynFlags` instead of `hscSetFlags`
@@ -837,9 +837,6 @@ newComponentCache recorder exts cradlePath cfp hsc_env uids ci = do
837837
evalGhcEnv hsc_env $ do
838838
_ <- setSessionDynFlags $ df
839839
getSession
840-
#else
841-
-- getOptions is enough to initialize units on GHC <9.2
842-
pure $ hscSetFlags df hsc_env { hsc_IC = (hsc_IC hsc_env) { ic_dflags = df } }
843840
#endif
844841

845842
let newFunc = maybe newHscEnvEqPreserveImportPaths newHscEnvEq cradlePath

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

Lines changed: 3 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -110,27 +110,17 @@ import System.IO.Extra (fixIO, newTempFileWithin)
110110

111111
import GHC.Tc.Gen.Splice
112112

113-
#if !MIN_VERSION_ghc(9,2,1)
114-
import GHC.Driver.Types
115-
#endif
116113

117-
#if !MIN_VERSION_ghc(9,2,0)
118-
import qualified Data.IntMap.Strict as IntMap
119-
#endif
120114

121-
#if MIN_VERSION_ghc(9,2,0)
122115
import qualified GHC as G
123-
#endif
124116

125-
#if MIN_VERSION_ghc(9,2,0) && !MIN_VERSION_ghc(9,3,0)
117+
#if !MIN_VERSION_ghc(9,3,0)
126118
import GHC (ModuleGraph)
127119
#endif
128120

129-
#if MIN_VERSION_ghc(9,2,1)
130121
import GHC.Types.ForeignStubs
131122
import GHC.Types.HpcInfo
132123
import GHC.Types.TypeEnv
133-
#endif
134124

135125
#if !MIN_VERSION_ghc(9,3,0)
136126
import Data.Map (Map)
@@ -265,7 +255,6 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
265255
; lintInteractiveExpr "hscCompileExpr" hsc_env prepd_expr
266256

267257

268-
#if MIN_VERSION_ghc(9,2,0)
269258
; let iNTERACTIVELoc = G.ModLocation{ ml_hs_file = Nothing,
270259
ml_hi_file = panic "hscCompileCoreExpr':ml_hi_file",
271260
ml_obj_file = panic "hscCompileCoreExpr':ml_obj_file",
@@ -293,11 +282,6 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
293282
(icInteractiveModule ictxt)
294283
stg_expr
295284
[] Nothing
296-
#else
297-
{- Convert to BCOs -}
298-
; bcos <- coreExprToBCOs hsc_env
299-
(icInteractiveModule (hsc_IC hsc_env)) prepd_expr
300-
#endif
301285

302286
-- Exclude wired-in names because we may not have read
303287
-- their interface files, so getLinkDeps will fail
@@ -312,11 +296,7 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
312296
moduleName mod -- On <= 9.2, just the name is enough because all unit ids will be the same
313297
#endif
314298

315-
#if MIN_VERSION_ghc(9,2,0)
316299
| n <- concatMap (uniqDSetToList . bcoFreeNames) $ bc_bcos bcos
317-
#else
318-
| n <- uniqDSetToList (bcoFreeNames bcos)
319-
#endif
320300
, Just mod <- [nameModule_maybe n] -- Names from other modules
321301
, not (isWiredInName n) -- Exclude wired-in names
322302
, moduleUnitId mod `elem` home_unit_ids -- Only care about stuff from the home package set
@@ -357,13 +337,10 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
357337
{- load it -}
358338
; (fv_hvs, lbss, pkgs) <- loadDecls (hscInterp hsc_env') hsc_env' srcspan bcos
359339
; let hval = ((expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs), lbss, pkgs)
360-
#elif MIN_VERSION_ghc(9,2,0)
340+
#else
361341
{- load it -}
362342
; fv_hvs <- loadDecls (hscInterp hsc_env') hsc_env' srcspan bcos
363343
; let hval = (expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs)
364-
#else
365-
{- link it -}
366-
; hval <- linkExpr hsc_env' srcspan bcos
367344
#endif
368345

369346
; modifyIORef' var (flip extendModuleEnvList [(mi_module $ hm_iface hm, linkableHash lb) | lb <- lbs, let hm = linkableHomeMod lb])
@@ -881,7 +858,7 @@ generateHieAsts hscEnv tcm =
881858
where
882859
dflags = hsc_dflags hscEnv
883860
run _ts = -- ts is only used in GHC 9.2
884-
#if MIN_VERSION_ghc(9,2,0) && !MIN_VERSION_ghc(9,3,0)
861+
#if !MIN_VERSION_ghc(9,3,0)
885862
fmap (join . snd) . liftIO . initDs hscEnv _ts
886863
#else
887864
id
@@ -1714,9 +1691,6 @@ getDocsBatch hsc_env _names = do
17141691
#else
17151692
Map.lookup name dmap ,
17161693
#endif
1717-
#if !MIN_VERSION_ghc(9,2,0)
1718-
IntMap.fromAscList $ Map.toAscList $
1719-
#endif
17201694
#if MIN_VERSION_ghc(9,3,0)
17211695
lookupWithDefaultUniqMap amap mempty name))
17221696
#else
@@ -1739,12 +1713,7 @@ lookupName :: HscEnv
17391713
lookupName _ name
17401714
| Nothing <- nameModule_maybe name = pure Nothing
17411715
lookupName hsc_env name = exceptionHandle $ do
1742-
#if MIN_VERSION_ghc(9,2,0)
17431716
mb_thing <- liftIO $ lookupType hsc_env name
1744-
#else
1745-
eps <- liftIO $ readIORef (hsc_EPS hsc_env)
1746-
let mb_thing = lookupType (hsc_dflags hsc_env) (hsc_HPT hsc_env) (eps_PTE eps) name
1747-
#endif
17481717
case mb_thing of
17491718
x@(Just _) -> return x
17501719
Nothing

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

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -697,12 +697,10 @@ dependencyInfoForFiles fs = do
697697
mg = mkModuleGraph mns
698698
#else
699699
let mg = mkModuleGraph $
700-
#if MIN_VERSION_ghc(9,2,0)
701700
-- We don't do any instantiation for backpack at this point of time, so it is OK to use
702701
-- 'extendModSummaryNoDeps'.
703702
-- This may have to change in the future.
704703
map extendModSummaryNoDeps $
705-
#endif
706704
(catMaybes mss)
707705
#endif
708706
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg)
@@ -822,12 +820,10 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
822820
nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs)
823821
#else
824822
let module_graph_nodes =
825-
#if MIN_VERSION_ghc(9,2,0)
826823
-- We don't do any instantiation for backpack at this point of time, so it is OK to use
827824
-- 'extendModSummaryNoDeps'.
828825
-- This may have to change in the future.
829826
map extendModSummaryNoDeps $
830-
#endif
831827
nubOrdOn ms_mod (ms : concatMap mgModSummaries mgs)
832828
#endif
833829
liftIO $ evaluate $ liftRnf rwhnf module_graph_nodes
@@ -1219,12 +1215,7 @@ uses_th_qq (ms_hspp_opts -> dflags) =
12191215
-- Depends on whether it uses unboxed tuples or sums
12201216
computeLinkableTypeForDynFlags :: DynFlags -> LinkableType
12211217
computeLinkableTypeForDynFlags d
1222-
#if defined(GHC_PATCHED_UNBOXED_BYTECODE) || MIN_VERSION_ghc(9,2,0)
12231218
= BCOLinkable
1224-
#else
1225-
| _unboxed_tuples_or_sums = ObjectLinkable
1226-
| otherwise = BCOLinkable
1227-
#endif
12281219
where -- unboxed_tuples_or_sums is only used in GHC < 9.2
12291220
_unboxed_tuples_or_sums =
12301221
xopt LangExt.UnboxedTuples d || xopt LangExt.UnboxedSums d

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

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -63,9 +63,5 @@ doCpp env input_fn output_fn =
6363
let cpp_opts = True in
6464
#endif
6565

66-
#if MIN_VERSION_ghc(9,2,0)
6766
Pipeline.doCpp (hsc_logger env) (hsc_tmpfs env) (hsc_dflags env) (hsc_unit_env env) cpp_opts input_fn output_fn
68-
#else
69-
Pipeline.doCpp (hsc_dflags env) cpp_opts input_fn output_fn
70-
#endif
7167

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

Lines changed: 1 addition & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -31,13 +31,11 @@ module Development.IDE.GHC.Compat(
3131
pattern PFailedWithErrorMessages,
3232
isObjectLinkable,
3333

34-
#if MIN_VERSION_ghc(9,2,0)
3534
#if !MIN_VERSION_ghc(9,3,0)
3635
extendModSummaryNoDeps,
3736
emsModSummary,
3837
#endif
3938
myCoreToStgExpr,
40-
#endif
4139

4240
Usage(..),
4341

@@ -123,17 +121,12 @@ module Development.IDE.GHC.Compat(
123121
emptyInScopeSet,
124122
Unfolding(..),
125123
noUnfolding,
126-
#if MIN_VERSION_ghc(9,2,0)
127124
loadExpr,
128125
byteCodeGen,
129126
bc_bcos,
130127
loadDecls,
131128
hscInterp,
132129
expectJust,
133-
#else
134-
coreExprToBCOs,
135-
linkExpr,
136-
#endif
137130
extract_cons,
138131
recDotDot,
139132
#if MIN_VERSION_ghc(9,5,0)
@@ -194,22 +187,12 @@ import GHC.Iface.Make (mkIfaceExports)
194187
import qualified GHC.SysTools.Tasks as SysTools
195188
import qualified GHC.Types.Avail as Avail
196189

197-
#if !MIN_VERSION_ghc(9,2,0)
198-
import GHC.Utils.Error
199-
import GHC.CoreToByteCode (coreExprToBCOs)
200-
import GHC.Runtime.Linker (linkExpr)
201-
import GHC.Driver.Types
202-
#endif
203190

204191
#if !MIN_VERSION_ghc(9,5,0)
205192
import GHC.Core.Lint (lintInteractiveExpr)
206193
#endif
207194

208-
#if !MIN_VERSION_ghc(9,2,0)
209-
import Data.Bifunctor
210-
#endif
211195

212-
#if MIN_VERSION_ghc(9,2,0)
213196
import GHC.Iface.Env
214197
import qualified GHC.Types.SrcLoc as SrcLoc
215198
import GHC.Linker.Loader (loadExpr)
@@ -228,9 +211,8 @@ import GHC.Stg.Syntax
228211
import GHC.StgToByteCode
229212
import GHC.Types.CostCentre
230213
import GHC.Types.IPE
231-
#endif
232214

233-
#if MIN_VERSION_ghc(9,2,0) && !MIN_VERSION_ghc(9,3,0)
215+
#if !MIN_VERSION_ghc(9,3,0)
234216
import GHC.Unit.Module.Deps (Dependencies(dep_mods), Usage(..))
235217
import GHC.Linker.Types (isObjectLinkable)
236218
import GHC.Unit.Module.ModSummary
@@ -276,7 +258,6 @@ nameEnvElts :: NameEnv a -> [a]
276258
nameEnvElts = nonDetNameEnvElts
277259
#endif
278260

279-
#if MIN_VERSION_ghc(9,2,0)
280261
myCoreToStgExpr :: Logger -> DynFlags -> InteractiveContext
281262
#if MIN_VERSION_ghc(9,3,0)
282263
-> Bool
@@ -365,16 +346,8 @@ myCoreToStg logger dflags ictxt
365346
#endif
366347

367348
return (stg_binds2, denv, cost_centre_info)
368-
#endif
369349

370350

371-
#if !MIN_VERSION_ghc(9,2,0)
372-
reLoc :: Located a -> Located a
373-
reLoc = id
374-
375-
reLocA :: Located a -> Located a
376-
reLocA = id
377-
#endif
378351

379352
getDependentMods :: ModIface -> [ModuleName]
380353
#if MIN_VERSION_ghc(9,3,0)
@@ -408,19 +381,13 @@ renderMessages msgs =
408381
msgs
409382
#endif
410383

411-
#if MIN_VERSION_ghc(9,2,0)
412384
pattern PFailedWithErrorMessages :: forall a b. (b -> Bag (MsgEnvelope DecoratedSDoc)) -> ParseResult a
413385
pattern PFailedWithErrorMessages msgs
414386
#if MIN_VERSION_ghc(9,3,0)
415387
<- PFailed (const . fmap (fmap renderDiagnosticMessageWithHints) . getMessages . getPsErrorMessages -> msgs)
416388
#else
417389
<- PFailed (const . fmap pprError . getErrorMessages -> msgs)
418390
#endif
419-
#else
420-
pattern PFailedWithErrorMessages :: (DynFlags -> ErrorMessages) -> ParseResult a
421-
pattern PFailedWithErrorMessages msgs
422-
<- PFailed (getErrorMessages -> msgs)
423-
#endif
424391
{-# COMPLETE POk, PFailedWithErrorMessages #-}
425392

426393
hieExportNames :: HieFile -> [(SrcSpan, Name)]
@@ -578,19 +545,11 @@ ghcVersion = GHC810
578545

579546
runUnlit :: Logger -> DynFlags -> [Option] -> IO ()
580547
runUnlit =
581-
#if MIN_VERSION_ghc(9,2,0)
582548
SysTools.runUnlit
583-
#else
584-
const SysTools.runUnlit
585-
#endif
586549

587550
runPp :: Logger -> DynFlags -> [Option] -> IO ()
588551
runPp =
589-
#if MIN_VERSION_ghc(9,2,0)
590552
SysTools.runPp
591-
#else
592-
const SysTools.runPp
593-
#endif
594553

595554
simpleNodeInfoCompat :: FastStringCompat -> FastStringCompat -> NodeInfo a
596555
simpleNodeInfoCompat ctor typ = simpleNodeInfo (coerce ctor) (coerce typ)
@@ -599,42 +558,19 @@ isAnnotationInNodeInfo :: (FastStringCompat, FastStringCompat) -> NodeInfo a ->
599558
isAnnotationInNodeInfo p = S.member p . nodeAnnotations
600559

601560
nodeAnnotations :: NodeInfo a -> S.Set (FastStringCompat, FastStringCompat)
602-
#if MIN_VERSION_ghc(9,2,0)
603561
nodeAnnotations = S.map (\(NodeAnnotation ctor typ) -> (coerce ctor, coerce typ)) . GHC.nodeAnnotations
604-
#else
605-
nodeAnnotations = S.map (bimap coerce coerce) . GHC.nodeAnnotations
606-
#endif
607562

608-
#if MIN_VERSION_ghc(9,2,0)
609563
newtype FastStringCompat = FastStringCompat LexicalFastString
610-
#else
611-
newtype FastStringCompat = FastStringCompat FastString
612-
#endif
613564
deriving (Show, Eq, Ord)
614565

615566
instance IsString FastStringCompat where
616-
#if MIN_VERSION_ghc(9,2,0)
617567
fromString = FastStringCompat . LexicalFastString . fromString
618-
#else
619-
fromString = FastStringCompat . fromString
620-
#endif
621568

622569
mkAstNode :: NodeInfo a -> Span -> [HieAST a] -> HieAST a
623570
mkAstNode n = Node (SourcedNodeInfo $ Map.singleton GeneratedInfo n)
624571

625572
combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan
626-
#if MIN_VERSION_ghc(9,2,0)
627573
combineRealSrcSpans = SrcLoc.combineRealSrcSpans
628-
#else
629-
combineRealSrcSpans span1 span2
630-
= mkRealSrcSpan (mkRealSrcLoc file line_start col_start) (mkRealSrcLoc file line_end col_end)
631-
where
632-
(line_start, col_start) = min (srcSpanStartLine span1, srcSpanStartCol span1)
633-
(srcSpanStartLine span2, srcSpanStartCol span2)
634-
(line_end, col_end) = max (srcSpanEndLine span1, srcSpanEndCol span1)
635-
(srcSpanEndLine span2, srcSpanEndCol span2)
636-
file = srcSpanFile span1
637-
#endif
638574

639575
-- | Load modules, quickly. Input doesn't need to be desugared.
640576
-- A module must be loaded before dependent modules can be typechecked.

0 commit comments

Comments
 (0)