Skip to content

Commit

Permalink
Remove conditional source code for ghc < 9.0
Browse files Browse the repository at this point in the history
  • Loading branch information
blackgnezdo committed Dec 5, 2024
1 parent 824537a commit b73029d
Show file tree
Hide file tree
Showing 19 changed files with 41 additions and 430 deletions.
55 changes: 3 additions & 52 deletions ghc-show-ast/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,10 @@ import qualified GHC.Types.Error as GHC (NoDiagnosticOpts(..))
#elif MIN_VERSION_ghc(9,2,0)
import qualified GHC.Driver.Errors as Error
import qualified GHC.Parser.Errors.Ppr as Error
#elif MIN_VERSION_ghc(9,0,0)
#else
import qualified GHC.Utils.Error as Error
#endif

#if MIN_VERSION_ghc(9,0,1)
import GHC.Data.FastString
import GHC.Types.Name
( Name
Expand Down Expand Up @@ -60,57 +59,16 @@ import qualified GHC.Types.SrcLoc as GHC
import qualified GHC.Data.StringBuffer as GHC
import GHC.Paths (libdir)
import GHC.Driver.Monad (liftIO)
#else
import FastString
import Name
( Name
, isExternalName
, isInternalName
, isSystemName
, isWiredInName
, nameOccName
, nameUnique
)
import OccName
( OccName
, occNameSpace
, occNameString
, NameSpace
, varName
, dataName
, tvName
, tcClsName
)

import qualified DynFlags as GHC
import qualified FastString as GHC
import qualified GHC as GHC
import qualified GhcMonad as GHC
import qualified HeaderInfo as GHC
import qualified Lexer as GHC
import qualified Parser as Parser
import qualified SrcLoc as GHC
import qualified StringBuffer as GHC
import GHC.Paths (libdir)
#if MIN_VERSION_ghc(8,10,0)
import GhcMonad (liftIO)
import qualified ErrUtils as Error
#else
import qualified Outputable as GHC
#endif
#endif

#if MIN_VERSION_ghc(8,10,0)
import System.Exit (exitFailure)
#endif

main :: IO ()
main = do
[f] <- getArgs
result <- parseModule f
print $ gPrint result

#if MIN_VERSION_ghc(9,0,1) && !MIN_VERSION_ghc(9,6,0)
#if !MIN_VERSION_ghc(9,6,0)
parseModule :: FilePath -> IO GHC.HsModule
#else
parseModule :: FilePath -> IO (GHC.HsModule GHC.GhcPs)
Expand Down Expand Up @@ -177,18 +135,11 @@ parseModule f = GHC.runGhc (Just libdir) $ do
let errors = Error.pprError <$> GHC.getErrorMessages s
Error.printBagOfErrors logger dflags errors
exitFailure
#elif MIN_VERSION_ghc(8,10,0)
#else
GHC.PFailed s -> liftIO $ do
let (_warnings, errors) = GHC.messages s dflags
Error.printBagOfErrors dflags errors
exitFailure
#else
GHC.PFailed
-- Note: using printBagOfErrors on the messages doesn't produce any
-- useful output on older GHCs; so instead print the docs directly.
_messages
loc docs ->
error $ GHC.showPpr dflags loc ++ ": " ++ GHC.showSDoc dflags docs
#endif

gPrint :: Data a => a -> Doc
Expand Down
13 changes: 0 additions & 13 deletions src/GHC/SourceGen/Binds.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,20 +46,13 @@ module GHC.SourceGen.Binds
, (<--)
) where

#if MIN_VERSION_ghc(9,0,0)
import GHC (LexicalFixity(..))
#else
import GHC.Types.Basic (LexicalFixity(..))
#endif
import Data.Bool (bool)
import Data.Maybe (fromMaybe)
import GHC.Hs.Binds
import GHC.Hs.Expr
import GHC.Hs.Type
import GHC.Plugins (isSymOcc)
#if !MIN_VERSION_ghc(9,0,1)
import GHC.Tc.Types.Evidence (HsWrapper(WpHole))
#endif

