Skip to content

Commit 5caf534

Browse files
committed
Remove #if MIN_VERSION_ghc(9,4,0) CPP statements
1 parent 3e4a801 commit 5caf534

File tree

11 files changed

+42
-152
lines changed

11 files changed

+42
-152
lines changed

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

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -481,9 +481,7 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
481481
simplified_guts
482482

483483
final_iface' <- mkFullIface session partial_iface Nothing
484-
#if MIN_VERSION_ghc(9,4,2)
485484
Nothing
486-
#endif
487485
#if MIN_VERSION_ghc(9,11,0)
488486
NoStubs []
489487
#endif
@@ -647,11 +645,7 @@ generateObjectCode session summary guts = do
647645
(Just dot_o)
648646
$ hsc_dflags env'
649647
session' = hscSetFlags newFlags session
650-
#if MIN_VERSION_ghc(9,4,2)
651648
(outputFilename, _mStub, _foreign_files, _cinfos, _stgcinfos) <- hscGenHardCode session' guts
652-
#else
653-
(outputFilename, _mStub, _foreign_files, _cinfos) <- hscGenHardCode session' guts
654-
#endif
655649
(ms_location summary)
656650
fp
657651
obj <- compileFile session' driverNoStop (outputFilename, Just (As False))
@@ -1637,7 +1631,7 @@ setNonHomeFCHook hsc_env =
16371631
with negative if clauses coming before positive if clauses of the same
16381632
version. (If you think about which GHC version a clause activates for this
16391633
should make sense `!MIN_VERSION_GHC(9,0,0)` refers to 8.10 and lower which is
1640-
a earlier version than `MIN_VERSION_GHC(9,0,0)` which refers to versions 9.0
1634+
an earlier version than `MIN_VERSION_GHC(9,0,0)` which refers to versions 9.0
16411635
and later). In addition there should be a space before and after each CPP
16421636
clause.
16431637

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

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -267,10 +267,8 @@ myCoreToStg logger dflags ictxt
267267

