diff --git a/.github/workflows/ci.yaml b/.github/workflows/ci.yaml index 88761d1..897b928 100644 --- a/.github/workflows/ci.yaml +++ b/.github/workflows/ci.yaml @@ -16,7 +16,7 @@ jobs: fail-fast: false matrix: os: [ubuntu-latest] - ghc: ["9.0", "9.2", "9.4", "9.6", "9.8", "9.10"] + ghc: ["9.0", "9.2", "9.4", "9.6", "9.8", "9.10", "9.12"] env: STACK_YAML: stack-${{ matrix.ghc }}.yaml runs-on: ${{ matrix.os }} diff --git a/ghc-source-gen.cabal b/ghc-source-gen.cabal index 789bda1..a024561 100644 --- a/ghc-source-gen.cabal +++ b/ghc-source-gen.cabal @@ -1,6 +1,6 @@ cabal-version: 1.12 --- This file has been generated from package.yaml by hpack version 0.36.0. +-- This file has been generated from package.yaml by hpack version 0.38.0. -- -- see: https://github.com/sol/hpack @@ -61,7 +61,7 @@ library TypeSynonymInstances build-depends: base >=4.7 && <5 - , ghc >=8.4 && <9.11 + , ghc >=8.4 && <9.13 default-language: Haskell2010 if impl(ghc<8.10) other-modules: @@ -102,13 +102,13 @@ test-suite name_test FlexibleInstances TypeSynonymInstances build-depends: - QuickCheck >=2.10 && <2.15 + QuickCheck >=2.10 && <2.17 , base >=4.7 && <5 - , ghc >=8.4 && <9.11 + , ghc >=8.4 && <9.13 , ghc-source-gen , tasty >=1.0 && <1.6 , tasty-hunit ==0.10.* - , tasty-quickcheck >=0.9 && <0.11 + , tasty-quickcheck >=0.9 && <0.12 default-language: Haskell2010 test-suite pprint_examples @@ -125,7 +125,7 @@ test-suite pprint_examples TypeSynonymInstances build-depends: base >=4.7 && <5 - , ghc >=8.4 && <9.11 + , ghc >=8.4 && <9.13 , ghc-paths ==0.1.* , ghc-source-gen , tasty >=1.0 && <1.6 @@ -151,7 +151,7 @@ test-suite pprint_test TypeSynonymInstances build-depends: base >=4.7 && <5 - , ghc >=8.4 && <9.11 + , ghc >=8.4 && <9.13 , ghc-paths ==0.1.* , ghc-source-gen , tasty >=1.0 && <1.6 diff --git a/package.yaml b/package.yaml index 21b2492..ab511d0 100644 --- a/package.yaml +++ b/package.yaml @@ -30,7 +30,7 @@ description: | dependencies: - base >= 4.7 && < 5 -- ghc >= 8.4 && < 9.11 +- ghc >= 8.4 && < 9.13 default-extensions: - DataKinds @@ -116,7 +116,7 @@ tests: source-dirs: tests dependencies: - ghc-source-gen - - QuickCheck >= 2.10 && < 2.15 + - QuickCheck >= 2.10 && < 2.17 - tasty >= 1.0 && < 1.6 - tasty-hunit == 0.10.* - - tasty-quickcheck >= 0.9 && < 0.11 + - tasty-quickcheck >= 0.9 && < 0.12 diff --git a/src/GHC/SourceGen/Binds.hs b/src/GHC/SourceGen/Binds.hs index 97e93c8..ebf3f2b 100644 --- a/src/GHC/SourceGen/Binds.hs +++ b/src/GHC/SourceGen/Binds.hs @@ -81,7 +81,11 @@ typeSigs names t = sigB $ TypeSig ann (map (typeRdrName . unqual) names) $ sigWcType t where +# if MIN_VERSION_ghc(9,12,0) + ann = AnnSig noAnn Nothing Nothing +# else ann = AnnSig noAnn [] +# endif #else sigB $ withEpAnnNotUsed TypeSig (map (typeRdrName . unqual) names) $ sigWcType t @@ -124,7 +128,11 @@ funBindsWithFixity fixity name matches = bindB $ withPlaceHolder name' = valueRdrName $ unqual name occ = valueOccName name fixity' = fromMaybe (bool Prefix Infix $ isSymOcc occ) fixity +#if MIN_VERSION_ghc(9,12,0) + context = FunRhs name' fixity' NoSrcStrict noAnn +#else context = FunRhs name' fixity' NoSrcStrict +#endif -- | Defines a function or value. -- @@ -328,7 +336,7 @@ stmt e = -- > bvar "x" <-- var "act" (<--) :: Pat' -> HsExpr' -> Stmt' #if MIN_VERSION_ghc(9,10,0) -p <-- e = withPlaceHolder $ BindStmt [] (builtPat p) (mkLocated e) +p <-- e = withPlaceHolder $ BindStmt noAnn (builtPat p) (mkLocated e) #elif MIN_VERSION_ghc(9,0,0) p <-- e = withPlaceHolder $ withEpAnnNotUsed BindStmt (builtPat p) (mkLocated e) #else diff --git a/src/GHC/SourceGen/Binds/Internal.hs b/src/GHC/SourceGen/Binds/Internal.hs index 0fbd71b..5a9b1c8 100644 --- a/src/GHC/SourceGen/Binds/Internal.hs +++ b/src/GHC/SourceGen/Binds/Internal.hs @@ -5,6 +5,7 @@ -- https://developers.google.com/open-source/licenses/bsd {-# LANGUAGE CPP #-} +{-# LANGUAGE TypeApplications #-} module GHC.SourceGen.Binds.Internal where #if MIN_VERSION_ghc(9,0,0) @@ -17,6 +18,7 @@ import GHC.Types.Basic ( Origin(Generated) #endif ) import GHC.Data.Bag (listToBag) +import GHC.Hs.Extension (GhcPs) #else import BasicTypes (Origin(Generated)) import Bag (listToBag) @@ -25,12 +27,16 @@ import GHC.Hs.Binds import GHC.Hs.Decls import GHC.Hs.Expr (MatchGroup(..), Match(..), GRHSs(..)) +#if MIN_VERSION_ghc(9,12,0) +import Language.Haskell.Syntax.Extension (wrapXRec, noExtField) +#endif + #if !MIN_VERSION_ghc(8,6,0) import PlaceHolder (PlaceHolder(..)) #endif #if MIN_VERSION_ghc(9,10,0) -import GHC.Parser.Annotation (noAnn) +import GHC.Parser.Annotation (noAnn, emptyComments) #endif import GHC.SourceGen.Pat.Internal (parenthesize) @@ -52,7 +58,11 @@ valBinds vbs = #if MIN_VERSION_ghc(9,10,0) HsValBinds noAnn $ withNoAnnSortKey ValBinds +# if MIN_VERSION_ghc(9,12,0) + (map mkLocated binds) +# else (listToBag $ map mkLocated binds) +# endif (map mkLocated sigs) #elif MIN_VERSION_ghc(8,6,0) withEpAnnNotUsed HsValBinds @@ -121,17 +131,22 @@ matchGroup context matches = matches' = mkLocated $ map (mkLocated . mkMatch) matches mkMatch :: RawMatch -> Match' LHsExpr' #if MIN_VERSION_ghc(9,10,0) - mkMatch r = Match [] context +# if MIN_VERSION_ghc(9,12,0) + mkMatch r = Match noExtField context + (wrapXRec @GhcPs $ map builtPat $ map parenthesize $ rawMatchPats r) +# else + mkMatch r = Match noAnn context (map builtPat $ map parenthesize $ rawMatchPats r) - (mkGRHSs $ rawMatchGRHSs r) +# endif #else mkMatch r = withEpAnnNotUsed Match context (map builtPat $ map parenthesize $ rawMatchPats r) - (mkGRHSs $ rawMatchGRHSs r) #endif + (mkGRHSs $ rawMatchGRHSs r) mkGRHSs :: RawGRHSs -> GRHSs' LHsExpr' mkGRHSs g = withEmptyEpAnnComments GRHSs +--mkGRHSs g = GRHSs emptyComments #if MIN_VERSION_ghc(9,4,0) (map mkLocated $ rawGRHSs g) #else @@ -166,7 +181,6 @@ type GuardedExpr = GRHS' LHsExpr' class HasValBind t where sigB :: Sig' -> t bindB :: HsBind' -> t - instance HasValBind HsDecl' where sigB = noExt SigD bindB = noExt ValD diff --git a/src/GHC/SourceGen/Decl.hs b/src/GHC/SourceGen/Decl.hs index 9546f2a..972b7e7 100644 --- a/src/GHC/SourceGen/Decl.hs +++ b/src/GHC/SourceGen/Decl.hs @@ -54,9 +54,11 @@ module GHC.SourceGen.Decl #if MIN_VERSION_ghc(9,0,0) import GHC (LexicalFixity(Prefix)) import GHC.Data.Bag (listToBag) +import GHC.Hs #if MIN_VERSION_ghc(9,10,0) import GHC (GhcPs) +import GHC.Parser.PostProcess (mkBangTy) #elif MIN_VERSION_ghc(9,6,0) import GHC (GhcPs, LayoutInfo (NoLayoutInfo)) #else @@ -66,6 +68,7 @@ import GHC.Types.SrcLoc (LayoutInfo(NoLayoutInfo)) #else import BasicTypes (LexicalFixity(Prefix)) import Bag (listToBag) +import GHC.Hs.Extension (GhcPs) #endif #if !MIN_VERSION_ghc(8,6,0) import BasicTypes (DerivStrategy(..)) @@ -74,8 +77,8 @@ import GHC.Hs.Binds import GHC.Hs.Decls import GHC.Hs.Type - ( ConDeclField(..) - , FieldOcc(..) + ( + FieldOcc(..) , HsConDetails(..) #if !MIN_VERSION_ghc(9,2,0) , HsImplicitBndrs (..) @@ -88,15 +91,13 @@ import GHC.Hs.Type , LHsType #if MIN_VERSION_ghc(8,6,0) , HsWildCardBndrs (..) + , ConDeclField (..) #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) @@ -117,7 +118,6 @@ import GHC.SourceGen.Name import GHC.SourceGen.Name.Internal import GHC.SourceGen.Syntax.Internal import GHC.SourceGen.Type.Internal -import GHC.Hs -- | A definition that can appear in the body of a @class@ declaration. -- @@ -185,7 +185,7 @@ class' context name vars decls = noExt TyClD $ ClassDecl { tcdCtxt = toHsContext $ mkLocated $ map mkLocated context #if MIN_VERSION_ghc(9,10,0) - , tcdCExt = ([], EpNoLayout, NoAnnSortKey) + , tcdCExt = (noAnn, EpNoLayout, NoAnnSortKey) #elif MIN_VERSION_ghc(9,6,0) , tcdLayout = NoLayoutInfo , tcdCExt = (EpAnnNotUsed, NoAnnSortKey) @@ -208,14 +208,18 @@ class' context name vars decls ] , tcdSigs = [mkLocated sig | ClassSig sig <- decls] , tcdMeths = +#if MIN_VERSION_ghc(9,12,0) + [mkLocated bind | ClassDefaultMethod bind <- decls] +#else listToBag [mkLocated bind | ClassDefaultMethod bind <- decls] +#endif , tcdATs = [] -- Associated types , tcdATDefs = [] -- Associated type defaults , tcdDocs = [] -- Haddocks } where #if MIN_VERSION_ghc(9,10,0) - funDep' = FunDep [] + funDep' = FunDep noAnn #elif MIN_VERSION_ghc(9,2,0) funDep' = withEpAnnNotUsed FunDep #else @@ -258,7 +262,7 @@ instance' :: HsType' -> [RawInstDecl] -> HsDecl' instance' ty decls = noExt InstD $ noExt ClsInstD $ ClsInstDecl { cid_poly_ty = sigType ty #if MIN_VERSION_ghc(9,10,0) - , cid_ext = (Nothing, [], NoAnnSortKey) + , cid_ext = (Nothing, noAnn, NoAnnSortKey) #elif MIN_VERSION_ghc(9,2,0) , cid_ext = (EpAnnNotUsed, NoAnnSortKey) #elif MIN_VERSION_ghc(8,10,0) @@ -266,7 +270,11 @@ instance' ty decls = noExt InstD $ noExt ClsInstD $ ClsInstDecl #elif MIN_VERSION_ghc(8,6,0) , cid_ext = NoExt #endif +#if MIN_VERSION_ghc(9,12,0) + , cid_binds = [mkLocated b | InstBind b <- decls] +#else , cid_binds = listToBag [mkLocated b | InstBind b <- decls] +#endif , cid_sigs = [mkLocated sig | InstSig sig <- decls] , cid_tyfam_insts = [mkLocated $ t | InstTyFam t <- decls] , cid_datafam_insts = [] @@ -295,14 +303,14 @@ tyFamInst :: HasTyFamInst t => RdrNameStr -> [HsType'] -> HsType' -> t tyFamInst name params ty = tyFamInstD $ tyFamInstDecl $ FamEqn - [] + noAnn (typeRdrName name) eqnBndrs (map (noExt HsValArg . mkLocated) params) Prefix (mkLocated ty) where - tyFamInstDecl = TyFamInstDecl [] + tyFamInstDecl = TyFamInstDecl noAnn eqnBndrs = noExt HsOuterImplicit #elif MIN_VERSION_ghc(9,2,0) tyFamInst name params ty = tyFamInstD @@ -353,7 +361,7 @@ tyFamInst name params ty = tyFamInstD type' :: OccNameStr -> [HsTyVarBndr'] -> HsType' -> HsDecl' type' name vars t = #if MIN_VERSION_ghc(9,10,0) - noExt TyClD $ withPlaceHolder $ SynDecl [] (typeRdrName $ unqual name) + noExt TyClD $ withPlaceHolder $ SynDecl noAnn (typeRdrName $ unqual name) (mkQTyVars vars) Prefix (mkLocated t) @@ -374,7 +382,17 @@ newOrDataType newOrDataType newOrData name vars conDecls derivs = noExt TyClD $ withPlaceHolder $ withPlaceHolder $ #if MIN_VERSION_ghc(9,6,0) -#if MIN_VERSION_ghc(9,10,0) +#if MIN_VERSION_ghc(9,12,0) + noExt DataDecl (typeRdrName $ unqual name) + (mkQTyVars vars) + Prefix + $ HsDataDefn noAnn + Nothing + Nothing + Nothing + (mkDataDefnCon newOrData conDecls) + (map mkLocated derivs) +#elif MIN_VERSION_ghc(9,10,0) DataDecl [] (typeRdrName $ unqual name) (mkQTyVars vars) Prefix @@ -495,7 +513,7 @@ recordCon name fields = renderCon98Decl name where mkLConDeclField (n, f) = #if MIN_VERSION_ghc(9,10,0) - mkLocated $ ConDeclField [] + mkLocated $ ConDeclField noAnn [mkLocated $ withPlaceHolder $ noExt FieldOcc $ valueRdrName $ unqual n] #elif MIN_VERSION_ghc(9,4,0) mkLocated $ withEpAnnNotUsed ConDeclField @@ -554,7 +572,7 @@ renderField f = wrap $ parenthesizeTypeForApp $ mkLocated $ fieldType f wrap = case strictness f of NoSrcStrict -> id #if MIN_VERSION_ghc(9,10,0) - s -> mkLocated . (HsBangTy [] $ noSourceText HsSrcBang NoSrcUnpack s) + s -> mkLocated . mkBangTy noAnn s #else s -> mkLocated . (withEpAnnNotUsed HsBangTy $ noSourceText HsSrcBang NoSrcUnpack s) #endif @@ -564,7 +582,7 @@ renderCon98Decl name details = conDeclH98 (typeRdrName $ unqual name) False [] Nothing details Nothing where #if MIN_VERSION_ghc(9,10,0) - conDeclH98 = ConDeclH98 [] + conDeclH98 = ConDeclH98 noAnn #elif MIN_VERSION_ghc(9,2,0) conDeclH98 = withEpAnnNotUsed ConDeclH98 #elif MIN_VERSION_ghc(8,6,0) @@ -579,7 +597,7 @@ deriving' = derivingWay Nothing derivingWay :: Maybe DerivStrategy' -> [HsType'] -> HsDerivingClause' derivingWay way ts = #if MIN_VERSION_ghc(9,10,0) - HsDerivingClause [] (fmap mkLocated way) $ mkLocated $ derivClauseTys $ map sigType ts + HsDerivingClause noAnn (fmap mkLocated way) $ mkLocated $ derivClauseTys $ map sigType ts #elif MIN_VERSION_ghc(9,4,0) withEpAnnNotUsed HsDerivingClause (fmap mkLocated way) $ mkLocated $ derivClauseTys $ map sigType ts #else @@ -597,7 +615,7 @@ derivingStock :: [HsType'] -> HsDerivingClause' derivingStock = derivingWay (Just strat) where #if MIN_VERSION_ghc(9,10,0) - strat = StockStrategy [] + strat = StockStrategy noAnn #elif MIN_VERSION_ghc(9,2,0) strat = withEpAnnNotUsed StockStrategy #else @@ -608,7 +626,7 @@ derivingNewtype :: [HsType'] -> HsDerivingClause' derivingNewtype = derivingWay (Just strat) where #if MIN_VERSION_ghc(9,10,0) - strat = NewtypeStrategy [] + strat = NewtypeStrategy noAnn #elif MIN_VERSION_ghc(9,2,0) strat = withEpAnnNotUsed NewtypeStrategy #else @@ -619,7 +637,7 @@ derivingAnyclass :: [HsType'] -> HsDerivingClause' derivingAnyclass = derivingWay (Just strat) where #if MIN_VERSION_ghc(9,10,0) - strat = AnyclassStrategy [] + strat = AnyclassStrategy noAnn #elif MIN_VERSION_ghc(9,2,0) strat = withEpAnnNotUsed AnyclassStrategy #else @@ -637,7 +655,7 @@ derivingVia :: HsType' -> [HsType'] -> HsDerivingClause' derivingVia t = derivingWay (Just $ strat $ sigType t) where #if MIN_VERSION_ghc(9,10,0) - strat = ViaStrategy . XViaStrategyPs [] + strat = ViaStrategy . XViaStrategyPs noAnn #elif MIN_VERSION_ghc(9,2,0) strat = ViaStrategy . withEpAnnNotUsed XViaStrategyPs #else @@ -652,7 +670,7 @@ standaloneDerivingStock :: HsType' -> HsDecl' standaloneDerivingStock = standaloneDerivingWay (Just strat) where #if MIN_VERSION_ghc(9,10,0) - strat = StockStrategy [] + strat = StockStrategy noAnn #elif MIN_VERSION_ghc(9,2,0) strat = withEpAnnNotUsed StockStrategy #else @@ -663,7 +681,7 @@ standaloneDerivingNewtype :: HsType' -> HsDecl' standaloneDerivingNewtype = standaloneDerivingWay (Just strat) where #if MIN_VERSION_ghc(9,10,0) - strat = NewtypeStrategy [] + strat = NewtypeStrategy noAnn #elif MIN_VERSION_ghc(9,2,0) strat = withEpAnnNotUsed NewtypeStrategy #else @@ -674,7 +692,7 @@ standaloneDerivingAnyclass :: HsType' -> HsDecl' standaloneDerivingAnyclass = standaloneDerivingWay (Just strat) where #if MIN_VERSION_ghc(9,10,0) - strat = AnyclassStrategy [] + strat = AnyclassStrategy noAnn #elif MIN_VERSION_ghc(9,2,0) strat = withEpAnnNotUsed AnyclassStrategy #else @@ -685,7 +703,7 @@ standaloneDerivingWay :: Maybe DerivStrategy' -> HsType' -> HsDecl' standaloneDerivingWay way ty = noExt DerivD derivDecl where derivDecl = #if MIN_VERSION_ghc(9,10,0) - DerivDecl (Nothing, []) (hsWC $ sigType ty) (fmap mkLocated way) Nothing + DerivDecl noAnn (hsWC $ sigType ty) (fmap mkLocated way) Nothing #elif MIN_VERSION_ghc(9,4,0) withEpAnnNotUsed DerivDecl (hsWC $ sigType ty) (fmap mkLocated way) Nothing #else @@ -731,7 +749,7 @@ patSynSig n = patSynSigs [n] patSynBind :: OccNameStr -> [OccNameStr] -> Pat' -> HsDecl' #if MIN_VERSION_ghc(9,10,0) patSynBind n ns p = bindB $ noExt PatSynBind - $ withPlaceHolder (PSB [] (valueRdrName $ unqual n)) + $ withPlaceHolder (PSB noAnn (valueRdrName $ unqual n)) (PrefixCon [] (map (valueRdrName . unqual) ns)) (builtPat p) ImplicitBidirectional diff --git a/src/GHC/SourceGen/Expr.hs b/src/GHC/SourceGen/Expr.hs index 9fd8992..493b65d 100644 --- a/src/GHC/SourceGen/Expr.hs +++ b/src/GHC/SourceGen/Expr.hs @@ -31,6 +31,7 @@ module GHC.SourceGen.Expr import GHC.Hs.Expr import GHC.Hs.Extension (GhcPs) #if MIN_VERSION_ghc(9,10,0) +import Control.Monad (mzero) import GHC.Hs.Expr (EpAnnHsCase (..)) import GHC.Parser.Annotation (EpToken(..), noAnn, noSpanAnchor) import GHC.Types.SourceText (SourceText(NoSourceText)) @@ -43,7 +44,12 @@ import GHC.Hs.Pat (HsFieldBind(..), HsRecFields(..)) #else import GHC.Hs.Pat (HsRecField'(..), HsRecFields(..)) #endif -import GHC.Hs.Type (FieldOcc(..), AmbiguousFieldOcc(..)) +import GHC.Hs.Type ( + FieldOcc(..) +#if !MIN_VERSION_ghc(9,12,0) + , AmbiguousFieldOcc(..) +#endif + ) import GHC.Hs.Utils (mkHsIf) import Data.String (fromString) #if MIN_VERSION_ghc(9,0,0) @@ -75,7 +81,9 @@ import GHC.SourceGen.Type.Internal overLabel :: String -> HsExpr' overLabel = hsOverLabel . fromString where -#if MIN_VERSION_ghc(9,10,0) +#if MIN_VERSION_ghc(9,12,0) + hsOverLabel = HsOverLabel NoSourceText +#elif MIN_VERSION_ghc(9,10,0) hsOverLabel = noExt HsOverLabel NoSourceText #elif MIN_VERSION_ghc(9,6,0) hsOverLabel = withEpAnnNotUsed HsOverLabel NoSourceText @@ -105,7 +113,11 @@ case' :: HsExpr' -> [RawMatch] -> HsExpr' case' e matches = HsCase ann (mkLocated e) $ matchGroup CaseAlt matches where - ann = EpAnnHsCase noSpanAnchor noSpanAnchor [] +# if MIN_VERSION_ghc(9,12,0) + ann = EpAnnHsCase noAnn noAnn +# elif MIN_VERSION_ghc(9,10,0) + ann = EpAnnHsCase noAnn noAnn [] +# endif #else case' e matches = withEpAnnNotUsed HsCase (mkLocated e) $ matchGroup CaseAlt matches @@ -113,14 +125,14 @@ case' e matches = withEpAnnNotUsed HsCase (mkLocated e) lambda :: [Pat'] -> HsExpr' -> HsExpr' #if MIN_VERSION_ghc(9,10,0) -lambda ps e = HsLam [] LamSingle $ matchGroup (LamAlt LamSingle) [match ps e] +lambda ps e = HsLam noAnn LamSingle $ matchGroup (LamAlt LamSingle) [match ps e] #else lambda ps e = noExt HsLam $ matchGroup LambdaExpr [match ps e] #endif lambdaCase :: [RawMatch] -> HsExpr' #if MIN_VERSION_ghc(9,10,0) -lambdaCase = HsLam [] LamCase . matchGroup CaseAlt +lambdaCase = HsLam noAnn LamCase . matchGroup CaseAlt #elif MIN_VERSION_ghc(9,4,0) lambdaCase = withEpAnnNotUsed HsLamCase LamCase . matchGroup CaseAlt #else @@ -151,7 +163,9 @@ if' x y z = mkHsIf -- > , guardedStmt (var "otherwise") $ rhs (string "h") -- > ] multiIf :: [GuardedExpr] -> HsExpr' -#if MIN_VERSION_ghc(9,10,0) +#if MIN_VERSION_ghc(9,12,0) +multiIf = withPlaceHolder (HsMultiIf (NoEpTok, NoEpTok, NoEpTok)) . map mkLocated +#elif MIN_VERSION_ghc(9,10,0) multiIf = withPlaceHolder (HsMultiIf []) . map mkLocated #elif MIN_VERSION_ghc(9,4,0) multiIf = withPlaceHolder (withEpAnnNotUsed HsMultiIf) . map mkLocated @@ -223,7 +237,7 @@ listComp lastExpr stmts = -- > var "e" @::@ var "t" (@::@) :: HsExpr' -> HsType' -> HsExpr' #if MIN_VERSION_ghc(9,10,0) -e @::@ t = ExprWithTySig [] (mkLocated e) (sigWcType t) +e @::@ t = ExprWithTySig noAnn (mkLocated e) (sigWcType t) #elif MIN_VERSION_ghc(8,8,0) e @::@ t = withEpAnnNotUsed ExprWithTySig (mkLocated e) (sigWcType t) #elif MIN_VERSION_ghc(8,6,0) @@ -263,14 +277,19 @@ tyApp e t = HsAppType e' t' -- > recordConE "A" [("x", var "y")] recordConE :: RdrNameStr -> [(RdrNameStr, HsExpr')] -> HsExpr' #if MIN_VERSION_ghc(9,10,0) -recordConE c fs = (withPlaceHolder $ RecordCon [] (valueRdrName c)) +recordConE c fs = (withPlaceHolder $ RecordCon noAnn (valueRdrName c)) #else recordConE c fs = (withPlaceHolder $ withEpAnnNotUsed RecordCon (valueRdrName c)) #endif #if !MIN_VERSION_ghc(8,6,0) noPostTcExpr #endif - $ HsRecFields (map recField fs) +#if MIN_VERSION_ghc(9,12,0) + $ noExt HsRecFields +#else + $ HsRecFields +#endif + (map recField fs) Nothing -- No ".." where recField :: (RdrNameStr, HsExpr') -> LHsRecField' LHsExpr' @@ -281,7 +300,7 @@ recordConE c fs = (withPlaceHolder $ withEpAnnNotUsed RecordCon (valueRdrName c) mkLocated $ withPlaceHolder $ noExt FieldOcc $ valueRdrName f , hfbRHS = mkLocated e , hfbPun = False - , hfbAnn = [] + , hfbAnn = mzero #elif MIN_VERSION_ghc(9,4,0) mkLocated HsFieldBind { hfbLHS = @@ -318,7 +337,7 @@ recordUpd :: HsExpr' -> [(RdrNameStr, HsExpr')] -> HsExpr' recordUpd e fs = #if MIN_VERSION_ghc(9,10,0) withPlaceHolder4 - $ RecordUpd [] (parenthesizeExprForApp $ mkLocated e) + $ RecordUpd noAnn (parenthesizeExprForApp $ mkLocated e) $ toRecordUpdFields $ map mkField fs #else withPlaceHolder4 @@ -331,10 +350,14 @@ recordUpd e fs = #if MIN_VERSION_ghc(9,10,0) mkLocated HsFieldBind { hfbLHS = +# if MIN_VERSION_ghc(9,12,0) + mkLocated $ withPlaceHolder $ noExt FieldOcc $ valueRdrName f +# else mkLocated $ withPlaceHolder $ noExt Ambiguous $ valueRdrName f +# endif , hfbRHS = mkLocated e' , hfbPun = False - , hfbAnn = [] + , hfbAnn = mzero #elif MIN_VERSION_ghc(9,4,0) mkLocated HsFieldBind { hfbLHS = @@ -366,7 +389,7 @@ recordUpd e fs = arithSeq :: ArithSeqInfo GhcPs -> HsExpr' arithSeq = #if MIN_VERSION_ghc(9,10,0) - ArithSeq [] Nothing + ArithSeq noAnn Nothing #elif MIN_VERSION_ghc(8,6,0) withEpAnnNotUsed ArithSeq Nothing #else diff --git a/src/GHC/SourceGen/Lit.hs b/src/GHC/SourceGen/Lit.hs index 94635ae..6ddb617 100644 --- a/src/GHC/SourceGen/Lit.hs +++ b/src/GHC/SourceGen/Lit.hs @@ -20,6 +20,7 @@ module GHC.SourceGen.Lit #if MIN_VERSION_ghc(9,2,0) import GHC.Types.SourceText (mkTHFractionalLit, mkIntegralLit) import GHC.Data.FastString (fsLit) +import GHC.Parser.Annotation (noAnn) #elif MIN_VERSION_ghc(9,0,0) import GHC.Types.Basic (mkFractionalLit, mkIntegralLit) import GHC.Data.FastString (fsLit) @@ -51,7 +52,7 @@ instance HasLit Pat' where lit = noExt LitPat #if MIN_VERSION_ghc(9,10,0) overLit l = withPlaceHolder - $ NPat [] (mkLocated l) Nothing noSyntaxExpr + $ NPat noAnn (mkLocated l) Nothing noSyntaxExpr #elif MIN_VERSION_ghc(9,4,0) overLit l = withPlaceHolder $ withEpAnnNotUsed NPat (mkLocated l) Nothing noSyntaxExpr diff --git a/src/GHC/SourceGen/Module.hs b/src/GHC/SourceGen/Module.hs index 513b5da..4a062ab 100644 --- a/src/GHC/SourceGen/Module.hs +++ b/src/GHC/SourceGen/Module.hs @@ -29,14 +29,13 @@ module GHC.SourceGen.Module import GHC.Hs.ImpExp ( IEWildcard(..), IEWrappedName(..), IE(..) #if MIN_VERSION_ghc(9,6,0) - , ImportListInterpretation (EverythingBut, Exactly), XImportDeclPass (ideclSourceText, ideclImplicit) -#else - , LIEWrappedName + , ImportListInterpretation (EverythingBut, Exactly) #endif ) import GHC.Hs ( HsModule(..) , ImportDecl(..) + , simpleImportDecl #if MIN_VERSION_ghc(8,10,0) , ImportDeclQualifiedStyle(..) #endif @@ -47,7 +46,9 @@ import GHC.Hs , LayoutInfo (NoLayoutInfo) #endif #if MIN_VERSION_ghc(9,6,0) - , hsmodDeprecMessage, hsmodHaddockModHeader, hsmodAnn, AnnKeywordId, XModulePs (XModulePs, hsmodLayout), noAnn, GhcPs, XImportDeclPass (XImportDeclPass, ideclAnn), SrcSpanAnnA, noExtField + , hsmodDeprecMessage, hsmodHaddockModHeader, hsmodAnn, XModulePs (XModulePs, hsmodLayout), noAnn, GhcPs, XImportDeclPass (XImportDeclPass, ideclAnn), SrcSpanAnnA, noExtField +#else + , LIEWrappedName #endif ) #if MIN_VERSION_ghc(9,0,0) && !MIN_VERSION_ghc(9,6,0) @@ -69,7 +70,6 @@ import GHC.Parser.Annotation (EpLayout (..), noAnn) import GHC.SourceGen.Syntax.Internal import GHC.SourceGen.Name.Internal -import GHC.SourceGen.Lit.Internal (noSourceText) import GHC.SourceGen.Name (unqual) #if MIN_VERSION_ghc(9,4,0) import GHC.SourceGen.Name (RdrNameStr, ModuleNameStr(unModuleNameStr), OccNameStr) @@ -123,44 +123,7 @@ as' :: ImportDecl' -> ModuleNameStr -> ImportDecl' as' d m = d { ideclAs = Just (mkLocated $ unModuleNameStr m) } import' :: ModuleNameStr -> ImportDecl' -import' m = importDecl - (mkLocated $ unModuleNameStr m) -#if MIN_VERSION_ghc(9,4,0) - NoRawPkgQual -#else - Nothing -#endif -#if MIN_VERSION_ghc(9,0,0) - NotBoot -#else - False -#endif - False -#if MIN_VERSION_ghc(8,10,0) - NotQualified -#else - False -#endif -#if !MIN_VERSION_ghc(9,6,0) - False -#endif - Nothing Nothing - where -#if MIN_VERSION_ghc(9,10,0) - importDecl = ImportDecl - (XImportDeclPass{ ideclAnn = noAnn - , ideclSourceText = NoSourceText - , ideclImplicit = False - }) -#elif MIN_VERSION_ghc(9,6,0) - importDecl = ImportDecl - (XImportDeclPass{ ideclAnn = EpAnnNotUsed - , ideclSourceText = NoSourceText - , ideclImplicit = False - }) -#else - importDecl = noSourceText (withEpAnnNotUsed ImportDecl) -#endif +import' m = simpleImportDecl (unModuleNameStr m) exposing :: ImportDecl' -> [IE'] -> ImportDecl' exposing d ies = d @@ -195,7 +158,7 @@ source d = d { ideclSource = -- > thingAll "A" thingAll :: RdrNameStr -> IE' #if MIN_VERSION_ghc(9,10,0) -thingAll n = IEThingAll (Nothing, []) (wrappedName n) Nothing +thingAll n = IEThingAll noAnn (wrappedName n) Nothing #else thingAll = withEpAnnNotUsed' IEThingAll . wrappedName #endif @@ -207,7 +170,7 @@ thingAll = withEpAnnNotUsed' IEThingAll . wrappedName -- > thingWith "A" ["b", "C"] thingWith :: RdrNameStr -> [OccNameStr] -> IE' #if MIN_VERSION_ghc(9,10,0) -thingWith n cs = IEThingWith (Nothing, []) (wrappedName n) NoIEWildcard (map (wrappedName . unqual) cs) Nothing +thingWith n cs = IEThingWith noAnn (wrappedName n) NoIEWildcard (map (wrappedName . unqual) cs) Nothing #else thingWith n cs = withEpAnnNotUsed' IEThingWith (wrappedName n) NoIEWildcard (map (wrappedName . unqual) cs) @@ -237,7 +200,7 @@ wrappedName = mkLocated . IEName . exportRdrName -- > moduleContents "M" moduleContents :: ModuleNameStr -> IE' #if MIN_VERSION_ghc(9,10,0) -moduleContents n = IEModuleContents (Nothing, []) (mkLocated (unModuleNameStr n)) +moduleContents n = IEModuleContents noAnn (mkLocated (unModuleNameStr n)) #else moduleContents = withEpAnnNotUsed' IEModuleContents . mkLocated . unModuleNameStr #endif diff --git a/src/GHC/SourceGen/Overloaded.hs b/src/GHC/SourceGen/Overloaded.hs index 5794c3e..c31780c 100644 --- a/src/GHC/SourceGen/Overloaded.hs +++ b/src/GHC/SourceGen/Overloaded.hs @@ -21,15 +21,16 @@ module GHC.SourceGen.Overloaded import GHC.Hs.Type ( HsType(..) , HsTyVarBndr(..) +#if MIN_VERSION_ghc(9,12,0) + , HsBndrVar(HsBndrVar) + , HsBndrKind(HsBndrNoKind) +#endif #if MIN_VERSION_ghc(9,8,0) , HsBndrVis (HsBndrRequired) + , mkHsOpTy #endif ) -import GHC.Hs (IE(..), IEWrappedName(..) -#if MIN_VERSION_ghc(9,6,0) - , noExtField -#endif - ) +import GHC.Hs (IE(..), IEWrappedName(..)) #if !MIN_VERSION_ghc(8,6,0) import PlaceHolder(PlaceHolder(..)) #endif @@ -45,7 +46,7 @@ import GHC.Hs #endif ) #if MIN_VERSION_ghc(9,10,0) -import GHC.Parser.Annotation (AnnList (..), AnnParen (AnnParen), ParenType (AnnParens), noAnn) +import GHC.Parser.Annotation (AnnList (..), noAnn) #endif #if MIN_VERSION_ghc(9,0,0) import GHC.Types.Basic (Boxity(..)) @@ -94,7 +95,7 @@ instance Par Pat' where instance Par HsType' where #if MIN_VERSION_ghc(9,10,0) - par = HsParTy (AnnParen AnnParens noSpanAnchor noSpanAnchor) . mkLocated + par = HsParTy noAnn . mkLocated #else par = withEpAnnNotUsed HsParTy . mkLocated #endif @@ -162,8 +163,11 @@ infixl 2 @@ instance App HsExpr' where #if MIN_VERSION_ghc(9,10,0) - op x o y - = OpApp [] +# if MIN_VERSION_ghc(9,12,0) + op x o y = noExt OpApp +# else + op x o y = OpApp [] +# endif (parenthesizeExprForOp $ mkLocated x) (mkLocated $ var o) (parenthesizeExprForOp $ mkLocated y) @@ -188,7 +192,7 @@ instance App HsExpr' where instance App HsType' where op x o y #if MIN_VERSION_ghc(9,10,0) - = HsOpTy [] notPromoted (parenthesizeTypeForOp $ mkLocated x) + = mkHsOpTy notPromoted (parenthesizeTypeForOp $ mkLocated x) (typeRdrName o) (parenthesizeTypeForOp $ mkLocated y) #elif MIN_VERSION_ghc(9,4,0) @@ -216,7 +220,7 @@ instance HasTuple HsExpr' where #if MIN_VERSION_ghc(9,10,0) tupleOf b ts = - ExplicitTuple [] (map (noExt Present . mkLocated) ts) b + ExplicitTuple noAnn (map (noExt Present . mkLocated) ts) b #else tupleOf b ts = explicitTuple @@ -236,7 +240,7 @@ unitDataConName = mkLocated $ nameRdrName $ dataConName $ unitDataCon instance HasTuple HsType' where #if MIN_VERSION_ghc(9,10,0) - tupleOf b = HsTupleTy (AnnParen AnnParens noSpanAnchor noSpanAnchor) b' . map mkLocated + tupleOf b = HsTupleTy noAnn b' . map mkLocated #else tupleOf b = withEpAnnNotUsed HsTupleTy b' . map mkLocated #endif @@ -251,7 +255,7 @@ instance HasTuple HsType' where instance HasTuple Pat' where tupleOf b ps = #if MIN_VERSION_ghc(9,10,0) - TuplePat [] (map builtPat ps) b + TuplePat noAnn (map builtPat ps) b #elif MIN_VERSION_ghc(8,6,0) withEpAnnNotUsed TuplePat (map builtPat ps) b #else @@ -331,7 +335,7 @@ instance BVar HsExpr' where instance Var HsType' where #if MIN_VERSION_ghc(9,10,0) - var = HsTyVar [] notPromoted . typeRdrName + var = HsTyVar noAnn notPromoted . typeRdrName #else var = withEpAnnNotUsed HsTyVar notPromoted . typeRdrName #endif @@ -339,11 +343,16 @@ instance Var HsType' where instance BVar HsType' where bvar = var . UnqualStr -#if MIN_VERSION_ghc(9,10,0) +#if MIN_VERSION_ghc(9,12,0) +instance BVar HsTyVarBndr' where + bvar n = HsTvb noAnn (noExt HsBndrRequired) (noExt HsBndrVar $ typeRdrName $ UnqualStr n) (noExt HsBndrNoKind) +instance BVar HsTyVarBndrS' where + bvar n = HsTvb noAnn SpecifiedSpec (noExt HsBndrVar $ typeRdrName $ UnqualStr n) (noExt HsBndrNoKind) +#elif MIN_VERSION_ghc(9,10,0) instance BVar HsTyVarBndr' where - bvar = UserTyVar [] (noExt HsBndrRequired) . typeRdrName . UnqualStr + bvar = UserTyVar noAnn (noExt HsBndrRequired) . typeRdrName . UnqualStr instance BVar HsTyVarBndrS' where - bvar = UserTyVar [] SpecifiedSpec . typeRdrName . UnqualStr + bvar = UserTyVar noAnn SpecifiedSpec . typeRdrName . UnqualStr #elif MIN_VERSION_ghc(9,8,0) instance BVar HsTyVarBndr' where bvar = withEpAnnNotUsed UserTyVar HsBndrRequired . typeRdrName . UnqualStr diff --git a/src/GHC/SourceGen/Pat.hs b/src/GHC/SourceGen/Pat.hs index 166a910..f432080 100644 --- a/src/GHC/SourceGen/Pat.hs +++ b/src/GHC/SourceGen/Pat.hs @@ -64,16 +64,16 @@ v `asP` p = -- > ===== -- > conP "A" [bvar "b", bvar "c"] conP :: RdrNameStr -> [Pat'] -> Pat' -conP c = conPat (valueRdrName c) . prefixCon . map (builtPat . parenthesize) +conP c pats = conPat (valueRdrName c) (prefixCon (map (builtPat . parenthesize) pats)) where #if MIN_VERSION_ghc(9,10,0) - conPat = ConPat [] + conPat = ConPat noAnn #elif MIN_VERSION_ghc(9,0,0) conPat = withEpAnnNotUsed ConPat #else conPat = ConPatIn #endif -#if MIN_VERSION_ghc(9,2,0) +#if !MIN_VERSION_ghc(9,13,0) && MIN_VERSION_ghc(9,2,0) prefixCon = PrefixCon [] #else prefixCon = PrefixCon @@ -90,14 +90,18 @@ conP_ c = conP c [] recordConP :: RdrNameStr -> [(RdrNameStr, Pat')] -> Pat' recordConP c fs = #if MIN_VERSION_ghc(9,10,0) - ConPat [] + ConPat noAnn #elif MIN_VERSION_ghc(9,0,0) withEpAnnNotUsed ConPat #else ConPatIn #endif (valueRdrName c) +#if MIN_VERSION_ghc(9,12,0) + $ RecCon $ noExt HsRecFields (map mkRecField fs) Nothing -- No ".." +#else $ RecCon $ HsRecFields (map mkRecField fs) Nothing -- No ".." +#endif where mkRecField :: (RdrNameStr, Pat') -> LHsRecField' LPat' mkRecField (f, p) = @@ -132,7 +136,7 @@ recordConP c fs = -- > strictP (bvar x) strictP :: Pat' -> Pat' #if MIN_VERSION_ghc(9,10,0) -strictP = BangPat [] . builtPat . parenthesize +strictP = BangPat noAnn . builtPat . parenthesize #else strictP = withEpAnnNotUsed BangPat . builtPat . parenthesize #endif @@ -144,7 +148,7 @@ strictP = withEpAnnNotUsed BangPat . builtPat . parenthesize -- > lazyP (conP "A" [bvar x]) lazyP :: Pat' -> Pat' #if MIN_VERSION_ghc(9,10,0) -lazyP = LazyPat [] . builtPat . parenthesize +lazyP = LazyPat noAnn . builtPat . parenthesize #else lazyP = withEpAnnNotUsed LazyPat . builtPat . parenthesize #endif @@ -156,7 +160,7 @@ lazyP = withEpAnnNotUsed LazyPat . builtPat . parenthesize -- > sigPat (bvar "x") (var "y") sigP :: Pat' -> HsType' -> Pat' #if MIN_VERSION_ghc(9,10,0) -sigP p t = SigPat [] (builtPat p) (patSigType t) +sigP p t = SigPat noAnn (builtPat p) (patSigType t) #elif MIN_VERSION_ghc(8,8,0) sigP p t = withEpAnnNotUsed SigPat (builtPat p) (patSigType t) #elif MIN_VERSION_ghc(8,6,0) diff --git a/src/GHC/SourceGen/Pat/Internal.hs b/src/GHC/SourceGen/Pat/Internal.hs index ce62a1c..37a18e8 100644 --- a/src/GHC/SourceGen/Pat/Internal.hs +++ b/src/GHC/SourceGen/Pat/Internal.hs @@ -32,7 +32,9 @@ needsPar (NPat _ l _ _) = overLitNeedsParen $ unLoc l needsPar (LitPat l) = litNeedsParen l needsPar (NPat l _ _ _) = overLitNeedsParen $ unLoc l #endif -#if MIN_VERSION_ghc(9,2,0) +#if MIN_VERSION_ghc(9,14,0) +needsPar (ConPat _ _ (PrefixCon xs)) = not $ null xs +#elif MIN_VERSION_ghc(9,2,0) needsPar (ConPat _ _ (PrefixCon _ xs)) = not $ null xs #elif MIN_VERSION_ghc(9,0,0) needsPar (ConPat _ _ (PrefixCon xs)) = not $ null xs diff --git a/src/GHC/SourceGen/Type.hs b/src/GHC/SourceGen/Type.hs index 40d854e..fd66b5b 100644 --- a/src/GHC/SourceGen/Type.hs +++ b/src/GHC/SourceGen/Type.hs @@ -32,6 +32,9 @@ import GHC.Hs.Type #if MIN_VERSION_ghc(9,4,0) import Language.Haskell.Syntax.Extension #endif +#if MIN_VERSION_ghc(9,12,0) +import Language.Haskell.Syntax.Type +#endif import GHC.SourceGen.Syntax.Internal import GHC.SourceGen.Lit.Internal (noSourceText) @@ -41,7 +44,7 @@ import GHC.SourceGen.Type.Internal -- | A promoted name, for example from the @DataKinds@ extension. tyPromotedVar :: RdrNameStr -> HsType' #if MIN_VERSION_ghc(9,10,0) -tyPromotedVar = HsTyVar [] promoted . typeRdrName +tyPromotedVar = HsTyVar noAnn promoted . typeRdrName #else tyPromotedVar = withEpAnnNotUsed HsTyVar promoted . typeRdrName #endif @@ -54,7 +57,7 @@ numTy = noExt HsTyLit . noSourceText HsNumTy listTy :: HsType' -> HsType' #if MIN_VERSION_ghc(9,10,0) -listTy = HsListTy (AnnParen AnnParens noSpanAnchor noSpanAnchor) . mkLocated +listTy = HsListTy noAnn . mkLocated #else listTy = withEpAnnNotUsed HsListTy . mkLocated #endif @@ -63,13 +66,15 @@ listPromotedTy :: [HsType'] -> HsType' -- Lists of two or more elements don't need the explicit tick (`'`). -- But for consistency, just always add it. #if MIN_VERSION_ghc(9,10,0) -listPromotedTy = withPlaceHolder (HsExplicitListTy [] promoted) . map mkLocated +listPromotedTy = withPlaceHolder (HsExplicitListTy noAnn promoted) . map mkLocated #else listPromotedTy = withPlaceHolder (withEpAnnNotUsed HsExplicitListTy promoted) . map mkLocated #endif tuplePromotedTy :: [HsType'] -> HsType' -#if MIN_VERSION_ghc(9,10,0) +#if MIN_VERSION_ghc(9,12,0) +tuplePromotedTy = withPlaceHolders (HsExplicitTupleTy noAnn IsPromoted) . map mkLocated +#elif MIN_VERSION_ghc(9,10,0) tuplePromotedTy = withPlaceHolders (withEpAnnNotUsed (HsExplicitTupleTy [])) . map mkLocated #else tuplePromotedTy = withPlaceHolders (withEpAnnNotUsed HsExplicitTupleTy) . map mkLocated @@ -84,17 +89,18 @@ tuplePromotedTy = withPlaceHolders (withEpAnnNotUsed HsExplicitTupleTy) . map mk a --> b = #if MIN_VERSION_ghc(9,10,0) (noExt HsFunTy) + --(HsUnannotated (EpArrow (EpUniTok noSpanAnchor NormalSyntax))) (HsUnrestrictedArrow (EpUniTok noSpanAnchor NormalSyntax)) - (parenthesizeTypeForFun $ mkLocated a) (mkLocated b) #elif MIN_VERSION_ghc(9,4,0) withEpAnnNotUsed HsFunTy (HsUnrestrictedArrow mkUniToken) - (parenthesizeTypeForFun $ mkLocated a) (mkLocated b) #elif MIN_VERSION_ghc(9,0,0) withEpAnnNotUsed HsFunTy (HsUnrestrictedArrow NormalSyntax) - (parenthesizeTypeForFun $ mkLocated a) (mkLocated b) +#else + withEpAnnNotUsed HsFunTy #endif + (parenthesizeTypeForFun $ mkLocated a) (mkLocated b) infixr 0 --> @@ -156,7 +162,9 @@ infixr 0 ==> -- > kindedVar "x" (var "A") kindedVar :: OccNameStr -> HsType' -> HsTyVarBndr' kindedVar v t = -#if MIN_VERSION_ghc(9,10,0) +#if MIN_VERSION_ghc(9,12,0) + HsTvb noAnn (noExt HsBndrRequired) (noExt HsBndrVar $ typeRdrName $ UnqualStr v) (noExt HsBndrKind $ mkLocated t) +#elif MIN_VERSION_ghc(9,10,0) KindedTyVar [] (noExt HsBndrRequired) @@ -169,4 +177,7 @@ kindedVar v t = withEpAnnNotUsed KindedTyVar () (typeRdrName $ UnqualStr v) (mkLocated t) +#else + withEpAnnNotUsed KindedTyVar + (typeRdrName $ UnqualStr v) (mkLocated t) #endif diff --git a/src/GHC/SourceGen/Type/Internal.hs b/src/GHC/SourceGen/Type/Internal.hs index 9c9a95f..3f53537 100644 --- a/src/GHC/SourceGen/Type/Internal.hs +++ b/src/GHC/SourceGen/Type/Internal.hs @@ -18,7 +18,7 @@ import SrcLoc (unLoc) #endif #if MIN_VERSION_ghc(9,10,0) -import GHC.Parser.Annotation (AnnParen (AnnParen), ParenType (AnnParens), noAnn, noSpanAnchor) +import GHC.Parser.Annotation (AnnParen, noAnn, noSpanAnchor) #endif import GHC.SourceGen.Syntax.Internal @@ -68,7 +68,7 @@ needsParenForApp t = case t of parTy :: LHsType GhcPs -> LHsType GhcPs #if MIN_VERSION_ghc(9,10,0) -parTy = mkLocated . HsParTy (AnnParen AnnParens noSpanAnchor noSpanAnchor) +parTy = mkLocated . HsParTy noAnn #else parTy = mkLocated . withEpAnnNotUsed HsParTy #endif diff --git a/stack-9.10.yaml b/stack-9.10.yaml index 201009a..babf42e 100644 --- a/stack-9.10.yaml +++ b/stack-9.10.yaml @@ -4,8 +4,8 @@ # license that can be found in the LICENSE file or at # https://developers.google.com/open-source/licenses/bsd -resolver: nightly-2024-10-27 -compiler: ghc-9.10.1 +resolver: lts-24.6 +compiler: ghc-9.10.2 packages: - . @@ -13,14 +13,3 @@ packages: ghc-options: "$locals": -Wall -Werror -Wwarn=unused-imports -Wwarn=dodgy-imports - -allow-newer: true - -extra-deps: -- Cabal-3.12.0.0 -- Cabal-syntax-3.12.0.0 -- directory-1.3.8.3 -- filepath-1.5.2.0 -- os-string-2.0.2 -- process-1.6.19.0 -- unix-2.8.5.1 diff --git a/stack-9.12.yaml b/stack-9.12.yaml new file mode 100644 index 0000000..a3a9ba5 --- /dev/null +++ b/stack-9.12.yaml @@ -0,0 +1,15 @@ +# Copyright 2019 Google LLC +# +# Use of this source code is governed by a BSD-style +# license that can be found in the LICENSE file or at +# https://developers.google.com/open-source/licenses/bsd + +resolver: nightly-2025-08-23 +compiler: ghc-9.12.2 + +packages: +- . +- ghc-show-ast + +ghc-options: + "$locals": -Wall -Werror -Wwarn=unused-imports -Wwarn=dodgy-imports