Skip to content

Commit 10a9e22

Browse files
committed
Remove conditional source code for ghc < 9.0
1 parent e22811b commit 10a9e22

File tree

19 files changed

+41
-430
lines changed

19 files changed

+41
-430
lines changed

ghc-show-ast/Main.hs

Lines changed: 3 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -23,11 +23,10 @@ import qualified GHC.Types.Error as GHC (NoDiagnosticOpts(..))
2323
#elif MIN_VERSION_ghc(9,2,0)
2424
import qualified GHC.Driver.Errors as Error
2525
import qualified GHC.Parser.Errors.Ppr as Error
26-
#elif MIN_VERSION_ghc(9,0,0)
26+
#else
2727
import qualified GHC.Utils.Error as Error
2828
#endif
2929

30-
#if MIN_VERSION_ghc(9,0,1)
3130
import GHC.Data.FastString
3231
import GHC.Types.Name
3332
( Name
@@ -60,57 +59,16 @@ import qualified GHC.Types.SrcLoc as GHC
6059
import qualified GHC.Data.StringBuffer as GHC
6160
import GHC.Paths (libdir)
6261
import GHC.Driver.Monad (liftIO)
63-
#else
64-
import FastString
65-
import Name
66-
( Name
67-
, isExternalName
68-
, isInternalName
69-
, isSystemName
70-
, isWiredInName
71-
, nameOccName
72-
, nameUnique
73-
)
74-
import OccName
75-
( OccName
76-
, occNameSpace
77-
, occNameString
78-
, NameSpace
79-
, varName
80-
, dataName
81-
, tvName
82-
, tcClsName
83-
)
84-
85-
import qualified DynFlags as GHC
86-
import qualified FastString as GHC
87-
import qualified GHC as GHC
88-
import qualified GhcMonad as GHC
89-
import qualified HeaderInfo as GHC
90-
import qualified Lexer as GHC
91-
import qualified Parser as Parser
92-
import qualified SrcLoc as GHC
93-
import qualified StringBuffer as GHC
94-
import GHC.Paths (libdir)
95-
#if MIN_VERSION_ghc(8,10,0)
96-
import GhcMonad (liftIO)
97-
import qualified ErrUtils as Error
98-
#else
99-
import qualified Outputable as GHC
100-
#endif
101-
#endif
10262

103-
#if MIN_VERSION_ghc(8,10,0)
10463
import System.Exit (exitFailure)
105-
#endif
10664

10765
main :: IO ()
10866
main = do
10967
[f] <- getArgs
11068
result <- parseModule f
11169
print $ gPrint result
11270

113-
#if MIN_VERSION_ghc(9,0,1) && !MIN_VERSION_ghc(9,6,0)
71+
#if !MIN_VERSION_ghc(9,6,0)
11472
parseModule :: FilePath -> IO GHC.HsModule
11573
#else
11674
parseModule :: FilePath -> IO (GHC.HsModule GHC.GhcPs)
@@ -177,18 +135,11 @@ parseModule f = GHC.runGhc (Just libdir) $ do
177135
let errors = Error.pprError <$> GHC.getErrorMessages s
178136
Error.printBagOfErrors logger dflags errors
179137
exitFailure
180-
#elif MIN_VERSION_ghc(8,10,0)
138+
#else
181139
GHC.PFailed s -> liftIO $ do
182140
let (_warnings, errors) = GHC.messages s dflags
183141
Error.printBagOfErrors dflags errors
184142
exitFailure
185-
#else
186-
GHC.PFailed
187-
-- Note: using printBagOfErrors on the messages doesn't produce any
188-
-- useful output on older GHCs; so instead print the docs directly.
189-
_messages
190-
loc docs ->
191-
error $ GHC.showPpr dflags loc ++ ": " ++ GHC.showSDoc dflags docs
192143
#endif
193144

194145
gPrint :: Data a => a -> Doc

src/GHC/SourceGen/Binds.hs

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -46,20 +46,13 @@ module GHC.SourceGen.Binds
4646
, (<--)
4747
) where
4848