268268
#if MIN_VERSION_ghc(9,8,0)
269269
(unzip -> (stg_binds2,_),_)
270-
#elif MIN_VERSION_ghc(9,4,2)
271-
(stg_binds2,_)
272270
#else
273-
stg_binds2
271+
(stg_binds2,_)
274272
#endif
275273
<- {-# SCC "Stg2Stg" #-}
276274
stg2stg logger

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

Lines changed: 0 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -375,18 +375,7 @@ module Development.IDE.GHC.Compat.Core (
375375
module GHC.Unit.Finder.Types,
376376
module GHC.Unit.Env,
377377
module GHC.Driver.Phases,
378-
#if !MIN_VERSION_ghc(9,4,0)
379-
pattern HsFieldBind,
380-
hfbAnn,
381-
hfbLHS,
382-
hfbRHS,
383-
hfbPun,
384-
#endif
385-
#if !MIN_VERSION_ghc_boot_th(9,4,1)
386-
Extension(.., NamedFieldPuns),
387-
#else
388378
Extension(..),
389-
#endif
390379
mkCgInteractiveGuts,
391380
justBytecode,
392381
justObjects,
@@ -769,17 +758,6 @@ driverNoStop :: StopPhase
769758
driverNoStop = NoStop
770759

771760

772-
#if !MIN_VERSION_ghc(9,4,0)
773-
pattern HsFieldBind :: XHsRecField id -> id -> arg -> Bool -> HsRecField' id arg
774-
pattern HsFieldBind {hfbAnn, hfbLHS, hfbRHS, hfbPun} <- HsRecField hfbAnn (SrcLoc.unLoc -> hfbLHS) hfbRHS hfbPun where
775-
HsFieldBind ann lhs rhs pun = HsRecField ann (SrcLoc.noLoc lhs) rhs pun
776-
#endif
777-
778-
#if !MIN_VERSION_ghc_boot_th(9,4,1)
779-
pattern NamedFieldPuns :: Extension
780-
pattern NamedFieldPuns = RecordPuns
781-
#endif
782-
783761
groupOrigin :: MatchGroup GhcRn body -> Origin
784762
#if MIN_VERSION_ghc(9,5,0)
785763
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b

ghcide/src/Development/IDE/Import/FindImports.hs

Lines changed: 2 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -145,9 +145,8 @@ locateModule env comp_info exts targetFor modName mbPkgName isSource = do
145145
dflags = hsc_dflags env
146146
import_paths = mapMaybe (mkImportDirs env) comp_info
147147
other_imports =
148-
#if MIN_VERSION_ghc(9,4,0)
149-
-- On 9.4+ instead of bringing all the units into scope, only bring into scope the units
150-
-- this one depends on
148+
-- Instead of bringing all the units into scope, only bring into scope the units
149+
-- this one depends on.
151150
-- This way if you have multiple units with the same module names, we won't get confused
152151
-- For example if unit a imports module M from unit B, when there is also a module M in unit C,
153152
-- and unit a only depends on unit b, without this logic there is the potential to get confused
@@ -163,17 +162,6 @@ locateModule env comp_info exts targetFor modName mbPkgName isSource = do
163162
units = homeUnitEnv_units $ ue_findHomeUnitEnv (homeUnitId_ dflags) ue
164163
hpt_deps :: [UnitId]
165164
hpt_deps = homeUnitDepends units
166-
#else
167-
_import_paths'
168-
#endif
169-
170-
-- first try to find the module as a file. If we can't find it try to find it in the package
171-
-- database.
172-
-- Here the importPaths for the current modules are added to the front of the import paths from the other components.
173-
-- This is particularly important for Paths_* modules which get generated for every component but unless you use it in
174-
-- each component will end up being found in the wrong place and cause a multi-cradle match failure.
175-
_import_paths' = -- import_paths' is only used in GHC < 9.4
176-
import_paths
177165

178166
toModLocation uid file = liftIO $ do
179167
loc <- mkHomeModLocation dflags (unLoc modName) (fromNormalizedFilePath file)

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Util.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -77,9 +77,7 @@ showErr e =
7777
$ bagToList
7878
$ fmap (vcat . unDecorated
7979
. diagnosticMessage
80-
#if MIN_VERSION_ghc(9,5,0)
8180
(defaultDiagnosticOpts @GhcMessage)
82-
#endif
8381
. errMsgDiagnostic)
8482
$ getMessages msgs
8583
_ ->

plugins/hls-refactor-plugin/src/Development/IDE/GHC/Dump.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -239,13 +239,8 @@ showAstDataHtml a0 = html $
239239
annotationEpAnnHsCase :: EpAnn EpAnnHsCase -> SDoc
240240
annotationEpAnnHsCase = annotation' (text "EpAnn EpAnnHsCase")
241241

242-
#if MIN_VERSION_ghc(9,4,0)
243242
annotationEpAnnHsLet :: EpAnn NoEpAnns -> SDoc
244243
annotationEpAnnHsLet = annotation' (text "EpAnn NoEpAnns")
245-
#else
246-
annotationEpAnnHsLet :: EpAnn AnnsLet -> SDoc
247-
annotationEpAnnHsLet = annotation' (text "EpAnn AnnsLet")
248-
#endif
249244

250245
#if MIN_VERSION_ghc(9,11,0)
251246
annotationAnnList :: EpAnn (AnnList ()) -> SDoc

plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs

Lines changed: 0 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -735,26 +735,16 @@ annotate :: ASTElement l ast
735735
annotate dflags needs_space ast = do
736736
uniq <- show <$> uniqueSrcSpanT
737737
let rendered = render dflags ast
738-
#if MIN_VERSION_ghc(9,4,0)
739738
expr' <- TransformT $ lift $ mapLeft (showSDoc dflags . ppr) $ parseAST dflags uniq rendered
740739
pure $ setPrecedingLines expr' 0 (bool 0 1 needs_space)
741-
#else
742-
expr' <- lift $ mapLeft show $ parseAST dflags uniq rendered
743-
pure $ setPrecedingLines expr' 0 (bool 0 1 needs_space)
744-
#endif
745740

746741
-- | Given an 'LHsDecl', compute its exactprint annotations.
747742
annotateDecl :: DynFlags -> LHsDecl GhcPs -> TransformT (Either String) (LHsDecl GhcPs)
748743
annotateDecl dflags ast = do
749744
uniq <- show <$> uniqueSrcSpanT
750745
let rendered = render dflags ast
751-
#if MIN_VERSION_ghc(9,4,0)
752746
expr' <- TransformT $ lift $ mapLeft (showSDoc dflags . ppr) $ parseDecl dflags uniq rendered
753747
pure $ setPrecedingLines expr' 1 0
754-
#else
755-
expr' <- lift $ mapLeft show $ parseDecl dflags uniq rendered
756-
pure $ setPrecedingLines expr' 1 0
757-
#endif
758748

759749
------------------------------------------------------------------------------
760750

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 16 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -73,8 +73,7 @@ import Development.IDE.Types.Diagnostics
7373
import Development.IDE.Types.Exports
7474
import Development.IDE.Types.Location
7575
import Development.IDE.Types.Options
76-
import GHC (
77-
DeltaPos (..),
76+
import GHC (DeltaPos (..),
7877
EpAnn (..),
7978
LEpaComment)
8079
import qualified GHC.LanguageExtensions as Lang
@@ -109,9 +108,9 @@ import Text.Regex.TDFA ((=~), (=~~))
109108
#if !MIN_VERSION_ghc(9,9,0)
110109
import Development.IDE.GHC.Compat.ExactPrint (makeDeltaAst)
111110
import GHC (AddEpAnn (AddEpAnn),
112-
AnnsModule (am_main),
113111
Anchor (anchor_op),
114112
AnchorOperation (..),
113+
AnnsModule (am_main),
115114
EpaLocation (..))
116115
#endif
117116

@@ -123,11 +122,11 @@ import GHC (AddEpAnn (Ad
123122
HasLoc (..))
124123
#endif
125124
#if MIN_VERSION_ghc(9,11,0)
126-
import GHC (EpaLocation,
127-
AnnsModule (am_where),
125+
import GHC (AnnsModule (am_where),
126+
EpToken (..),
127+
EpaLocation,
128128
EpaLocation' (..),
129-
HasLoc (..),
130-
EpToken (..))
129+
HasLoc (..))
131130
#endif
132131

133132

@@ -680,14 +679,16 @@ suggestDeleteUnusedBinding
680679
indexedContent
681680
name
682681
(L _ Match{m_grhss=GRHSs{grhssLocalBinds}}) = do
683-
let go bag lsigs =
682+
let emptyBag bag =
684683
#if MIN_VERSION_ghc(9,11,0)
685-
if null bag
684+
null bag
686685
#else
687-
if isEmptyBag bag
686+
isEmptyBag bag
688687
#endif
689-
then []
690-
else concatMap (findRelatedSpanForHsBind indexedContent name lsigs) bag
688+
go bag lsigs =
689+
if emptyBag bag
690+
then []
691+
else concatMap (findRelatedSpanForHsBind indexedContent name lsigs) bag
691692
case grhssLocalBinds of
692693
(HsValBinds _ (ValBinds _ bag lsigs)) -> go bag lsigs
693694
_ -> []
@@ -858,7 +859,6 @@ suggestAddTypeAnnotationToSatisfyConstraints sourceOpt Diagnostic{_range=_range,
858859
| otherwise = []
859860
where
860861
makeAnnotatedLit ty lit = "(" <> lit <> " :: " <> ty <> ")"
861-
#if MIN_VERSION_ghc(9,4,0)
862862
pat multiple at inArg inExpr = T.concat [ ".*Defaulting the type variable "
863863
, ".*to type ‘([^ ]+)’ "
864864
, "in the following constraint"
@@ -869,17 +869,6 @@ suggestAddTypeAnnotationToSatisfyConstraints sourceOpt Diagnostic{_range=_range,
869869
, if inExpr then ".+In the expression" else ""
870870
, ".+In the expression"
871871
]
872-
#else
873-
pat multiple at inArg inExpr = T.concat [ ".*Defaulting the following constraint"
874-
, if multiple then "s" else ""
875-
, " to type ‘([^ ]+)’ "
876-
, ".*arising from the literal ‘(.+)’"
877-
, if inArg then ".+In the.+argument" else ""
878-
, if at then ".+at ([^ ]*)" else ""
879-
, if inExpr then ".+In the expression" else ""
880-
, ".+In the expression"
881-
]
882-
#endif
883872
codeEdit range ty lit replacement =
884873
let title = "Add type annotation ‘" <> ty <> "’ to ‘" <> lit <> ""
885874
edits = [TextEdit range replacement]
@@ -1757,8 +1746,8 @@ findPositionAfterModuleName ps _hsmodName' = do
17571746
EpAnnNotUsed -> Nothing
17581747
#endif
17591748
#if MIN_VERSION_ghc(9,11,0)
1760-
filterWhere (EpTok loc) = Just loc
1761-
filterWhere _ = Nothing
1749+
filterWhere (EpTok loc) = Just loc
1750+
filterWhere _ = Nothing
17621751
#else
17631752
filterWhere (AddEpAnn AnnWhere loc) = Just loc
17641753
filterWhere _ = Nothing
@@ -1797,7 +1786,7 @@ findPositionAfterModuleName ps _hsmodName' = do
17971786

17981787
#if MIN_VERSION_ghc(9,11,0)
17991788
anchorOpLine :: EpaLocation' a -> Int
1800-
anchorOpLine EpaSpan{} = 0
1789+
anchorOpLine EpaSpan{} = 0
18011790
anchorOpLine (EpaDelta _ (SameLine _) _) = 0
18021791
anchorOpLine (EpaDelta _ (DifferentLine line _) _) = line
18031792
#elif MIN_VERSION_ghc(9,9,0)

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

Lines changed: 1 addition & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -139,10 +139,8 @@ removeConstraint toRemove = go . traceAst "REMOVE_CONSTRAINT_input"
139139
go :: LHsType GhcPs -> Rewrite
140140
#if MIN_VERSION_ghc(9,9,0)
141141
go lHsType@(makeDeltaAst -> L l it@HsQualTy{hst_ctxt = L l' ctxt, hst_body}) = Rewrite (locA lHsType) $ \_ -> do
142-
#elif MIN_VERSION_ghc(9,4,0)
143-
go (L l it@HsQualTy{hst_ctxt = L l' ctxt, hst_body}) = Rewrite (locA l) $ \_ -> do
144142
#else
145-
go (L l it@HsQualTy{hst_ctxt = Just (L l' ctxt), hst_body}) = Rewrite (locA l) $ \_ -> do
143+
go (L l it@HsQualTy{hst_ctxt = L l' ctxt, hst_body}) = Rewrite (locA l) $ \_ -> do
146144
#endif
147145
let ctxt' = filter (not . toRemove) ctxt
148146
removeStuff = (toRemove <$> headMaybe ctxt) == Just True
@@ -151,11 +149,7 @@ removeConstraint toRemove = go . traceAst "REMOVE_CONSTRAINT_input"
151149
[] -> hst_body'
152150
_ -> do
153151
let ctxt'' = over _last (first removeComma) ctxt'
154-
#if MIN_VERSION_ghc(9,4,0)
155152
L l $ it{ hst_ctxt = L l' ctxt''
156-
#else
157-
L l $ it{ hst_ctxt = Just $ L l' ctxt''
158-
#endif
159153
, hst_body = hst_body'
160154
}
161155
go (L _ (HsParTy _ ty)) = go ty
@@ -172,11 +166,7 @@ appendConstraint ::
172166
Rewrite
173167
appendConstraint constraintT = go . traceAst "appendConstraint"
174168
where
175-
#if MIN_VERSION_ghc(9,4,0)
176169
go (L l it@HsQualTy{hst_ctxt = L l' ctxt}) = Rewrite (locA l) $ \df -> do
177-
#else
178-
go (L l it@HsQualTy{hst_ctxt = Just (L l' ctxt)}) = Rewrite (locA l) $ \df -> do
179-
#endif
180170
constraint <- liftParseAST df constraintT
181171
constraint <- pure $ setEntryDP constraint (SameLine 1)
182172
#if MIN_VERSION_ghc(9,9,0)
@@ -196,23 +186,15 @@ appendConstraint constraintT = go . traceAst "appendConstraint"
196186
#endif
197187
_ -> Nothing
198188
ctxt' = over _last (first addComma) $ map dropHsParTy ctxt
199-
#if MIN_VERSION_ghc(9,4,0)
200189
return $ L l $ it{hst_ctxt = L l'' $ ctxt' ++ [constraint]}
201-
#else
202-
return $ L l $ it{hst_ctxt = Just $ L l'' $ ctxt' ++ [constraint]}
203-
#endif
204190
go (L _ HsForAllTy{hst_body}) = go hst_body
205191
go (L _ (HsParTy _ ty)) = go ty
206192
go ast@(L l _) = Rewrite (locA l) $ \df -> do
207193
-- there isn't a context, so we must create one
208194
constraint <- liftParseAST df constraintT
209195
lContext <- uniqueSrcSpanT
210196
lTop <- uniqueSrcSpanT
211-
#if MIN_VERSION_ghc(9,4,0)
212197
let context = reAnnL annCtxt emptyComments $ L lContext [resetEntryDP constraint]
213-
#else
214-
let context = Just $ reAnnL annCtxt emptyComments $ L lContext [resetEntryDP constraint]
215-
#endif
216198
#if MIN_VERSION_ghc(9,11,0)
217199
annCtxt = AnnContext (Just (EpUniTok (epl 1) NormalSyntax)) [EpTok (epl 0) | needsParens] [EpTok (epl 0) | needsParens]
218200
#else

0 commit comments

Comments
 (0)