#if MIN_VERSION_ghc(9,10,0)
import GHC.Parser.Annotation (noAnn)
Expand Down Expand Up @@ -113,9 +106,6 @@ funBindsWithFixity :: HasValBind t => Maybe LexicalFixity -> OccNameStr -> [RawM
funBindsWithFixity fixity name matches = bindB $ withPlaceHolder
(noExt FunBind name'
(matchGroup context matches)
#if !MIN_VERSION_ghc(9,0,1)
WpHole
#endif
)
#if !MIN_VERSION_ghc(9,6,0)
[]
Expand Down Expand Up @@ -329,11 +319,8 @@ stmt e =
(<--) :: Pat' -> HsExpr' -> Stmt'
#if MIN_VERSION_ghc(9,10,0)
p <-- e = withPlaceHolder $ BindStmt [] (builtPat p) (mkLocated e)
#elif MIN_VERSION_ghc(9,0,0)
p <-- e = withPlaceHolder $ withEpAnnNotUsed BindStmt (builtPat p) (mkLocated e)
#else
p <-- e = withPlaceHolder $ withEpAnnNotUsed BindStmt (builtPat p) (mkLocated e)
noSyntaxExpr noSyntaxExpr
#endif
infixl 1 <--

Expand Down
20 changes: 2 additions & 18 deletions src/GHC/SourceGen/Binds/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@
{-# LANGUAGE CPP #-}
module GHC.SourceGen.Binds.Internal where

#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.Basic ( Origin(Generated)
#if MIN_VERSION_ghc(9,10,0)
, GenReason(OtherExpansion)
Expand All @@ -17,18 +16,10 @@ import GHC.Types.Basic ( Origin(Generated)
#endif
)
import GHC.Data.Bag (listToBag)
#else
import BasicTypes (Origin(Generated))
import Bag (listToBag)
#endif
import GHC.Hs.Binds
import GHC.Hs.Decls
import GHC.Hs.Expr (MatchGroup(..), Match(..), GRHSs(..))

#if !MIN_VERSION_ghc(8,6,0)
import PlaceHolder (PlaceHolder(..))
#endif

#if MIN_VERSION_ghc(9,10,0)
import GHC.Parser.Annotation (noAnn)
#endif
Expand All @@ -54,14 +45,9 @@ valBinds vbs =
$ withNoAnnSortKey ValBinds
(listToBag $ map mkLocated binds)
(map mkLocated sigs)
#elif MIN_VERSION_ghc(8,6,0)
withEpAnnNotUsed HsValBinds
$ withNoAnnSortKey ValBinds
(listToBag $ map mkLocated binds)
(map mkLocated sigs)
#else
withEpAnnNotUsed HsValBinds
$ noExt ValBindsIn
$ withNoAnnSortKey ValBinds
(listToBag $ map mkLocated binds)
(map mkLocated sigs)
#endif
Expand Down Expand Up @@ -112,9 +98,7 @@ matchGroup context matches =
noExt MG
#endif
matches'
#if !MIN_VERSION_ghc(8,6,0)
[] PlaceHolder
#elif !MIN_VERSION_ghc(9,6,0)
#if !MIN_VERSION_ghc(9,6,0)
Generated
#endif
where
Expand Down
68 changes: 6 additions & 62 deletions src/GHC/SourceGen/Decl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,9 +29,7 @@ module GHC.SourceGen.Decl
, derivingStock
, derivingAnyclass
, derivingNewtype
#if MIN_VERSION_ghc(8,6,0)
, derivingVia
#endif
, standaloneDeriving
, standaloneDerivingStock
, standaloneDerivingNewtype
Expand All @@ -51,7 +49,6 @@ module GHC.SourceGen.Decl
, patSynBind
) where

#if MIN_VERSION_ghc(9,0,0)
import GHC (LexicalFixity(Prefix))
import GHC.Data.Bag (listToBag)

Expand All @@ -62,14 +59,6 @@ import GHC (GhcPs, LayoutInfo (NoLayoutInfo))
#else
import GHC.Types.SrcLoc (LayoutInfo(NoLayoutInfo))
#endif

#else
import BasicTypes (LexicalFixity(Prefix))
import Bag (listToBag)
#endif
#if !MIN_VERSION_ghc(8,6,0)
import BasicTypes (DerivStrategy(..))
#endif
import GHC.Hs.Binds
import GHC.Hs.Decls

Expand All @@ -86,29 +75,19 @@ import GHC.Hs.Type
, HsSrcBang(..)
, HsType(..)
, LHsType
#if MIN_VERSION_ghc(8,6,0)
, HsWildCardBndrs (..)
#endif
#if MIN_VERSION_ghc(8,8,0)
, HsArg(..)
#endif
, SrcStrictness(..)
, SrcUnpackedness(..)
#if MIN_VERSION_ghc(9,0,0)
, hsUnrestricted
#endif
)

#if MIN_VERSION_ghc(9,10,0)
import GHC.Parser.Annotation (AnnSortKey(..), EpAnn(..), EpLayout (EpNoLayout))
#elif MIN_VERSION_ghc(9,2,0)
import GHC.Parser.Annotation (AnnSortKey(..), EpAnn(..))
#elif MIN_VERSION_ghc(8,10,0)
import GHC.Hs.Extension (NoExtField(NoExtField))
#elif MIN_VERSION_ghc(8,6,0)
import GHC.Hs.Extension (NoExt(NoExt))
#else
import PlaceHolder (PlaceHolder(..))
import GHC.Hs.Extension (NoExtField(NoExtField))
#endif