49-
#if MIN_VERSION_ghc(9,0,0)
5049
import GHC (LexicalFixity(..))
51-
#else
52-
import GHC.Types.Basic (LexicalFixity(..))
53-
#endif
5450
import Data.Bool (bool)
5551
import Data.Maybe (fromMaybe)
5652
import GHC.Hs.Binds
5753
import GHC.Hs.Expr
5854
import GHC.Hs.Type
5955
import GHC.Plugins (isSymOcc)
60-
#if !MIN_VERSION_ghc(9,0,1)
61-
import GHC.Tc.Types.Evidence (HsWrapper(WpHole))
62-
#endif
6356

6457
#if MIN_VERSION_ghc(9,10,0)
6558
import GHC.Parser.Annotation (noAnn)
@@ -113,9 +106,6 @@ funBindsWithFixity :: HasValBind t => Maybe LexicalFixity -> OccNameStr -> [RawM
113106
funBindsWithFixity fixity name matches = bindB $ withPlaceHolder
114107
(noExt FunBind name'
115108
(matchGroup context matches)
116-
#if !MIN_VERSION_ghc(9,0,1)
117-
WpHole
118-
#endif
119109
)
120110
#if !MIN_VERSION_ghc(9,6,0)
121111
[]
@@ -329,11 +319,8 @@ stmt e =
329319
(<--) :: Pat' -> HsExpr' -> Stmt'
330320
#if MIN_VERSION_ghc(9,10,0)
331321
p <-- e = withPlaceHolder $ BindStmt [] (builtPat p) (mkLocated e)
332-
#elif MIN_VERSION_ghc(9,0,0)
333-
p <-- e = withPlaceHolder $ withEpAnnNotUsed BindStmt (builtPat p) (mkLocated e)
334322
#else
335323
p <-- e = withPlaceHolder $ withEpAnnNotUsed BindStmt (builtPat p) (mkLocated e)
336-
noSyntaxExpr noSyntaxExpr
337324
#endif
338325
infixl 1 <--
339326

src/GHC/SourceGen/Binds/Internal.hs

Lines changed: 2 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
{-# LANGUAGE CPP #-}
88
module GHC.SourceGen.Binds.Internal where
99

10-
#if MIN_VERSION_ghc(9,0,0)
1110
import GHC.Types.Basic ( Origin(Generated)
1211
#if MIN_VERSION_ghc(9,10,0)
1312
, GenReason(OtherExpansion)
@@ -17,18 +16,10 @@ import GHC.Types.Basic ( Origin(Generated)
1716
#endif
1817
)
1918
import GHC.Data.Bag (listToBag)
20-
#else
21-
import BasicTypes (Origin(Generated))
22-
import Bag (listToBag)
23-
#endif
2419
import GHC.Hs.Binds
2520
import GHC.Hs.Decls
2621
import GHC.Hs.Expr (MatchGroup(..), Match(..), GRHSs(..))
2722

28-
#if !MIN_VERSION_ghc(8,6,0)
29-
import PlaceHolder (PlaceHolder(..))
30-
#endif
31-
3223
#if MIN_VERSION_ghc(9,10,0)
3324
import GHC.Parser.Annotation (noAnn)
3425
#endif
@@ -54,14 +45,9 @@ valBinds vbs =
5445
$ withNoAnnSortKey ValBinds
5546
(listToBag $ map mkLocated binds)
5647
(map mkLocated sigs)
57-
#elif MIN_VERSION_ghc(8,6,0)
58-
withEpAnnNotUsed HsValBinds
59-
$ withNoAnnSortKey ValBinds
60-
(listToBag $ map mkLocated binds)
61-
(map mkLocated sigs)
6248
#else
6349
withEpAnnNotUsed HsValBinds
64-
$ noExt ValBindsIn
50+
$ withNoAnnSortKey ValBinds
6551
(listToBag $ map mkLocated binds)
6652
(map mkLocated sigs)
6753
#endif
@@ -112,9 +98,7 @@ matchGroup context matches =
11298
noExt MG
11399
#endif
114100
matches'
115-
#if !MIN_VERSION_ghc(8,6,0)
116-
[] PlaceHolder
117-
#elif !MIN_VERSION_ghc(9,6,0)
101+
#if !MIN_VERSION_ghc(9,6,0)
118102
Generated
119103
#endif
120104
where

src/GHC/SourceGen/Decl.hs

Lines changed: 6 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -29,9 +29,7 @@ module GHC.SourceGen.Decl
2929
, derivingStock
3030
, derivingAnyclass
3131
, derivingNewtype
32-
#if MIN_VERSION_ghc(8,6,0)
3332
, derivingVia
34-
#endif
3533
, standaloneDeriving
3634
, standaloneDerivingStock
3735
, standaloneDerivingNewtype
@@ -51,7 +49,6 @@ module GHC.SourceGen.Decl
5149
, patSynBind
5250
) where
5351

54-
#if MIN_VERSION_ghc(9,0,0)
5552
import GHC (LexicalFixity(Prefix))
5653
import GHC.Data.Bag (listToBag)
5754

@@ -62,14 +59,6 @@ import GHC (GhcPs, LayoutInfo (NoLayoutInfo))
6259
#else
6360
import GHC.Types.SrcLoc (LayoutInfo(NoLayoutInfo))
6461
#endif
65-
66-
#else
67-
import BasicTypes (LexicalFixity(Prefix))
68-
import Bag (listToBag)
69-
#endif
70-
#if !MIN_VERSION_ghc(8,6,0)
71-
import BasicTypes (DerivStrategy(..))
72-
#endif
7362
import GHC.Hs.Binds
7463
import GHC.Hs.Decls
7564

@@ -86,29 +75,19 @@ import GHC.Hs.Type
8675
, HsSrcBang(..)
8776
, HsType(..)
8877
, LHsType
89-
#if MIN_VERSION_ghc(8,6,0)
9078
, HsWildCardBndrs (..)
91-
#endif
92-
#if MIN_VERSION_ghc(8,8,0)
9379
, HsArg(..)
94-
#endif
9580
, SrcStrictness(..)
9681
, SrcUnpackedness(..)
97-
#if MIN_VERSION_ghc(9,0,0)
9882
, hsUnrestricted
99-
#endif
10083
)
10184

10285
#if MIN_VERSION_ghc(9,10,0)
10386
import GHC.Parser.Annotation (AnnSortKey(..), EpAnn(..), EpLayout (EpNoLayout))
10487
#elif MIN_VERSION_ghc(9,2,0)
10588
import GHC.Parser.Annotation (AnnSortKey(..), EpAnn(..))
106-
#elif MIN_VERSION_ghc(8,10,0)
107-
import GHC.Hs.Extension (NoExtField(NoExtField))
108-
#elif MIN_VERSION_ghc(8,6,0)
109-
import GHC.Hs.Extension (NoExt(NoExt))
11089
#else
111-
import PlaceHolder (PlaceHolder(..))
90+
import GHC.Hs.Extension (NoExtField(NoExtField))
11291
#endif
11392

11493
import GHC.SourceGen.Binds.Internal
@@ -191,14 +170,8 @@ class' context name vars decls
191170
, tcdCExt = (EpAnnNotUsed, NoAnnSortKey)
192171
#elif MIN_VERSION_ghc(9,2,0)
193172
, tcdCExt = (EpAnnNotUsed, NoAnnSortKey, NoLayoutInfo)
194-
#elif MIN_VERSION_ghc(9,0,0)
195-
, tcdCExt = NoLayoutInfo
196-
#elif MIN_VERSION_ghc(8,10,0)
197-
, tcdCExt = NoExtField
198-
#elif MIN_VERSION_ghc(8,6,0)
199-
, tcdCExt = NoExt
200173
#else
201-
, tcdFVs = PlaceHolder
174+
, tcdCExt = NoLayoutInfo
202175
#endif
203176
, tcdLName = typeRdrName $ unqual name
204177
, tcdTyVars = mkQTyVars vars
@@ -261,10 +234,8 @@ instance' ty decls = noExt InstD $ noExt ClsInstD $ ClsInstDecl
261234
, cid_ext = (Nothing, [], NoAnnSortKey)
262235
#elif MIN_VERSION_ghc(9,2,0)
263236
, cid_ext = (EpAnnNotUsed, NoAnnSortKey)
264-
#elif MIN_VERSION_ghc(8,10,0)
237+
#else
265238
, cid_ext = NoExtField
266-
#elif MIN_VERSION_ghc(8,6,0)
267-
, cid_ext = NoExt
268239
#endif
269240
, cid_binds = listToBag [mkLocated b | InstBind b <- decls]
270241
, cid_sigs = [mkLocated sig | InstSig sig <- decls]
@@ -317,19 +288,6 @@ tyFamInst name params ty = tyFamInstD
317288
tyFamInstDecl = withEpAnnNotUsed TyFamInstDecl
318289
famEqn tycon bndrs pats = withEpAnnNotUsed FamEqn tycon bndrs (map HsValArg pats)
319290
eqn_bndrs = noExt HsOuterImplicit
320-
#elif MIN_VERSION_ghc(8,8,0)
321-
tyFamInst name params ty = tyFamInstD
322-
$ tyFamInstDecl
323-
$ famEqn
324-
(typeRdrName name)
325-
eqn_bndrs
326-
(map mkLocated params)
327-
Prefix
328-
(mkLocated ty)
329-
where
330-
tyFamInstDecl = TyFamInstDecl . withPlaceHolder . noExt (withPlaceHolder HsIB)
331-
famEqn tycon bndrs pats = noExt FamEqn tycon bndrs (map HsValArg pats)
332-
eqn_bndrs = Nothing
333291
#else
334292
tyFamInst name params ty = tyFamInstD
335293
$ tyFamInstDecl
@@ -341,7 +299,7 @@ tyFamInst name params ty = tyFamInstD
341299
(mkLocated ty)
342300
where
343301
tyFamInstDecl = TyFamInstDecl . withPlaceHolder . noExt (withPlaceHolder HsIB)
344-
famEqn tycon _ = noExt FamEqn tycon
302+
famEqn tycon bndrs pats = noExt FamEqn tycon bndrs (map HsValArg pats)
345303
eqn_bndrs = Nothing
346304
#endif
347305

@@ -541,11 +499,6 @@ strict f = f { strictness = SrcStrict }
541499
lazy :: Field -> Field
542500
lazy f = f { strictness = SrcLazy }
543501

544-
#if !MIN_VERSION_ghc(9,0,0)
545-
hsUnrestricted :: a -> a
546-
hsUnrestricted = id
547-
#endif
548-
549502
renderField :: Field -> LHsType GhcPs
550503
-- TODO: parenthesizeTypeForApp is an overestimate in the case of
551504
-- rendering an infix or record type.
@@ -567,10 +520,8 @@ renderCon98Decl name details =
567520
conDeclH98 = ConDeclH98 []
568521
#elif MIN_VERSION_ghc(9,2,0)
569522
conDeclH98 = withEpAnnNotUsed ConDeclH98
570-
#elif MIN_VERSION_ghc(8,6,0)
571-
conDeclH98 n = noExt ConDeclH98 n . builtLoc
572523
#else
573-
conDeclH98 n _ _ = ConDeclH98 n Nothing
524+
conDeclH98 n = noExt ConDeclH98 n . builtLoc
574525
#endif
575526

576527
deriving' :: [HsType'] -> HsDerivingClause'
@@ -626,7 +577,6 @@ derivingAnyclass = derivingWay (Just strat)
626577
strat = AnyclassStrategy
627578
#endif
628579

629-
#if MIN_VERSION_ghc(8,6,0)
630580
-- | A `DerivingVia` clause.
631581
--
632582
-- > deriving (Eq, Show) via T
@@ -643,7 +593,6 @@ derivingVia t = derivingWay (Just $ strat $ sigType t)
643593
#else
644594
strat = ViaStrategy
645595
#endif
646-
#endif
647596

648597
standaloneDeriving :: HsType' -> HsDecl'
649598
standaloneDeriving = standaloneDerivingWay Nothing
@@ -691,12 +640,7 @@ standaloneDerivingWay way ty = noExt DerivD derivDecl
691640
#else
692641
withEpAnnNotUsed DerivDecl (hsWC $ sigType ty) (fmap builtLoc way) Nothing
693642
#endif
694-
hsWC =
695-
#if MIN_VERSION_ghc(8,6,0)
696-
noExt HsWC
697-
#else
698-
id
699-
#endif
643+
hsWC = noExt HsWC
700644

701645
-- | Declares multiple pattern signatures of the same type.
702646
--

0 commit comments

Comments
 (0)