import GHC.SourceGen.Binds.Internal
Expand Down Expand Up @@ -191,14 +170,8 @@ class' context name vars decls
, tcdCExt = (EpAnnNotUsed, NoAnnSortKey)
#elif MIN_VERSION_ghc(9,2,0)
, tcdCExt = (EpAnnNotUsed, NoAnnSortKey, NoLayoutInfo)
#elif MIN_VERSION_ghc(9,0,0)
, tcdCExt = NoLayoutInfo
#elif MIN_VERSION_ghc(8,10,0)
, tcdCExt = NoExtField
#elif MIN_VERSION_ghc(8,6,0)
, tcdCExt = NoExt
#else
, tcdFVs = PlaceHolder
, tcdCExt = NoLayoutInfo
#endif
, tcdLName = typeRdrName $ unqual name
, tcdTyVars = mkQTyVars vars
Expand Down Expand Up @@ -261,10 +234,8 @@ instance' ty decls = noExt InstD $ noExt ClsInstD $ ClsInstDecl
, cid_ext = (Nothing, [], NoAnnSortKey)
#elif MIN_VERSION_ghc(9,2,0)
, cid_ext = (EpAnnNotUsed, NoAnnSortKey)
#elif MIN_VERSION_ghc(8,10,0)
#else
, cid_ext = NoExtField
#elif MIN_VERSION_ghc(8,6,0)
, cid_ext = NoExt
#endif
, cid_binds = listToBag [mkLocated b | InstBind b <- decls]
, cid_sigs = [mkLocated sig | InstSig sig <- decls]
Expand Down Expand Up @@ -317,19 +288,6 @@ tyFamInst name params ty = tyFamInstD
tyFamInstDecl = withEpAnnNotUsed TyFamInstDecl
famEqn tycon bndrs pats = withEpAnnNotUsed FamEqn tycon bndrs (map HsValArg pats)
eqn_bndrs = noExt HsOuterImplicit
#elif MIN_VERSION_ghc(8,8,0)
tyFamInst name params ty = tyFamInstD
$ tyFamInstDecl
$ famEqn
(typeRdrName name)
eqn_bndrs
(map mkLocated params)
Prefix
(mkLocated ty)
where
tyFamInstDecl = TyFamInstDecl . withPlaceHolder . noExt (withPlaceHolder HsIB)
famEqn tycon bndrs pats = noExt FamEqn tycon bndrs (map HsValArg pats)
eqn_bndrs = Nothing
#else
tyFamInst name params ty = tyFamInstD
$ tyFamInstDecl
Expand All @@ -341,7 +299,7 @@ tyFamInst name params ty = tyFamInstD
(mkLocated ty)
where
tyFamInstDecl = TyFamInstDecl . withPlaceHolder . noExt (withPlaceHolder HsIB)
famEqn tycon _ = noExt FamEqn tycon
famEqn tycon bndrs pats = noExt FamEqn tycon bndrs (map HsValArg pats)
eqn_bndrs = Nothing
#endif

Expand Down Expand Up @@ -541,11 +499,6 @@ strict f = f { strictness = SrcStrict }
lazy :: Field -> Field
lazy f = f { strictness = SrcLazy }

#if !MIN_VERSION_ghc(9,0,0)
hsUnrestricted :: a -> a
hsUnrestricted = id
#endif

renderField :: Field -> LHsType GhcPs
-- TODO: parenthesizeTypeForApp is an overestimate in the case of
-- rendering an infix or record type.
Expand All @@ -567,10 +520,8 @@ renderCon98Decl name details =
conDeclH98 = ConDeclH98 []
#elif MIN_VERSION_ghc(9,2,0)
conDeclH98 = withEpAnnNotUsed ConDeclH98
#elif MIN_VERSION_ghc(8,6,0)
conDeclH98 n = noExt ConDeclH98 n . builtLoc
#else
conDeclH98 n _ _ = ConDeclH98 n Nothing
conDeclH98 n = noExt ConDeclH98 n . builtLoc
#endif

deriving' :: [HsType'] -> HsDerivingClause'
Expand Down Expand Up @@ -626,7 +577,6 @@ derivingAnyclass = derivingWay (Just strat)
strat = AnyclassStrategy
#endif

#if MIN_VERSION_ghc(8,6,0)
-- | A `DerivingVia` clause.
--
-- > deriving (Eq, Show) via T
Expand All @@ -643,7 +593,6 @@ derivingVia t = derivingWay (Just $ strat $ sigType t)
#else
strat = ViaStrategy
#endif
#endif

standaloneDeriving :: HsType' -> HsDecl'
standaloneDeriving = standaloneDerivingWay Nothing
Expand Down Expand Up @@ -691,12 +640,7 @@ standaloneDerivingWay way ty = noExt DerivD derivDecl
#else
withEpAnnNotUsed DerivDecl (hsWC $ sigType ty) (fmap builtLoc way) Nothing
#endif
hsWC =
#if MIN_VERSION_ghc(8,6,0)
noExt HsWC
#else
id
#endif
hsWC = noExt HsWC

-- | Declares multiple pattern signatures of the same type.
--
Expand Down
Loading

0 comments on commit b73029d

Please # to comment.