diff options
author | Alan Zimmerman <alan.zimm@gmail.com> | 2021-03-25 21:24:27 +0000 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2021-03-31 11:13:28 -0400 |
commit | 0fe5175ac537c0ce2afe969ec82a0d1c73a4ae38 (patch) | |
tree | da9e816a7d18be58e795b3c9dd07b87106ab82fc /compiler | |
parent | 2fcebb72d97edd1e630002bef89bc6982529e36f (diff) | |
download | haskell-0fe5175ac537c0ce2afe969ec82a0d1c73a4ae38.tar.gz |
EPA : Rename ApiAnn to EPAnn
Follow-up from !2418, see #19579
Updates haddock submodule
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/GHC/Driver/Main.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Hs.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Hs/Binds.hs | 30 | ||||
-rw-r--r-- | compiler/GHC/Hs/Decls.hs | 62 | ||||
-rw-r--r-- | compiler/GHC/Hs/Dump.hs | 82 | ||||
-rw-r--r-- | compiler/GHC/Hs/Expr.hs | 114 | ||||
-rw-r--r-- | compiler/GHC/Hs/Extension.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Hs/ImpExp.hs | 12 | ||||
-rw-r--r-- | compiler/GHC/Hs/Pat.hs | 32 | ||||
-rw-r--r-- | compiler/GHC/Hs/Type.hs | 60 | ||||
-rw-r--r-- | compiler/GHC/Hs/Utils.hs | 40 | ||||
-rw-r--r-- | compiler/GHC/Parser.y | 324 | ||||
-rw-r--r-- | compiler/GHC/Parser/Annotation.hs | 252 | ||||
-rw-r--r-- | compiler/GHC/Parser/Lexer.x | 20 | ||||
-rw-r--r-- | compiler/GHC/Parser/PostProcess.hs | 190 | ||||
-rw-r--r-- | compiler/GHC/Parser/Types.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Module.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/ThToHs.hs | 2 |
18 files changed, 618 insertions, 618 deletions
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs index 9329e96d19..aca035e026 100644 --- a/compiler/GHC/Driver/Main.hs +++ b/compiler/GHC/Driver/Main.hs @@ -428,7 +428,7 @@ hscParse' mod_summary FormatHaskell (ppr rdr_module) liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed_ast "Parser AST" FormatHaskell (showAstData NoBlankSrcSpan - NoBlankApiAnnotations + NoBlankEpAnnotations rdr_module) liftIO $ dumpIfSet_dyn logger dflags Opt_D_source_stats "Source Statistics" FormatText (ppSourceStats False rdr_module) @@ -481,7 +481,7 @@ extract_renamed_stuff mod_summary tc_result = do dflags <- getDynFlags logger <- getLogger liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_rn_ast "Renamer" - FormatHaskell (showAstData NoBlankSrcSpan NoBlankApiAnnotations rn_info) + FormatHaskell (showAstData NoBlankSrcSpan NoBlankEpAnnotations rn_info) -- Create HIE files when (gopt Opt_WriteHie dflags) $ do @@ -2078,7 +2078,7 @@ hscParseThingWithLocation source linenumber parser str = do liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed "Parser" FormatHaskell (ppr thing) liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed_ast "Parser AST" - FormatHaskell (showAstData NoBlankSrcSpan NoBlankApiAnnotations thing) + FormatHaskell (showAstData NoBlankSrcSpan NoBlankEpAnnotations thing) return thing diff --git a/compiler/GHC/Hs.hs b/compiler/GHC/Hs.hs index 171238a85a..8b645ac5fc 100644 --- a/compiler/GHC/Hs.hs +++ b/compiler/GHC/Hs.hs @@ -69,7 +69,7 @@ import Data.Data hiding ( Fixity ) -- All we actually declare here is the top-level structure for a module. data HsModule = HsModule { - hsmodAnn :: ApiAnn' AnnsModule, + hsmodAnn :: EpAnn' AnnsModule, hsmodLayout :: LayoutInfo, -- ^ Layout info for the module. -- For incomplete modules (e.g. the output of parseHeader), it is NoLayoutInfo. diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs index e40d1acc93..c89406a63e 100644 --- a/compiler/GHC/Hs/Binds.hs +++ b/compiler/GHC/Hs/Binds.hs @@ -69,8 +69,8 @@ Global bindings (where clauses) -- the ...LR datatypes are parametrized by two id types, -- one for the left and one for the right. -type instance XHsValBinds (GhcPass pL) (GhcPass pR) = ApiAnn' AnnList -type instance XHsIPBinds (GhcPass pL) (GhcPass pR) = ApiAnn' AnnList +type instance XHsValBinds (GhcPass pL) (GhcPass pR) = EpAnn' AnnList +type instance XHsIPBinds (GhcPass pL) (GhcPass pR) = EpAnn' AnnList type instance XEmptyLocalBinds (GhcPass pL) (GhcPass pR) = NoExtField type instance XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) = NoExtCon @@ -93,7 +93,7 @@ type instance XFunBind (GhcPass pL) GhcPs = NoExtField type instance XFunBind (GhcPass pL) GhcRn = NameSet -- Free variables type instance XFunBind (GhcPass pL) GhcTc = HsWrapper -- See comments on FunBind.fun_ext -type instance XPatBind GhcPs (GhcPass pR) = ApiAnn +type instance XPatBind GhcPs (GhcPass pR) = EpAnn type instance XPatBind GhcRn (GhcPass pR) = NameSet -- Free variables type instance XPatBind GhcTc (GhcPass pR) = Type -- Type of the GRHSs @@ -105,7 +105,7 @@ type instance XXHsBindsLR (GhcPass pL) (GhcPass pR) = NoExtCon type instance XABE (GhcPass p) = NoExtField type instance XXABExport (GhcPass p) = NoExtCon -type instance XPSB (GhcPass idL) GhcPs = ApiAnn +type instance XPSB (GhcPass idL) GhcPs = EpAnn type instance XPSB (GhcPass idL) GhcRn = NameSet type instance XPSB (GhcPass idL) GhcTc = NameSet @@ -552,7 +552,7 @@ isEmptyIPBindsPR (IPBinds _ is) = null is isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool isEmptyIPBindsTc (IPBinds ds is) = null is && isEmptyTcEvBinds ds -type instance XCIPBind (GhcPass p) = ApiAnn +type instance XCIPBind (GhcPass p) = EpAnn type instance XXIPBind (GhcPass p) = NoExtCon instance OutputableBndrId p @@ -574,17 +574,17 @@ instance OutputableBndrId p => Outputable (IPBind (GhcPass p)) where ************************************************************************ -} -type instance XTypeSig (GhcPass p) = ApiAnn' AnnSig -type instance XPatSynSig (GhcPass p) = ApiAnn' AnnSig -type instance XClassOpSig (GhcPass p) = ApiAnn' AnnSig +type instance XTypeSig (GhcPass p) = EpAnn' AnnSig +type instance XPatSynSig (GhcPass p) = EpAnn' AnnSig +type instance XClassOpSig (GhcPass p) = EpAnn' AnnSig type instance XIdSig (GhcPass p) = NoExtField -- No anns, generated -type instance XFixSig (GhcPass p) = ApiAnn -type instance XInlineSig (GhcPass p) = ApiAnn -type instance XSpecSig (GhcPass p) = ApiAnn -type instance XSpecInstSig (GhcPass p) = ApiAnn -type instance XMinimalSig (GhcPass p) = ApiAnn -type instance XSCCFunSig (GhcPass p) = ApiAnn -type instance XCompleteMatchSig (GhcPass p) = ApiAnn +type instance XFixSig (GhcPass p) = EpAnn +type instance XInlineSig (GhcPass p) = EpAnn +type instance XSpecSig (GhcPass p) = EpAnn +type instance XSpecInstSig (GhcPass p) = EpAnn +type instance XMinimalSig (GhcPass p) = EpAnn +type instance XSCCFunSig (GhcPass p) = EpAnn +type instance XCompleteMatchSig (GhcPass p) = EpAnn type instance XXSig (GhcPass p) = NoExtCon diff --git a/compiler/GHC/Hs/Decls.hs b/compiler/GHC/Hs/Decls.hs index bc0aaff318..b3eac48499 100644 --- a/compiler/GHC/Hs/Decls.hs +++ b/compiler/GHC/Hs/Decls.hs @@ -325,22 +325,22 @@ instance OutputableBndrId p type instance XFamDecl (GhcPass _) = NoExtField -type instance XSynDecl GhcPs = ApiAnn +type instance XSynDecl GhcPs = EpAnn type instance XSynDecl GhcRn = NameSet -- FVs type instance XSynDecl GhcTc = NameSet -- FVs -type instance XDataDecl GhcPs = ApiAnn -- AZ: used? +type instance XDataDecl GhcPs = EpAnn -- AZ: used? type instance XDataDecl GhcRn = DataDeclRn type instance XDataDecl GhcTc = DataDeclRn -type instance XClassDecl GhcPs = (ApiAnn, AnnSortKey, LayoutInfo) -- See Note [Class LayoutInfo] +type instance XClassDecl GhcPs = (EpAnn, AnnSortKey, LayoutInfo) -- See Note [Class LayoutInfo] -- TODO:AZ:tidy up AnnSortKey above type instance XClassDecl GhcRn = NameSet -- FVs type instance XClassDecl GhcTc = NameSet -- FVs type instance XXTyClDecl (GhcPass _) = NoExtCon -type instance XCTyFamInstDecl (GhcPass _) = ApiAnn +type instance XCTyFamInstDecl (GhcPass _) = EpAnn type instance XXTyFamInstDecl (GhcPass _) = NoExtCon -- Dealing with names @@ -463,7 +463,7 @@ pprTyClDeclFlavour (DataDecl { tcdDataDefn = HsDataDefn { dd_ND = nd } }) instance OutputableBndrId p => Outputable (FunDep (GhcPass p)) where ppr = pprFunDep -type instance XCFunDep (GhcPass _) = ApiAnn +type instance XCFunDep (GhcPass _) = EpAnn type instance XXFunDep (GhcPass _) = NoExtCon pprFundeps :: OutputableBndrId p => [FunDep (GhcPass p)] -> SDoc @@ -497,7 +497,7 @@ type instance XCKindSig (GhcPass _) = NoExtField type instance XTyVarSig (GhcPass _) = NoExtField type instance XXFamilyResultSig (GhcPass _) = NoExtCon -type instance XCFamilyDecl (GhcPass _) = ApiAnn +type instance XCFamilyDecl (GhcPass _) = EpAnn type instance XXFamilyDecl (GhcPass _) = NoExtCon @@ -524,7 +524,7 @@ resultVariableName _ = Nothing ------------- Pretty printing FamilyDecls ----------- -type instance XCInjectivityAnn (GhcPass _) = ApiAnn +type instance XCInjectivityAnn (GhcPass _) = EpAnn type instance XXInjectivityAnn (GhcPass _) = NoExtCon instance OutputableBndrId p @@ -568,10 +568,10 @@ instance OutputableBndrId p * * ********************************************************************* -} -type instance XCHsDataDefn (GhcPass _) = ApiAnn +type instance XCHsDataDefn (GhcPass _) = EpAnn type instance XXHsDataDefn (GhcPass _) = NoExtCon -type instance XCHsDerivingClause (GhcPass _) = ApiAnn +type instance XCHsDerivingClause (GhcPass _) = EpAnn type instance XXHsDerivingClause (GhcPass _) = NoExtCon instance OutputableBndrId p @@ -598,7 +598,7 @@ instance OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) where ppr (DctSingle _ ty) = ppr ty ppr (DctMulti _ tys) = parens (interpp'SP tys) -type instance XStandaloneKindSig GhcPs = ApiAnn +type instance XStandaloneKindSig GhcPs = EpAnn type instance XStandaloneKindSig GhcRn = NoExtField type instance XStandaloneKindSig GhcTc = NoExtField @@ -607,8 +607,8 @@ type instance XXStandaloneKindSig (GhcPass p) = NoExtCon standaloneKindSigName :: StandaloneKindSig (GhcPass p) -> IdP (GhcPass p) standaloneKindSigName (StandaloneKindSig _ lname _) = unLoc lname -type instance XConDeclGADT (GhcPass _) = ApiAnn -type instance XConDeclH98 (GhcPass _) = ApiAnn +type instance XConDeclGADT (GhcPass _) = EpAnn +type instance XConDeclH98 (GhcPass _) = EpAnn type instance XXConDecl (GhcPass _) = NoExtCon @@ -724,14 +724,14 @@ ppr_con_names = pprWithCommas (pprPrefixOcc . unLoc) ************************************************************************ -} -type instance XCFamEqn (GhcPass _) r = ApiAnn +type instance XCFamEqn (GhcPass _) r = EpAnn type instance XXFamEqn (GhcPass _) r = NoExtCon type instance Anno (FamEqn (GhcPass p) _) = SrcSpanAnnA ----------------- Class instances ------------- -type instance XCClsInstDecl GhcPs = (ApiAnn, AnnSortKey) -- TODO:AZ:tidy up +type instance XCClsInstDecl GhcPs = (EpAnn, AnnSortKey) -- TODO:AZ:tidy up type instance XCClsInstDecl GhcRn = NoExtField type instance XCClsInstDecl GhcTc = NoExtField @@ -741,7 +741,7 @@ type instance XXClsInstDecl (GhcPass _) = NoExtCon type instance XClsInstD (GhcPass _) = NoExtField -type instance XDataFamInstD GhcPs = ApiAnn +type instance XDataFamInstD GhcPs = EpAnn type instance XDataFamInstD GhcRn = NoExtField type instance XDataFamInstD GhcTc = NoExtField @@ -887,7 +887,7 @@ instDeclDataFamInsts inst_decls ************************************************************************ -} -type instance XCDerivDecl (GhcPass _) = ApiAnn +type instance XCDerivDecl (GhcPass _) = EpAnn type instance XXDerivDecl (GhcPass _) = NoExtCon type instance Anno OverlapMode = SrcSpanAnnP @@ -911,15 +911,15 @@ instance OutputableBndrId p ************************************************************************ -} -type instance XStockStrategy GhcPs = ApiAnn +type instance XStockStrategy GhcPs = EpAnn type instance XStockStrategy GhcRn = NoExtField type instance XStockStrategy GhcTc = NoExtField -type instance XAnyClassStrategy GhcPs = ApiAnn +type instance XAnyClassStrategy GhcPs = EpAnn type instance XAnyClassStrategy GhcRn = NoExtField type instance XAnyClassStrategy GhcTc = NoExtField -type instance XNewtypeStrategy GhcPs = ApiAnn +type instance XNewtypeStrategy GhcPs = EpAnn type instance XNewtypeStrategy GhcRn = NoExtField type instance XNewtypeStrategy GhcTc = NoExtField @@ -927,7 +927,7 @@ type instance XViaStrategy GhcPs = XViaStrategyPs type instance XViaStrategy GhcRn = LHsSigType GhcRn type instance XViaStrategy GhcTc = Type -data XViaStrategyPs = XViaStrategyPs ApiAnn (LHsSigType GhcPs) +data XViaStrategyPs = XViaStrategyPs EpAnn (LHsSigType GhcPs) instance OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) where @@ -966,7 +966,7 @@ mapDerivStrategy f ds = foldDerivStrategy ds (ViaStrategy . f) ds ************************************************************************ -} -type instance XCDefaultDecl GhcPs = ApiAnn +type instance XCDefaultDecl GhcPs = EpAnn type instance XCDefaultDecl GhcRn = NoExtField type instance XCDefaultDecl GhcTc = NoExtField @@ -985,11 +985,11 @@ instance OutputableBndrId p ************************************************************************ -} -type instance XForeignImport GhcPs = ApiAnn +type instance XForeignImport GhcPs = EpAnn type instance XForeignImport GhcRn = NoExtField type instance XForeignImport GhcTc = Coercion -type instance XForeignExport GhcPs = ApiAnn +type instance XForeignExport GhcPs = EpAnn type instance XForeignExport GhcRn = NoExtField type instance XForeignExport GhcTc = Coercion @@ -1012,13 +1012,13 @@ instance OutputableBndrId p ************************************************************************ -} -type instance XCRuleDecls GhcPs = ApiAnn +type instance XCRuleDecls GhcPs = EpAnn type instance XCRuleDecls GhcRn = NoExtField type instance XCRuleDecls GhcTc = NoExtField type instance XXRuleDecls (GhcPass _) = NoExtCon -type instance XHsRule GhcPs = ApiAnn' HsRuleAnn +type instance XHsRule GhcPs = EpAnn' HsRuleAnn type instance XHsRule GhcRn = HsRuleRn type instance XHsRule GhcTc = HsRuleRn @@ -1040,8 +1040,8 @@ data HsRuleAnn flattenRuleDecls :: [LRuleDecls (GhcPass p)] -> [LRuleDecl (GhcPass p)] flattenRuleDecls decls = concatMap (rds_rules . unLoc) decls -type instance XCRuleBndr (GhcPass _) = ApiAnn -type instance XRuleBndrSig (GhcPass _) = ApiAnn +type instance XCRuleBndr (GhcPass _) = EpAnn +type instance XRuleBndrSig (GhcPass _) = EpAnn type instance XXRuleBndr (GhcPass _) = NoExtCon instance (OutputableBndrId p) => Outputable (RuleDecls (GhcPass p)) where @@ -1079,13 +1079,13 @@ instance (OutputableBndrId p) => Outputable (RuleBndr (GhcPass p)) where ************************************************************************ -} -type instance XWarnings GhcPs = ApiAnn +type instance XWarnings GhcPs = EpAnn type instance XWarnings GhcRn = NoExtField type instance XWarnings GhcTc = NoExtField type instance XXWarnDecls (GhcPass _) = NoExtCon -type instance XWarning (GhcPass _) = ApiAnn +type instance XWarning (GhcPass _) = EpAnn type instance XXWarnDecl (GhcPass _) = NoExtCon @@ -1109,7 +1109,7 @@ instance OutputableBndrId p ************************************************************************ -} -type instance XHsAnnotation (GhcPass _) = ApiAnn' AnnPragma +type instance XHsAnnotation (GhcPass _) = EpAnn' AnnPragma type instance XXAnnDecl (GhcPass _) = NoExtCon instance (OutputableBndrId p) => Outputable (AnnDecl (GhcPass p)) where @@ -1131,7 +1131,7 @@ pprAnnProvenance (TypeAnnProvenance (L _ name)) ************************************************************************ -} -type instance XCRoleAnnotDecl GhcPs = ApiAnn +type instance XCRoleAnnotDecl GhcPs = EpAnn type instance XCRoleAnnotDecl GhcRn = NoExtField type instance XCRoleAnnotDecl GhcTc = NoExtField diff --git a/compiler/GHC/Hs/Dump.hs b/compiler/GHC/Hs/Dump.hs index 68ce567e46..1e282a1ee3 100644 --- a/compiler/GHC/Hs/Dump.hs +++ b/compiler/GHC/Hs/Dump.hs @@ -13,7 +13,7 @@ module GHC.Hs.Dump ( -- * Dumping ASTs showAstData, BlankSrcSpan(..), - BlankApiAnnotations(..), + BlankEpAnnotations(..), ) where import GHC.Prelude @@ -38,13 +38,13 @@ import qualified Data.ByteString as B data BlankSrcSpan = BlankSrcSpan | BlankSrcSpanFile | NoBlankSrcSpan deriving (Eq,Show) -data BlankApiAnnotations = BlankApiAnnotations | NoBlankApiAnnotations +data BlankEpAnnotations = BlankEpAnnotations | NoBlankEpAnnotations deriving (Eq,Show) -- | Show a GHC syntax tree. This parameterised because it is also used for -- comparing ASTs in ppr roundtripping tests, where the SrcSpan's are blanked -- out, to avoid comparing locations, only structure -showAstData :: Data a => BlankSrcSpan -> BlankApiAnnotations -> a -> SDoc +showAstData :: Data a => BlankSrcSpan -> BlankEpAnnotations -> a -> SDoc showAstData bs ba a0 = blankLine $$ showAstData' a0 where showAstData' :: Data a => a -> SDoc @@ -56,13 +56,13 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 `extQ` annotationModule `extQ` annotationAddEpAnn `extQ` annotationGrhsAnn - `extQ` annotationApiAnnHsCase - `extQ` annotationApiAnnHsLet + `extQ` annotationEpAnnHsCase + `extQ` annotationEpAnnHsLet `extQ` annotationAnnList - `extQ` annotationApiAnnImportDecl + `extQ` annotationEpAnnImportDecl `extQ` annotationAnnParen `extQ` annotationTrailingAnn - `extQ` addApiAnn + `extQ` addEpAnn `extQ` lit `extQ` litr `extQ` litt `extQ` sourceText `extQ` deltaPos @@ -178,11 +178,11 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 (text "")) - addApiAnn :: AddEpAnn -> SDoc - addApiAnn (AddEpAnn a s) = case ba of - BlankApiAnnotations -> parens + addEpAnn :: AddEpAnn -> SDoc + addEpAnn (AddEpAnn a s) = case ba of + BlankEpAnnotations -> parens $ text "blanked:" <+> text "AddEpAnn" - NoBlankApiAnnotations -> + NoBlankEpAnnotations -> parens $ text "AddEpAnn" <+> ppr a <+> annAnchor s var :: Var -> SDoc @@ -223,58 +223,58 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 -- ------------------------- - annotation :: ApiAnn -> SDoc - annotation = annotation' (text "ApiAnn") + annotation :: EpAnn -> SDoc + annotation = annotation' (text "EpAnn") - annotationModule :: ApiAnn' AnnsModule -> SDoc - annotationModule = annotation' (text "ApiAnn' AnnsModule") + annotationModule :: EpAnn' AnnsModule -> SDoc + annotationModule = annotation' (text "EpAnn' AnnsModule") - annotationAddEpAnn :: ApiAnn' AddEpAnn -> SDoc - annotationAddEpAnn = annotation' (text "ApiAnn' AddEpAnn") + annotationAddEpAnn :: EpAnn' AddEpAnn -> SDoc + annotationAddEpAnn = annotation' (text "EpAnn' AddEpAnn") - annotationGrhsAnn :: ApiAnn' GrhsAnn -> SDoc - annotationGrhsAnn = annotation' (text "ApiAnn' GrhsAnn") + annotationGrhsAnn :: EpAnn' GrhsAnn -> SDoc + annotationGrhsAnn = annotation' (text "EpAnn' GrhsAnn") - annotationApiAnnHsCase :: ApiAnn' ApiAnnHsCase -> SDoc - annotationApiAnnHsCase = annotation' (text "ApiAnn' ApiAnnHsCase") + annotationEpAnnHsCase :: EpAnn' EpAnnHsCase -> SDoc + annotationEpAnnHsCase = annotation' (text "EpAnn' EpAnnHsCase") - annotationApiAnnHsLet :: ApiAnn' AnnsLet -> SDoc - annotationApiAnnHsLet = annotation' (text "ApiAnn' AnnsLet") + annotationEpAnnHsLet :: EpAnn' AnnsLet -> SDoc + annotationEpAnnHsLet = annotation' (text "EpAnn' AnnsLet") - annotationAnnList :: ApiAnn' AnnList -> SDoc - annotationAnnList = annotation' (text "ApiAnn' AnnList") + annotationAnnList :: EpAnn' AnnList -> SDoc + annotationAnnList = annotation' (text "EpAnn' AnnList") - annotationApiAnnImportDecl :: ApiAnn' ApiAnnImportDecl -> SDoc - annotationApiAnnImportDecl = annotation' (text "ApiAnn' ApiAnnImportDecl") + annotationEpAnnImportDecl :: EpAnn' EpAnnImportDecl -> SDoc + annotationEpAnnImportDecl = annotation' (text "EpAnn' EpAnnImportDecl") - annotationAnnParen :: ApiAnn' AnnParen -> SDoc - annotationAnnParen = annotation' (text "ApiAnn' AnnParen") + annotationAnnParen :: EpAnn' AnnParen -> SDoc + annotationAnnParen = annotation' (text "EpAnn' AnnParen") - annotationTrailingAnn :: ApiAnn' TrailingAnn -> SDoc - annotationTrailingAnn = annotation' (text "ApiAnn' TrailingAnn") + annotationTrailingAnn :: EpAnn' TrailingAnn -> SDoc + annotationTrailingAnn = annotation' (text "EpAnn' TrailingAnn") annotation' :: forall a .(Data a, Typeable a) - => SDoc -> ApiAnn' a -> SDoc + => SDoc -> EpAnn' a -> SDoc annotation' tag anns = case ba of - BlankApiAnnotations -> parens (text "blanked:" <+> tag) - NoBlankApiAnnotations -> parens $ text (showConstr (toConstr anns)) + BlankEpAnnotations -> parens (text "blanked:" <+> tag) + NoBlankEpAnnotations -> parens $ text (showConstr (toConstr anns)) $$ vcat (gmapQ showAstData' anns) -- ------------------------- - srcSpanAnnA :: SrcSpanAnn' (ApiAnn' AnnListItem) -> SDoc + srcSpanAnnA :: SrcSpanAnn' (EpAnn' AnnListItem) -> SDoc srcSpanAnnA = locatedAnn'' (text "SrcSpanAnnA") - srcSpanAnnL :: SrcSpanAnn' (ApiAnn' AnnList) -> SDoc + srcSpanAnnL :: SrcSpanAnn' (EpAnn' AnnList) -> SDoc srcSpanAnnL = locatedAnn'' (text "SrcSpanAnnL") - srcSpanAnnP :: SrcSpanAnn' (ApiAnn' AnnPragma) -> SDoc + srcSpanAnnP :: SrcSpanAnn' (EpAnn' AnnPragma) -> SDoc srcSpanAnnP = locatedAnn'' (text "SrcSpanAnnP") - srcSpanAnnC :: SrcSpanAnn' (ApiAnn' AnnContext) -> SDoc + srcSpanAnnC :: SrcSpanAnn' (EpAnn' AnnContext) -> SDoc srcSpanAnnC = locatedAnn'' (text "SrcSpanAnnC") - srcSpanAnnN :: SrcSpanAnn' (ApiAnn' NameAnn) -> SDoc + srcSpanAnnN :: SrcSpanAnn' (EpAnn' NameAnn) -> SDoc srcSpanAnnN = locatedAnn'' (text "SrcSpanAnnN") locatedAnn'' :: forall a. (Typeable a, Data a) @@ -283,9 +283,9 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 case cast ss of Just ((SrcSpanAnn ann s) :: SrcSpanAnn' a) -> case ba of - BlankApiAnnotations + BlankEpAnnotations -> parens (text "blanked:" <+> tag) - NoBlankApiAnnotations + NoBlankEpAnnotations -> text "SrcSpanAnn" <+> showAstData' ann <+> srcSpan s Nothing -> text "locatedAnn:unmatched" <+> tag diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs index 0659c0f654..f9782756bd 100644 --- a/compiler/GHC/Hs/Expr.hs +++ b/compiler/GHC/Hs/Expr.hs @@ -206,13 +206,13 @@ could only do that if the extension field was strict (#18764) -- API Annotations types -data ApiAnnHsCase = ApiAnnHsCase +data EpAnnHsCase = EpAnnHsCase { hsCaseAnnCase :: AnnAnchor , hsCaseAnnOf :: AnnAnchor , hsCaseAnnsRest :: [AddEpAnn] } deriving Data -data ApiAnnUnboundVar = ApiAnnUnboundVar +data EpAnnUnboundVar = EpAnnUnboundVar { hsUnboundBackquotes :: (AnnAnchor, AnnAnchor) , hsUnboundHole :: AnnAnchor } deriving Data @@ -224,15 +224,15 @@ type instance XLam (GhcPass _) = NoExtField -- OverLabel not present in GhcTc pass; see GHC.Rename.Expr -- Note [Handling overloaded and rebindable constructs] -type instance XOverLabel GhcPs = ApiAnnCO -type instance XOverLabel GhcRn = ApiAnnCO +type instance XOverLabel GhcPs = EpAnnCO +type instance XOverLabel GhcRn = EpAnnCO type instance XOverLabel GhcTc = Void -- See Note [Constructor cannot occur] -- --------------------------------------------------------------------- type instance XVar (GhcPass _) = NoExtField -type instance XUnboundVar GhcPs = ApiAnn' ApiAnnUnboundVar +type instance XUnboundVar GhcPs = EpAnn' EpAnnUnboundVar type instance XUnboundVar GhcRn = NoExtField type instance XUnboundVar GhcTc = HoleExprRef -- We really don't need the whole HoleExprRef; just the IORef EvTerm @@ -242,14 +242,14 @@ type instance XUnboundVar GhcTc = HoleExprRef type instance XConLikeOut (GhcPass _) = NoExtField type instance XRecFld (GhcPass _) = NoExtField -type instance XIPVar (GhcPass _) = ApiAnnCO -type instance XOverLitE (GhcPass _) = ApiAnnCO -type instance XLitE (GhcPass _) = ApiAnnCO +type instance XIPVar (GhcPass _) = EpAnnCO +type instance XOverLitE (GhcPass _) = EpAnnCO +type instance XLitE (GhcPass _) = EpAnnCO type instance XLam (GhcPass _) = NoExtField -type instance XLamCase (GhcPass _) = ApiAnn -type instance XApp (GhcPass _) = ApiAnnCO +type instance XLamCase (GhcPass _) = EpAnn +type instance XApp (GhcPass _) = EpAnnCO type instance XAppTypeE GhcPs = SrcSpan -- Where the `@` lives type instance XAppTypeE GhcRn = NoExtField @@ -257,55 +257,55 @@ type instance XAppTypeE GhcTc = Type -- OpApp not present in GhcTc pass; see GHC.Rename.Expr -- Note [Handling overloaded and rebindable constructs] -type instance XOpApp GhcPs = ApiAnn +type instance XOpApp GhcPs = EpAnn type instance XOpApp GhcRn = Fixity type instance XOpApp GhcTc = Void -- See Note [Constructor cannot occur] -- SectionL, SectionR not present in GhcTc pass; see GHC.Rename.Expr -- Note [Handling overloaded and rebindable constructs] -type instance XSectionL GhcPs = ApiAnnCO -type instance XSectionR GhcPs = ApiAnnCO -type instance XSectionL GhcRn = ApiAnnCO -type instance XSectionR GhcRn = ApiAnnCO +type instance XSectionL GhcPs = EpAnnCO +type instance XSectionR GhcPs = EpAnnCO +type instance XSectionL GhcRn = EpAnnCO +type instance XSectionR GhcRn = EpAnnCO type instance XSectionL GhcTc = Void -- See Note [Constructor cannot occur] type instance XSectionR GhcTc = Void -- See Note [Constructor cannot occur] -type instance XNegApp GhcPs = ApiAnn +type instance XNegApp GhcPs = EpAnn type instance XNegApp GhcRn = NoExtField type instance XNegApp GhcTc = NoExtField -type instance XPar (GhcPass _) = ApiAnn' AnnParen +type instance XPar (GhcPass _) = EpAnn' AnnParen -type instance XExplicitTuple GhcPs = ApiAnn +type instance XExplicitTuple GhcPs = EpAnn type instance XExplicitTuple GhcRn = NoExtField type instance XExplicitTuple GhcTc = NoExtField -type instance XExplicitSum GhcPs = ApiAnn' AnnExplicitSum +type instance XExplicitSum GhcPs = EpAnn' AnnExplicitSum type instance XExplicitSum GhcRn = NoExtField type instance XExplicitSum GhcTc = [Type] -type instance XCase GhcPs = ApiAnn' ApiAnnHsCase +type instance XCase GhcPs = EpAnn' EpAnnHsCase type instance XCase GhcRn = NoExtField type instance XCase GhcTc = NoExtField -type instance XIf GhcPs = ApiAnn +type instance XIf GhcPs = EpAnn type instance XIf GhcRn = NoExtField type instance XIf GhcTc = NoExtField -type instance XMultiIf GhcPs = ApiAnn +type instance XMultiIf GhcPs = EpAnn type instance XMultiIf GhcRn = NoExtField type instance XMultiIf GhcTc = Type -type instance XLet GhcPs = ApiAnn' AnnsLet +type instance XLet GhcPs = EpAnn' AnnsLet type instance XLet GhcRn = NoExtField type instance XLet GhcTc = NoExtField -type instance XDo GhcPs = ApiAnn' AnnList +type instance XDo GhcPs = EpAnn' AnnList type instance XDo GhcRn = NoExtField type instance XDo GhcTc = Type -type instance XExplicitList GhcPs = ApiAnn' AnnList +type instance XExplicitList GhcPs = EpAnn' AnnList type instance XExplicitList GhcRn = NoExtField type instance XExplicitList GhcTc = Type -- GhcPs: ExplicitList includes all source-level @@ -316,43 +316,43 @@ type instance XExplicitList GhcTc = Type -- See Note [Handling overloaded and rebindable constructs] -- in GHC.Rename.Expr -type instance XRecordCon GhcPs = ApiAnn +type instance XRecordCon GhcPs = EpAnn type instance XRecordCon GhcRn = NoExtField type instance XRecordCon GhcTc = PostTcExpr -- Instantiated constructor function -type instance XRecordUpd GhcPs = ApiAnn +type instance XRecordUpd GhcPs = EpAnn type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc -type instance XGetField GhcPs = ApiAnnCO +type instance XGetField GhcPs = EpAnnCO type instance XGetField GhcRn = NoExtField type instance XGetField GhcTc = Void -- HsGetField is eliminated by the renamer. See [Handling overloaded -- and rebindable constructs]. -type instance XProjection GhcPs = ApiAnn' AnnProjection +type instance XProjection GhcPs = EpAnn' AnnProjection type instance XProjection GhcRn = NoExtField type instance XProjection GhcTc = Void -- HsProjection is eliminated by the renamer. See [Handling overloaded -- and rebindable constructs]. -type instance XExprWithTySig GhcPs = ApiAnn +type instance XExprWithTySig GhcPs = EpAnn type instance XExprWithTySig GhcRn = NoExtField type instance XExprWithTySig GhcTc = NoExtField -type instance XArithSeq GhcPs = ApiAnn +type instance XArithSeq GhcPs = EpAnn type instance XArithSeq GhcRn = NoExtField type instance XArithSeq GhcTc = PostTcExpr -type instance XBracket (GhcPass _) = ApiAnn +type instance XBracket (GhcPass _) = EpAnn type instance XRnBracketOut (GhcPass _) = NoExtField type instance XTcBracketOut (GhcPass _) = NoExtField -type instance XSpliceE (GhcPass _) = ApiAnnCO -type instance XProc (GhcPass _) = ApiAnn +type instance XSpliceE (GhcPass _) = EpAnnCO +type instance XProc (GhcPass _) = EpAnn -type instance XStatic GhcPs = ApiAnn +type instance XStatic GhcPs = EpAnn type instance XStatic GhcRn = NameSet type instance XStatic GhcTc = NameSet @@ -403,15 +403,15 @@ data AnnProjection -- --------------------------------------------------------------------- -type instance XSCC (GhcPass _) = ApiAnn' AnnPragma +type instance XSCC (GhcPass _) = EpAnn' AnnPragma type instance XXPragE (GhcPass _) = NoExtCon -type instance XCHsFieldLabel (GhcPass _) = ApiAnn' AnnFieldLabel +type instance XCHsFieldLabel (GhcPass _) = EpAnn' AnnFieldLabel type instance XXHsFieldLabel (GhcPass _) = NoExtCon -type instance XPresent (GhcPass _) = ApiAnn +type instance XPresent (GhcPass _) = EpAnn -type instance XMissing GhcPs = ApiAnn' AnnAnchor +type instance XMissing GhcPs = EpAnn' AnnAnchor type instance XMissing GhcRn = NoExtField type instance XMissing GhcTc = Scaled Type @@ -981,33 +981,33 @@ instance (Outputable a, Outputable b) => Outputable (HsExpansion a b) where ************************************************************************ -} -type instance XCmdArrApp GhcPs = ApiAnn' AddEpAnn +type instance XCmdArrApp GhcPs = EpAnn' AddEpAnn type instance XCmdArrApp GhcRn = NoExtField type instance XCmdArrApp GhcTc = Type -type instance XCmdArrForm GhcPs = ApiAnn' AnnList +type instance XCmdArrForm GhcPs = EpAnn' AnnList type instance XCmdArrForm GhcRn = NoExtField type instance XCmdArrForm GhcTc = NoExtField -type instance XCmdApp (GhcPass _) = ApiAnnCO +type instance XCmdApp (GhcPass _) = EpAnnCO type instance XCmdLam (GhcPass _) = NoExtField -type instance XCmdPar (GhcPass _) = ApiAnn' AnnParen +type instance XCmdPar (GhcPass _) = EpAnn' AnnParen -type instance XCmdCase GhcPs = ApiAnn' ApiAnnHsCase +type instance XCmdCase GhcPs = EpAnn' EpAnnHsCase type instance XCmdCase GhcRn = NoExtField type instance XCmdCase GhcTc = NoExtField -type instance XCmdLamCase (GhcPass _) = ApiAnn +type instance XCmdLamCase (GhcPass _) = EpAnn -type instance XCmdIf GhcPs = ApiAnn +type instance XCmdIf GhcPs = EpAnn type instance XCmdIf GhcRn = NoExtField type instance XCmdIf GhcTc = NoExtField -type instance XCmdLet GhcPs = ApiAnn' AnnsLet +type instance XCmdLet GhcPs = EpAnn' AnnsLet type instance XCmdLet GhcRn = NoExtField type instance XCmdLet GhcTc = NoExtField -type instance XCmdDo GhcPs = ApiAnn' AnnList +type instance XCmdDo GhcPs = EpAnn' AnnList type instance XCmdDo GhcRn = NoExtField type instance XCmdDo GhcTc = Type @@ -1152,7 +1152,7 @@ type instance XMG GhcTc b = MatchGroupTc type instance XXMatchGroup (GhcPass _) b = NoExtCon -type instance XCMatch (GhcPass _) b = ApiAnn +type instance XCMatch (GhcPass _) b = EpAnn type instance XXMatch (GhcPass _) b = NoExtCon instance (OutputableBndrId pr, Outputable body) @@ -1190,7 +1190,7 @@ data GrhsAnn ga_sep :: AddEpAnn -- ^ Match separator location } deriving (Data) -type instance XCGRHS (GhcPass _) _ = ApiAnn' GrhsAnn +type instance XCGRHS (GhcPass _) _ = EpAnn' GrhsAnn -- Location of matchSeparator -- TODO:AZ does this belong on the GRHS, or GRHSs? @@ -1304,7 +1304,7 @@ data RecStmtTc = type instance XLastStmt (GhcPass _) (GhcPass _) b = NoExtField -type instance XBindStmt (GhcPass _) GhcPs b = ApiAnn +type instance XBindStmt (GhcPass _) GhcPs b = EpAnn type instance XBindStmt (GhcPass _) GhcRn b = XBindStmtRn type instance XBindStmt (GhcPass _) GhcTc b = XBindStmtTc @@ -1328,17 +1328,17 @@ type instance XBodyStmt (GhcPass _) GhcPs b = NoExtField type instance XBodyStmt (GhcPass _) GhcRn b = NoExtField type instance XBodyStmt (GhcPass _) GhcTc b = Type -type instance XLetStmt (GhcPass _) (GhcPass _) b = ApiAnn +type instance XLetStmt (GhcPass _) (GhcPass _) b = EpAnn type instance XParStmt (GhcPass _) GhcPs b = NoExtField type instance XParStmt (GhcPass _) GhcRn b = NoExtField type instance XParStmt (GhcPass _) GhcTc b = Type -type instance XTransStmt (GhcPass _) GhcPs b = ApiAnn +type instance XTransStmt (GhcPass _) GhcPs b = EpAnn type instance XTransStmt (GhcPass _) GhcRn b = NoExtField type instance XTransStmt (GhcPass _) GhcTc b = Type -type instance XRecStmt (GhcPass _) GhcPs b = ApiAnn' AnnList +type instance XRecStmt (GhcPass _) GhcPs b = EpAnn' AnnList type instance XRecStmt (GhcPass _) GhcRn b = NoExtField type instance XRecStmt (GhcPass _) GhcTc b = RecStmtTc @@ -1523,8 +1523,8 @@ pprQuals quals = interpp'SP quals newtype HsSplicedT = HsSplicedT DelayedSplice deriving (Data) -type instance XTypedSplice (GhcPass _) = ApiAnn -type instance XUntypedSplice (GhcPass _) = ApiAnn +type instance XTypedSplice (GhcPass _) = EpAnn +type instance XUntypedSplice (GhcPass _) = EpAnn type instance XQuasiQuote (GhcPass _) = NoExtField type instance XSpliced (GhcPass _) = NoExtField type instance XXSplice GhcPs = NoExtCon @@ -1838,6 +1838,6 @@ type instance Anno (HsSplice (GhcPass p)) = SrcSpanAnnA type instance Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] = SrcSpanAnnL type instance Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] = SrcSpanAnnL -instance (Anno a ~ SrcSpanAnn' (ApiAnn' an)) +instance (Anno a ~ SrcSpanAnn' (EpAnn' an)) => WrapXRec (GhcPass p) a where wrapXRec = noLocA diff --git a/compiler/GHC/Hs/Extension.hs b/compiler/GHC/Hs/Extension.hs index 3b317f569f..1134e2520a 100644 --- a/compiler/GHC/Hs/Extension.hs +++ b/compiler/GHC/Hs/Extension.hs @@ -101,7 +101,7 @@ type instance Anno RdrName = SrcSpanAnnN type instance Anno Name = SrcSpanAnnN type instance Anno Id = SrcSpanAnnN -type IsSrcSpanAnn p a = ( Anno (IdGhcP p) ~ SrcSpanAnn' (ApiAnn' a), +type IsSrcSpanAnn p a = ( Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn' a), IsPass p) instance UnXRec (GhcPass p) where diff --git a/compiler/GHC/Hs/ImpExp.hs b/compiler/GHC/Hs/ImpExp.hs index f4c40bd185..309d0d8c62 100644 --- a/compiler/GHC/Hs/ImpExp.hs +++ b/compiler/GHC/Hs/ImpExp.hs @@ -113,7 +113,7 @@ data ImportDecl pass -- For details on above see note [Api annotations] in GHC.Parser.Annotation -type instance XCImportDecl GhcPs = ApiAnn' ApiAnnImportDecl +type instance XCImportDecl GhcPs = EpAnn' EpAnnImportDecl type instance XCImportDecl GhcRn = NoExtField type instance XCImportDecl GhcTc = NoExtField @@ -126,7 +126,7 @@ type instance Anno [LocatedA (IE (GhcPass p))] = SrcSpanAnnL -- API Annotations types -data ApiAnnImportDecl = ApiAnnImportDecl +data EpAnnImportDecl = EpAnnImportDecl { importDeclAnnImport :: AnnAnchor , importDeclAnnPragma :: Maybe (AnnAnchor, AnnAnchor) , importDeclAnnSafe :: Maybe AnnAnchor @@ -286,15 +286,15 @@ type instance XIEVar GhcPs = NoExtField type instance XIEVar GhcRn = NoExtField type instance XIEVar GhcTc = NoExtField -type instance XIEThingAbs (GhcPass _) = ApiAnn -type instance XIEThingAll (GhcPass _) = ApiAnn +type instance XIEThingAbs (GhcPass _) = EpAnn +type instance XIEThingAll (GhcPass _) = EpAnn -- See Note [IEThingWith] -type instance XIEThingWith (GhcPass 'Parsed) = ApiAnn +type instance XIEThingWith (GhcPass 'Parsed) = EpAnn type instance XIEThingWith (GhcPass 'Renamed) = [Located FieldLabel] type instance XIEThingWith (GhcPass 'Typechecked) = NoExtField -type instance XIEModuleContents GhcPs = ApiAnn +type instance XIEModuleContents GhcPs = EpAnn type instance XIEModuleContents GhcRn = NoExtField type instance XIEModuleContents GhcTc = NoExtField diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs index 34b4b8e173..36537728de 100644 --- a/compiler/GHC/Hs/Pat.hs +++ b/compiler/GHC/Hs/Pat.hs @@ -21,7 +21,7 @@ module GHC.Hs.Pat ( Pat(..), LPat, - ApiAnnSumPat(..), + EpAnnSumPat(..), ConPatTc (..), CoPat (..), ListPatTc(..), @@ -95,55 +95,55 @@ type instance XWildPat GhcTc = Type type instance XVarPat (GhcPass _) = NoExtField -type instance XLazyPat GhcPs = ApiAnn -- For '~' +type instance XLazyPat GhcPs = EpAnn -- For '~' type instance XLazyPat GhcRn = NoExtField type instance XLazyPat GhcTc = NoExtField -type instance XAsPat GhcPs = ApiAnn -- For '@' +type instance XAsPat GhcPs = EpAnn -- For '@' type instance XAsPat GhcRn = NoExtField type instance XAsPat GhcTc = NoExtField -type instance XParPat (GhcPass _) = ApiAnn' AnnParen +type instance XParPat (GhcPass _) = EpAnn' AnnParen -type instance XBangPat GhcPs = ApiAnn -- For '!' +type instance XBangPat GhcPs = EpAnn -- For '!' type instance XBangPat GhcRn = NoExtField type instance XBangPat GhcTc = NoExtField -- Note: XListPat cannot be extended when using GHC 8.0.2 as the bootstrap -- compiler, as it triggers https://gitlab.haskell.org/ghc/ghc/issues/14396 for -- `SyntaxExpr` -type instance XListPat GhcPs = ApiAnn' AnnList +type instance XListPat GhcPs = EpAnn' AnnList type instance XListPat GhcRn = Maybe (SyntaxExpr GhcRn) type instance XListPat GhcTc = ListPatTc -type instance XTuplePat GhcPs = ApiAnn +type instance XTuplePat GhcPs = EpAnn type instance XTuplePat GhcRn = NoExtField type instance XTuplePat GhcTc = [Type] -type instance XSumPat GhcPs = ApiAnn' ApiAnnSumPat +type instance XSumPat GhcPs = EpAnn' EpAnnSumPat type instance XSumPat GhcRn = NoExtField type instance XSumPat GhcTc = [Type] -type instance XConPat GhcPs = ApiAnn +type instance XConPat GhcPs = EpAnn type instance XConPat GhcRn = NoExtField type instance XConPat GhcTc = ConPatTc -type instance XViewPat GhcPs = ApiAnn +type instance XViewPat GhcPs = EpAnn type instance XViewPat GhcRn = NoExtField type instance XViewPat GhcTc = Type type instance XSplicePat (GhcPass _) = NoExtField type instance XLitPat (GhcPass _) = NoExtField -type instance XNPat GhcPs = ApiAnn -type instance XNPat GhcRn = ApiAnn +type instance XNPat GhcPs = EpAnn +type instance XNPat GhcRn = EpAnn type instance XNPat GhcTc = Type -type instance XNPlusKPat GhcPs = ApiAnn +type instance XNPlusKPat GhcPs = EpAnn type instance XNPlusKPat GhcRn = NoExtField type instance XNPlusKPat GhcTc = Type -type instance XSigPat GhcPs = ApiAnn +type instance XSigPat GhcPs = EpAnn type instance XSigPat GhcRn = NoExtField type instance XSigPat GhcTc = Type @@ -156,13 +156,13 @@ type instance ConLikeP GhcPs = RdrName -- IdP GhcPs type instance ConLikeP GhcRn = Name -- IdP GhcRn type instance ConLikeP GhcTc = ConLike -type instance XHsRecField _ = ApiAnn +type instance XHsRecField _ = EpAnn -- --------------------------------------------------------------------- -- API Annotations types -data ApiAnnSumPat = ApiAnnSumPat +data EpAnnSumPat = EpAnnSumPat { sumPatParens :: [AddEpAnn] , sumPatVbarsBefore :: [AnnAnchor] , sumPatVbarsAfter :: [AnnAnchor] diff --git a/compiler/GHC/Hs/Type.hs b/compiler/GHC/Hs/Type.hs index 5c49796b2f..ba07ad35b7 100644 --- a/compiler/GHC/Hs/Type.hs +++ b/compiler/GHC/Hs/Type.hs @@ -27,7 +27,7 @@ module GHC.Hs.Type ( hsLinear, hsUnrestricted, isUnrestricted, HsType(..), HsCoreTy, LHsType, HsKind, LHsKind, - HsForAllTelescope(..), ApiAnnForallTy, HsTyVarBndr(..), LHsTyVarBndr, + HsForAllTelescope(..), EpAnnForallTy, HsTyVarBndr(..), LHsTyVarBndr, LHsQTyVars(..), HsOuterTyVarBndrs(..), HsOuterFamEqnTyVarBndrs, HsOuterSigTyVarBndrs, HsWildCardBndrs(..), @@ -144,14 +144,14 @@ getBangStrictness _ = (HsSrcBang NoSourceText NoSrcUnpack NoSrcStrict) fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p) fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt -type instance XHsForAllVis (GhcPass _) = ApiAnnForallTy +type instance XHsForAllVis (GhcPass _) = EpAnnForallTy -- Location of 'forall' and '->' -type instance XHsForAllInvis (GhcPass _) = ApiAnnForallTy +type instance XHsForAllInvis (GhcPass _) = EpAnnForallTy -- Location of 'forall' and '.' type instance XXHsForAllTelescope (GhcPass _) = NoExtCon -type ApiAnnForallTy = ApiAnn' (AddEpAnn, AddEpAnn) +type EpAnnForallTy = EpAnn' (AddEpAnn, AddEpAnn) -- ^ Location of 'forall' and '->' for HsForAllVis -- Location of 'forall' and '.' for HsForAllInvis @@ -165,12 +165,12 @@ type instance XHsQTvs GhcTc = HsQTvsRn type instance XXLHsQTyVars (GhcPass _) = NoExtCon -mkHsForAllVisTele ::ApiAnnForallTy -> +mkHsForAllVisTele ::EpAnnForallTy -> [LHsTyVarBndr () (GhcPass p)] -> HsForAllTelescope (GhcPass p) mkHsForAllVisTele an vis_bndrs = HsForAllVis { hsf_xvis = an, hsf_vis_bndrs = vis_bndrs } -mkHsForAllInvisTele :: ApiAnnForallTy +mkHsForAllInvisTele :: EpAnnForallTy -> [LHsTyVarBndr Specificity (GhcPass p)] -> HsForAllTelescope (GhcPass p) mkHsForAllInvisTele an invis_bndrs = HsForAllInvis { hsf_xinvis = an, hsf_invis_bndrs = invis_bndrs } @@ -188,7 +188,7 @@ type instance XHsOuterImplicit GhcPs = NoExtField type instance XHsOuterImplicit GhcRn = [Name] type instance XHsOuterImplicit GhcTc = [TyVar] -type instance XHsOuterExplicit GhcPs _ = ApiAnnForallTy +type instance XHsOuterExplicit GhcPs _ = EpAnnForallTy type instance XHsOuterExplicit GhcRn _ = NoExtField type instance XHsOuterExplicit GhcTc flag = [VarBndr TyVar flag] @@ -228,7 +228,7 @@ hsOuterExplicitBndrs (HsOuterImplicit{}) = [] mkHsOuterImplicit :: HsOuterTyVarBndrs flag GhcPs mkHsOuterImplicit = HsOuterImplicit{hso_ximplicit = noExtField} -mkHsOuterExplicit :: ApiAnnForallTy -> [LHsTyVarBndr flag GhcPs] +mkHsOuterExplicit :: EpAnnForallTy -> [LHsTyVarBndr flag GhcPs] -> HsOuterTyVarBndrs flag GhcPs mkHsOuterExplicit an bndrs = HsOuterExplicit { hso_xexplicit = an , hso_bndrs = bndrs } @@ -238,7 +238,7 @@ mkHsImplicitSigType body = HsSig { sig_ext = noExtField , sig_bndrs = mkHsOuterImplicit, sig_body = body } -mkHsExplicitSigType :: ApiAnnForallTy +mkHsExplicitSigType :: EpAnnForallTy -> [LHsTyVarBndr Specificity GhcPs] -> LHsType GhcPs -> HsSigType GhcPs mkHsExplicitSigType an bndrs body = @@ -259,8 +259,8 @@ mkEmptyWildCardBndrs x = HsWC { hswc_body = x -------------------------------------------------- -type instance XUserTyVar (GhcPass _) = ApiAnn -type instance XKindedTyVar (GhcPass _) = ApiAnn +type instance XUserTyVar (GhcPass _) = EpAnn +type instance XKindedTyVar (GhcPass _) = EpAnn type instance XXTyVarBndr (GhcPass _) = NoExtCon @@ -285,17 +285,17 @@ instance NamedThing (HsTyVarBndr flag GhcRn) where type instance XForAllTy (GhcPass _) = NoExtField type instance XQualTy (GhcPass _) = NoExtField -type instance XTyVar (GhcPass _) = ApiAnn +type instance XTyVar (GhcPass _) = EpAnn type instance XAppTy (GhcPass _) = NoExtField -type instance XFunTy (GhcPass _) = ApiAnn' TrailingAnn -- For the AnnRarrow or AnnLolly -type instance XListTy (GhcPass _) = ApiAnn' AnnParen -type instance XTupleTy (GhcPass _) = ApiAnn' AnnParen -type instance XSumTy (GhcPass _) = ApiAnn' AnnParen +type instance XFunTy (GhcPass _) = EpAnn' TrailingAnn -- For the AnnRarrow or AnnLolly +type instance XListTy (GhcPass _) = EpAnn' AnnParen +type instance XTupleTy (GhcPass _) = EpAnn' AnnParen +type instance XSumTy (GhcPass _) = EpAnn' AnnParen type instance XOpTy (GhcPass _) = NoExtField -type instance XParTy (GhcPass _) = ApiAnn' AnnParen -type instance XIParamTy (GhcPass _) = ApiAnn +type instance XParTy (GhcPass _) = EpAnn' AnnParen +type instance XIParamTy (GhcPass _) = EpAnn type instance XStarTy (GhcPass _) = NoExtField -type instance XKindSig (GhcPass _) = ApiAnn +type instance XKindSig (GhcPass _) = EpAnn type instance XAppKindTy (GhcPass _) = SrcSpan -- Where the `@` lives @@ -303,18 +303,18 @@ type instance XSpliceTy GhcPs = NoExtField type instance XSpliceTy GhcRn = NoExtField type instance XSpliceTy GhcTc = Kind -type instance XDocTy (GhcPass _) = ApiAnn -type instance XBangTy (GhcPass _) = ApiAnn +type instance XDocTy (GhcPass _) = EpAnn +type instance XBangTy (GhcPass _) = EpAnn -type instance XRecTy GhcPs = ApiAnn' AnnList +type instance XRecTy GhcPs = EpAnn' AnnList type instance XRecTy GhcRn = NoExtField type instance XRecTy GhcTc = NoExtField -type instance XExplicitListTy GhcPs = ApiAnn +type instance XExplicitListTy GhcPs = EpAnn type instance XExplicitListTy GhcRn = NoExtField type instance XExplicitListTy GhcTc = Kind -type instance XExplicitTupleTy GhcPs = ApiAnn +type instance XExplicitTupleTy GhcPs = EpAnn type instance XExplicitTupleTy GhcRn = NoExtField type instance XExplicitTupleTy GhcTc = [Kind] @@ -354,7 +354,7 @@ pprHsArrow (HsUnrestrictedArrow _) = arrow pprHsArrow (HsLinearArrow _ _) = lollipop pprHsArrow (HsExplicitMult _ _ p) = (mulArrow (ppr p)) -type instance XConDeclField (GhcPass _) = ApiAnn +type instance XConDeclField (GhcPass _) = EpAnn type instance XXConDeclField (GhcPass _) = NoExtCon instance OutputableBndrId p @@ -474,7 +474,7 @@ mkHsAppKindTy ext ty k -- It returns API Annotations for any parens removed splitHsFunType :: LHsType (GhcPass p) - -> ( [AddEpAnn], ApiAnnComments -- The locations of any parens and + -> ( [AddEpAnn], EpAnnComments -- The locations of any parens and -- comments discarded , [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p)) splitHsFunType ty = go ty @@ -486,7 +486,7 @@ splitHsFunType ty = go ty cs' = cs S.<> apiAnnComments (ann l) S.<> apiAnnComments an in (anns', cs', args, res) - go (L ll (HsFunTy (ApiAnn _ an cs) mult x y)) + go (L ll (HsFunTy (EpAnn _ an cs) mult x y)) | (anns, csy, args, res) <- splitHsFunType y = (anns, csy S.<> apiAnnComments (ann ll), HsScaled mult x':args, res) where @@ -618,11 +618,11 @@ splitLHsGadtTy (L _ sig_ty) -- Unlike 'splitLHsSigmaTyInvis', this function does not look through -- parentheses, hence the suffix @_KP@ (short for \"Keep Parentheses\"). splitLHsForAllTyInvis :: - LHsType (GhcPass pass) -> ( (ApiAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]) + LHsType (GhcPass pass) -> ( (EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]) , LHsType (GhcPass pass)) splitLHsForAllTyInvis ty | ((mb_tvbs), body) <- splitLHsForAllTyInvis_KP (ignoreParens ty) - = (fromMaybe (ApiAnnNotUsed,[]) mb_tvbs, body) + = (fromMaybe (EpAnnNotUsed,[]) mb_tvbs, body) -- | Decompose a type of the form @forall <tvs>. body@ into its constituent -- parts. Only splits type variable binders that @@ -636,7 +636,7 @@ splitLHsForAllTyInvis ty -- Unlike 'splitLHsForAllTyInvis', this function does not look through -- parentheses, hence the suffix @_KP@ (short for \"Keep Parentheses\"). splitLHsForAllTyInvis_KP :: - LHsType (GhcPass pass) -> (Maybe (ApiAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]) + LHsType (GhcPass pass) -> (Maybe (EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]) , LHsType (GhcPass pass)) splitLHsForAllTyInvis_KP lty@(L _ ty) = case ty of diff --git a/compiler/GHC/Hs/Utils.hs b/compiler/GHC/Hs/Utils.hs index 7e298b8978..8151041996 100644 --- a/compiler/GHC/Hs/Utils.hs +++ b/compiler/GHC/Hs/Utils.hs @@ -190,14 +190,14 @@ mkSimpleMatch ctxt pats rhs unguardedGRHSs :: Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan - => SrcSpan -> LocatedA (body (GhcPass p)) -> ApiAnn' GrhsAnn + => SrcSpan -> LocatedA (body (GhcPass p)) -> EpAnn' GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) unguardedGRHSs loc rhs an = GRHSs noExtField (unguardedRHS an loc rhs) emptyLocalBinds unguardedRHS :: Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan - => ApiAnn' GrhsAnn -> SrcSpan -> LocatedA (body (GhcPass p)) + => EpAnn' GrhsAnn -> SrcSpan -> LocatedA (body (GhcPass p)) -> [LGRHS (GhcPass p) (LocatedA (body (GhcPass p)))] unguardedRHS an loc rhs = [L loc (GRHS an [] rhs)] @@ -305,16 +305,16 @@ mkHsIntegral :: IntegralLit -> HsOverLit GhcPs mkHsFractional :: FractionalLit -> HsOverLit GhcPs mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs mkHsDo :: HsStmtContext GhcRn -> LocatedL [ExprLStmt GhcPs] -> HsExpr GhcPs -mkHsDoAnns :: HsStmtContext GhcRn -> LocatedL [ExprLStmt GhcPs] -> ApiAnn' AnnList -> HsExpr GhcPs +mkHsDoAnns :: HsStmtContext GhcRn -> LocatedL [ExprLStmt GhcPs] -> EpAnn' AnnList -> HsExpr GhcPs mkHsComp :: HsStmtContext GhcRn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> HsExpr GhcPs mkHsCompAnns :: HsStmtContext GhcRn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs - -> ApiAnn' AnnList + -> EpAnn' AnnList -> HsExpr GhcPs -mkNPat :: Located (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> ApiAnn +mkNPat :: Located (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpAnn -> Pat GhcPs -mkNPlusKPat :: LocatedN RdrName -> Located (HsOverLit GhcPs) -> ApiAnn +mkNPlusKPat :: LocatedN RdrName -> Located (HsOverLit GhcPs) -> EpAnn -> Pat GhcPs -- NB: The following functions all use noSyntaxExpr: the generated expressions @@ -323,7 +323,7 @@ mkLastStmt :: IsPass idR => LocatedA (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (LocatedA (bodyR (GhcPass idR))) mkBodyStmt :: LocatedA (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (LocatedA (bodyR GhcPs)) -mkPsBindStmt :: ApiAnn -> LPat GhcPs -> LocatedA (bodyR GhcPs) +mkPsBindStmt :: EpAnn -> LPat GhcPs -> LocatedA (bodyR GhcPs) -> StmtLR GhcPs GhcPs (LocatedA (bodyR GhcPs)) mkRnBindStmt :: LPat GhcRn -> LocatedA (bodyR GhcRn) -> StmtLR GhcRn GhcRn (LocatedA (bodyR GhcRn)) @@ -345,7 +345,7 @@ mkRecStmt :: (Anno [GenLocated (Anno (StmtLR (GhcPass idL) GhcPs bodyR)) (StmtLR (GhcPass idL) GhcPs bodyR)] ~ SrcSpanAnnL) - => ApiAnn' AnnList + => EpAnn' AnnList -> LocatedL [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR @@ -363,12 +363,12 @@ mkHsCompAnns ctxt stmts expr anns = mkHsDoAnns ctxt (mkLocatedList (stmts ++ [la last_stmt = L (noAnnSrcSpan $ getLocA expr) $ mkLastStmt expr -- restricted to GhcPs because other phases might need a SyntaxExpr -mkHsIf :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> ApiAnn +mkHsIf :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> EpAnn -> HsExpr GhcPs mkHsIf c a b anns = HsIf anns c a b -- restricted to GhcPs because other phases might need a SyntaxExpr -mkHsCmdIf :: LHsExpr GhcPs -> LHsCmd GhcPs -> LHsCmd GhcPs -> ApiAnn +mkHsCmdIf :: LHsExpr GhcPs -> LHsCmd GhcPs -> LHsCmd GhcPs -> EpAnn -> HsCmd GhcPs mkHsCmdIf c a b anns = HsCmdIf anns noSyntaxExpr c a b @@ -376,17 +376,17 @@ mkNPat lit neg anns = NPat anns lit neg noSyntaxExpr mkNPlusKPat id lit anns = NPlusKPat anns id lit (unLoc lit) noSyntaxExpr noSyntaxExpr -mkTransformStmt :: ApiAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs +mkTransformStmt :: EpAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) -mkTransformByStmt :: ApiAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs +mkTransformByStmt :: EpAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) -mkGroupUsingStmt :: ApiAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs +mkGroupUsingStmt :: EpAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) -mkGroupByUsingStmt :: ApiAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs +mkGroupByUsingStmt :: EpAnn -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) -emptyTransStmt :: ApiAnn -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) +emptyTransStmt :: EpAnn -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) emptyTransStmt anns = TransStmt { trS_ext = anns , trS_form = panic "emptyTransStmt: form" , trS_stmts = [], trS_bndrs = [] @@ -436,7 +436,7 @@ emptyRecStmtId = emptyRecStmt' unitRecStmtTc -- a panic might trigger during zonking mkRecStmt anns stmts = (emptyRecStmt' anns) { recS_stmts = stmts } -mkLetStmt :: ApiAnn -> HsLocalBinds GhcPs -> StmtLR GhcPs GhcPs (LocatedA b) +mkLetStmt :: EpAnn -> HsLocalBinds GhcPs -> StmtLR GhcPs GhcPs (LocatedA b) mkLetStmt anns binds = LetStmt anns binds ------------------------------- @@ -448,10 +448,10 @@ mkHsOpApp e1 op e2 = OpApp noAnn e1 (noLocA (HsVar noExtField (noLocA op))) e2 unqualSplice :: RdrName unqualSplice = mkRdrUnqual (mkVarOccFS (fsLit "splice")) -mkUntypedSplice :: ApiAnn -> SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs +mkUntypedSplice :: EpAnn -> SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs mkUntypedSplice ann hasParen e = HsUntypedSplice ann hasParen unqualSplice e -mkTypedSplice :: ApiAnn -> SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs +mkTypedSplice :: EpAnn -> SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs mkTypedSplice ann hasParen e = HsTypedSplice ann hasParen unqualSplice e mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs @@ -657,7 +657,7 @@ mkLHsVarTuple ids ext = mkLHsTupleExpr (map nlHsVar ids) ext nlTuplePat :: [LPat GhcPs] -> Boxity -> LPat GhcPs nlTuplePat pats box = noLocA (TuplePat noAnn pats box) -missingTupArg :: ApiAnn' AnnAnchor -> HsTupArg GhcPs +missingTupArg :: EpAnn' AnnAnchor -> HsTupArg GhcPs missingTupArg ann = Missing ann mkLHsPatTup :: [LPat GhcRn] -> LPat GhcRn @@ -862,7 +862,7 @@ mkVarBind var rhs = L (getLoc rhs) $ var_id = var, var_rhs = rhs } mkPatSynBind :: LocatedN RdrName -> HsPatSynDetails GhcPs - -> LPat GhcPs -> HsPatSynDir GhcPs -> ApiAnn -> HsBind GhcPs + -> LPat GhcPs -> HsPatSynDir GhcPs -> EpAnn -> HsBind GhcPs mkPatSynBind name details lpat dir anns = PatSynBind noExtField psb where psb = PSB{ psb_ext = anns diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y index 79293b22cf..19b5642ff0 100644 --- a/compiler/GHC/Parser.y +++ b/compiler/GHC/Parser.y @@ -880,7 +880,7 @@ unitdecl :: { LHsUnitDecl PackageName } signature :: { Located HsModule } : 'signature' modid maybemodwarning maybeexports 'where' body {% fileSrcSpan >>= \ loc -> - acs (\cs-> (L loc (HsModule (ApiAnn (spanAsAnchor loc) (AnnsModule [mj AnnSignature $1, mj AnnWhere $5] (fstOf3 $6)) cs) + acs (\cs-> (L loc (HsModule (EpAnn (spanAsAnchor loc) (AnnsModule [mj AnnSignature $1, mj AnnWhere $5] (fstOf3 $6)) cs) (thdOf3 $6) (Just $2) $4 (fst $ sndOf3 $6) (snd $ sndOf3 $6) $3 Nothing)) ) } @@ -888,13 +888,13 @@ signature :: { Located HsModule } module :: { Located HsModule } : 'module' modid maybemodwarning maybeexports 'where' body {% fileSrcSpan >>= \ loc -> - acsFinal (\cs -> (L loc (HsModule (ApiAnn (spanAsAnchor loc) (AnnsModule [mj AnnModule $1, mj AnnWhere $5] (fstOf3 $6)) cs) + acsFinal (\cs -> (L loc (HsModule (EpAnn (spanAsAnchor loc) (AnnsModule [mj AnnModule $1, mj AnnWhere $5] (fstOf3 $6)) cs) (thdOf3 $6) (Just $2) $4 (fst $ sndOf3 $6) (snd $ sndOf3 $6) $3 Nothing) )) } | body2 {% fileSrcSpan >>= \ loc -> - acsFinal (\cs -> (L loc (HsModule (ApiAnn (spanAsAnchor loc) (AnnsModule [] (fstOf3 $1)) cs) + acsFinal (\cs -> (L loc (HsModule (EpAnn (spanAsAnchor loc) (AnnsModule [] (fstOf3 $1)) cs) (thdOf3 $1) Nothing Nothing (fst $ sndOf3 $1) (snd $ sndOf3 $1) Nothing Nothing))) } @@ -944,12 +944,12 @@ top1 :: { ([LImportDecl GhcPs], [LHsDecl GhcPs]) } header :: { Located HsModule } : 'module' modid maybemodwarning maybeexports 'where' header_body {% fileSrcSpan >>= \ loc -> - acs (\cs -> (L loc (HsModule (ApiAnn (spanAsAnchor loc) (AnnsModule [mj AnnModule $1,mj AnnWhere $5] (AnnList Nothing Nothing Nothing [] [])) cs) + acs (\cs -> (L loc (HsModule (EpAnn (spanAsAnchor loc) (AnnsModule [mj AnnModule $1,mj AnnWhere $5] (AnnList Nothing Nothing Nothing [] [])) cs) NoLayoutInfo (Just $2) $4 $6 [] $3 Nothing ))) } | 'signature' modid maybemodwarning maybeexports 'where' header_body {% fileSrcSpan >>= \ loc -> - acs (\cs -> (L loc (HsModule (ApiAnn (spanAsAnchor loc) (AnnsModule [mj AnnModule $1,mj AnnWhere $5] (AnnList Nothing Nothing Nothing [] [])) cs) + acs (\cs -> (L loc (HsModule (EpAnn (spanAsAnchor loc) (AnnsModule [mj AnnModule $1,mj AnnWhere $5] (AnnList Nothing Nothing Nothing [] [])) cs) NoLayoutInfo (Just $2) $4 $6 [] $3 Nothing ))) } | header_body2 @@ -1008,7 +1008,7 @@ exportlist1 :: { OrdList (LIE GhcPs) } export :: { OrdList (LIE GhcPs) } : qcname_ext export_subspec {% mkModuleImpExp (fst $ unLoc $2) $1 (snd $ unLoc $2) >>= \ie -> fmap (unitOL . reLocA) (return (sLL (reLoc $1) $> ie)) } - | 'module' modid {% fmap (unitOL . reLocA) (acs (\cs -> sLL $1 $> (IEModuleContents (ApiAnn (glR $1) [mj AnnModule $1] cs) $2))) } + | 'module' modid {% fmap (unitOL . reLocA) (acs (\cs -> sLL $1 $> (IEModuleContents (EpAnn (glR $1) [mj AnnModule $1] cs) $2))) } | 'pattern' qcon { unitOL (reLocA (sLL $1 (reLocN $>) (IEVar noExtField (sLLa $1 (reLocN $>) (IEPattern (glAA $1) $2))))) } @@ -1091,7 +1091,7 @@ importdecl :: { LImportDecl GhcPs } ; mPostQual = unLoc $7 } ; checkImportDecl mPreQual mPostQual ; let anns - = ApiAnnImportDecl + = EpAnnImportDecl { importDeclAnnImport = glAA $1 , importDeclAnnPragma = fst $ fst $2 , importDeclAnnSafe = fst $3 @@ -1100,7 +1100,7 @@ importdecl :: { LImportDecl GhcPs } , importDeclAnnAs = fst $8 } ; fmap reLocA $ acs (\cs -> L (comb5 $1 $6 $7 (snd $8) $9) $ - ImportDecl { ideclExt = ApiAnn (glR $1) anns cs + ImportDecl { ideclExt = EpAnn (glR $1) anns cs , ideclSourceSrc = snd $ fst $2 , ideclName = $6, ideclPkgQual = snd $5 , ideclSource = snd $2, ideclSafe = snd $3 @@ -1211,11 +1211,11 @@ topdecl :: { LHsDecl GhcPs } | stand_alone_deriving { sL1 $1 (DerivD noExtField (unLoc $1)) } | role_annot { sL1 $1 (RoleAnnotD noExtField (unLoc $1)) } | 'default' '(' comma_types0 ')' {% acsA (\cs -> sLL $1 $> - (DefD noExtField (DefaultDecl (ApiAnn (glR $1) [mj AnnDefault $1,mop $2,mcp $4] cs) $3))) } - | 'foreign' fdecl {% acsA (\cs -> sLL $1 $> ((snd $ unLoc $2) (ApiAnn (glR $1) (mj AnnForeign $1:(fst $ unLoc $2)) cs))) } - | '{-# DEPRECATED' deprecations '#-}' {% acsA (\cs -> sLL $1 $> $ WarningD noExtField (Warnings (ApiAnn (glR $1) [mo $1,mc $3] cs) (getDEPRECATED_PRAGs $1) (fromOL $2))) } - | '{-# WARNING' warnings '#-}' {% acsA (\cs -> sLL $1 $> $ WarningD noExtField (Warnings (ApiAnn (glR $1) [mo $1,mc $3] cs) (getWARNING_PRAGs $1) (fromOL $2))) } - | '{-# RULES' rules '#-}' {% acsA (\cs -> sLL $1 $> $ RuleD noExtField (HsRules (ApiAnn (glR $1) [mo $1,mc $3] cs) (getRULES_PRAGs $1) (reverse $2))) } + (DefD noExtField (DefaultDecl (EpAnn (glR $1) [mj AnnDefault $1,mop $2,mcp $4] cs) $3))) } + | 'foreign' fdecl {% acsA (\cs -> sLL $1 $> ((snd $ unLoc $2) (EpAnn (glR $1) (mj AnnForeign $1:(fst $ unLoc $2)) cs))) } + | '{-# DEPRECATED' deprecations '#-}' {% acsA (\cs -> sLL $1 $> $ WarningD noExtField (Warnings (EpAnn (glR $1) [mo $1,mc $3] cs) (getDEPRECATED_PRAGs $1) (fromOL $2))) } + | '{-# WARNING' warnings '#-}' {% acsA (\cs -> sLL $1 $> $ WarningD noExtField (Warnings (EpAnn (glR $1) [mo $1,mc $3] cs) (getWARNING_PRAGs $1) (fromOL $2))) } + | '{-# RULES' rules '#-}' {% acsA (\cs -> sLL $1 $> $ RuleD noExtField (HsRules (EpAnn (glR $1) [mo $1,mc $3] cs) (getRULES_PRAGs $1) (reverse $2))) } | annotation { $1 } | decl_no_th { $1 } @@ -1304,7 +1304,7 @@ inst_decl :: { LInstDecl GhcPs } {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (snd $ unLoc $4) ; let anns = (mj AnnInstance $1 : (fst $ unLoc $4)) ; let cid cs = ClsInstDecl - { cid_ext = (ApiAnn (glR $1) anns cs, NoAnnSortKey) + { cid_ext = (EpAnn (glR $1) anns cs, NoAnnSortKey) , cid_poly_ty = $3, cid_binds = binds , cid_sigs = mkClassOpSigs sigs , cid_tyfam_insts = ats @@ -1349,18 +1349,18 @@ overlap_pragma :: { Maybe (LocatedP OverlapMode) } | {- empty -} { Nothing } deriv_strategy_no_via :: { LDerivStrategy GhcPs } - : 'stock' {% acs (\cs -> sL1 $1 (StockStrategy (ApiAnn (glR $1) [mj AnnStock $1] cs))) } - | 'anyclass' {% acs (\cs -> sL1 $1 (AnyclassStrategy (ApiAnn (glR $1) [mj AnnAnyclass $1] cs))) } - | 'newtype' {% acs (\cs -> sL1 $1 (NewtypeStrategy (ApiAnn (glR $1) [mj AnnNewtype $1] cs))) } + : 'stock' {% acs (\cs -> sL1 $1 (StockStrategy (EpAnn (glR $1) [mj AnnStock $1] cs))) } + | 'anyclass' {% acs (\cs -> sL1 $1 (AnyclassStrategy (EpAnn (glR $1) [mj AnnAnyclass $1] cs))) } + | 'newtype' {% acs (\cs -> sL1 $1 (NewtypeStrategy (EpAnn (glR $1) [mj AnnNewtype $1] cs))) } deriv_strategy_via :: { LDerivStrategy GhcPs } - : 'via' sigktype {% acs (\cs -> sLLlA $1 $> (ViaStrategy (XViaStrategyPs (ApiAnn (glR $1) [mj AnnVia $1] cs) + : 'via' sigktype {% acs (\cs -> sLLlA $1 $> (ViaStrategy (XViaStrategyPs (EpAnn (glR $1) [mj AnnVia $1] cs) $2))) } deriv_standalone_strategy :: { Maybe (LDerivStrategy GhcPs) } - : 'stock' {% fmap Just $ acs (\cs -> sL1 $1 (StockStrategy (ApiAnn (glR $1) [mj AnnStock $1] cs))) } - | 'anyclass' {% fmap Just $ acs (\cs -> sL1 $1 (AnyclassStrategy (ApiAnn (glR $1) [mj AnnAnyclass $1] cs))) } - | 'newtype' {% fmap Just $ acs (\cs -> sL1 $1 (NewtypeStrategy (ApiAnn (glR $1) [mj AnnNewtype $1] cs))) } + : 'stock' {% fmap Just $ acs (\cs -> sL1 $1 (StockStrategy (EpAnn (glR $1) [mj AnnStock $1] cs))) } + | 'anyclass' {% fmap Just $ acs (\cs -> sL1 $1 (AnyclassStrategy (EpAnn (glR $1) [mj AnnAnyclass $1] cs))) } + | 'newtype' {% fmap Just $ acs (\cs -> sL1 $1 (NewtypeStrategy (EpAnn (glR $1) [mj AnnNewtype $1] cs))) } | deriv_strategy_via { Just $1 } | {- empty -} { Nothing } @@ -1373,7 +1373,7 @@ opt_injective_info :: { Located ([AddEpAnn], Maybe (LInjectivityAnn GhcPs)) } injectivity_cond :: { LInjectivityAnn GhcPs } : tyvarid '->' inj_varids - {% acs (\cs -> sLL (reLocN $1) $> (InjectivityAnn (ApiAnn (glNR $1) [mu AnnRarrow $2] cs) $1 (reverse (unLoc $3)))) } + {% acs (\cs -> sLL (reLocN $1) $> (InjectivityAnn (EpAnn (glNR $1) [mu AnnRarrow $2] cs) $1 (reverse (unLoc $3)))) } inj_varids :: { Located [LocatedN RdrName] } : inj_varids tyvarid { sLL $1 (reLocN $>) ($2 : unLoc $1) } @@ -1419,7 +1419,7 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs } ; tvbs <- fromSpecTyVarBndrs $2 ; let loc = comb2A $1 $> ; cs <- getCommentsFor loc - ; mkTyFamInstEqn loc (mkHsOuterExplicit (ApiAnn (glR $1) (mu AnnForall $1, mj AnnDot $3) cs) tvbs) $4 $6 [mj AnnEqual $5] }} + ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glR $1) (mu AnnForall $1, mj AnnDot $3) cs) tvbs) $4 $6 [mj AnnEqual $5] }} | type '=' ktype {% mkTyFamInstEqn (comb2A (reLoc $1) $>) mkHsOuterImplicit $1 $3 (mj AnnEqual $2:[]) } -- Note the use of type for the head; this allows @@ -1545,13 +1545,13 @@ datafam_inst_hdr :: { Located (Maybe (LHsContext GhcPs), HsOuterFamEqnTyVarBndrs >>= \tvbs -> (acs (\cs -> (sLL $1 (reLoc $>) (Just ( addTrailingDarrowC $4 $5 cs) - , mkHsOuterExplicit (ApiAnn (glR $1) (mu AnnForall $1, mj AnnDot $3) noCom) tvbs, $6)))) + , mkHsOuterExplicit (EpAnn (glR $1) (mu AnnForall $1, mj AnnDot $3) noCom) tvbs, $6)))) } | 'forall' tv_bndrs '.' type {% do { hintExplicitForall $1 ; tvbs <- fromSpecTyVarBndrs $2 ; let loc = comb2 $1 (reLoc $>) ; cs <- getCommentsFor loc - ; return (sL loc (Nothing, mkHsOuterExplicit (ApiAnn (glR $1) (mu AnnForall $1, mj AnnDot $3) cs) tvbs, $4)) + ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glR $1) (mu AnnForall $1, mj AnnDot $3) cs) tvbs, $4)) } } | context '=>' type {% acs (\cs -> (sLLAA $1 $>(Just (addTrailingDarrowC $1 $2 cs), mkHsOuterImplicit, $3))) } | type { sL1A $1 (Nothing, mkHsOuterImplicit, $1) } @@ -1578,7 +1578,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs } {% do { let { err = text "in the stand-alone deriving instance" <> colon <+> quotes (ppr $5) } ; acsA (\cs -> sLL $1 (reLoc $>) - (DerivDecl (ApiAnn (glR $1) [mj AnnDeriving $1, mj AnnInstance $3] cs) (mkHsWildCardBndrs $5) $2 $4)) }} + (DerivDecl (EpAnn (glR $1) [mj AnnDeriving $1, mj AnnInstance $3] cs) (mkHsWildCardBndrs $5) $2 $4)) }} ----------------------------------------------------------------------------- -- Role annotations @@ -1610,19 +1610,19 @@ pattern_synonym_decl :: { LHsDecl GhcPs } {% let (name, args, as ) = $2 in acsA (\cs -> sLL $1 (reLoc $>) . ValD noExtField $ mkPatSynBind name args $4 ImplicitBidirectional - (ApiAnn (glR $1) (as ++ [mj AnnPattern $1, mj AnnEqual $3]) cs)) } + (EpAnn (glR $1) (as ++ [mj AnnPattern $1, mj AnnEqual $3]) cs)) } | 'pattern' pattern_synonym_lhs '<-' pat {% let (name, args, as) = $2 in acsA (\cs -> sLL $1 (reLoc $>) . ValD noExtField $ mkPatSynBind name args $4 Unidirectional - (ApiAnn (glR $1) (as ++ [mj AnnPattern $1,mu AnnLarrow $3]) cs)) } + (EpAnn (glR $1) (as ++ [mj AnnPattern $1,mu AnnLarrow $3]) cs)) } | 'pattern' pattern_synonym_lhs '<-' pat where_decls {% do { let (name, args, as) = $2 ; mg <- mkPatSynMatchGroup name $5 ; acsA (\cs -> sLL $1 (reLoc $>) . ValD noExtField $ mkPatSynBind name args $4 (ExplicitBidirectional mg) - (ApiAnn (glR $1) (as ++ [mj AnnPattern $1,mu AnnLarrow $3]) cs)) + (EpAnn (glR $1) (as ++ [mj AnnPattern $1,mu AnnLarrow $3]) cs)) }} pattern_synonym_lhs :: { (LocatedN RdrName, HsPatSynDetails GhcPs, [AddEpAnn]) } @@ -1648,7 +1648,7 @@ where_decls :: { LocatedL (OrdList (LHsDecl GhcPs)) } pattern_synonym_sig :: { LSig GhcPs } : 'pattern' con_list '::' sigtype {% acsA (\cs -> sLL $1 (reLoc $>) - $ PatSynSig (ApiAnn (glR $1) (AnnSig (mu AnnDcolon $3) [mj AnnPattern $1]) cs) + $ PatSynSig (EpAnn (glR $1) (AnnSig (mu AnnDcolon $3) [mj AnnPattern $1]) cs) (unLoc $2) $4) } qvarcon :: { LocatedN RdrName } @@ -1670,7 +1670,7 @@ decl_cls : at_decl_cls { $1 } do { v <- checkValSigLhs $2 ; let err = text "in default signature" <> colon <+> quotes (ppr $2) - ; acsA (\cs -> sLL $1 (reLoc $>) $ SigD noExtField $ ClassOpSig (ApiAnn (glR $1) (AnnSig (mu AnnDcolon $3) [mj AnnDefault $1]) cs) True [v] $4) }} + ; acsA (\cs -> sLL $1 (reLoc $>) $ SigD noExtField $ ClassOpSig (EpAnn (glR $1) (AnnSig (mu AnnDcolon $3) [mj AnnDefault $1]) cs) True [v] $4) }} decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) } -- Reversed : decls_cls ';' decl_cls {% if isNilOL (snd $ unLoc $1) @@ -1793,14 +1793,14 @@ binds :: { Located (HsLocalBinds GhcPs) } : decllist {% do { val_binds <- cvBindGroup (unLoc $ snd $ unLoc $1) ; cs <- getCommentsFor (gl $1) ; if (isNilOL (unLoc $ snd $ unLoc $1)) - then return (sL1 $1 $ HsValBinds (ApiAnn (glR $1) (AnnList (Just $ glR $1) Nothing Nothing [] []) cs) val_binds) - else return (sL1 $1 $ HsValBinds (ApiAnn (glR $1) (fst $ unLoc $1) cs) val_binds) } } + then return (sL1 $1 $ HsValBinds (EpAnn (glR $1) (AnnList (Just $ glR $1) Nothing Nothing [] []) cs) val_binds) + else return (sL1 $1 $ HsValBinds (EpAnn (glR $1) (fst $ unLoc $1) cs) val_binds) } } | '{' dbinds '}' {% acs (\cs -> (L (comb3 $1 $2 $3) - $ HsIPBinds (ApiAnn (glR $1) (AnnList (Just$ glR $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) } + $ HsIPBinds (EpAnn (glR $1) (AnnList (Just$ glR $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) } | vocurly dbinds close {% acs (\cs -> (L (gl $2) - $ HsIPBinds (ApiAnn (glR $1) (AnnList (Just $ glR $2) Nothing Nothing [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) } + $ HsIPBinds (EpAnn (glR $1) (AnnList (Just $ glR $2) Nothing Nothing [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) } wherebinds :: { Maybe (Located (HsLocalBinds GhcPs)) } @@ -1831,7 +1831,7 @@ rule :: { LRuleDecl GhcPs } {%runPV (unECP $4) >>= \ $4 -> runPV (unECP $6) >>= \ $6 -> acsA (\cs -> (sLLlA $1 $> $ HsRule - { rd_ext = ApiAnn (glR $1) ((fstOf3 $3) (mj AnnEqual $5 : (fst $2))) cs + { rd_ext = EpAnn (glR $1) ((fstOf3 $3) (mj AnnEqual $5 : (fst $2))) cs , rd_name = L (gl $1) (getSTRINGs $1, getSTRING $1) , rd_act = (snd $2) `orElse` AlwaysActive , rd_tyvs = sndOf3 $3, rd_tmvs = thdOf3 $3 @@ -1891,7 +1891,7 @@ rule_vars :: { [LRuleTyTmVar] } rule_var :: { LRuleTyTmVar } : varid { sL1N $1 (RuleTyTmVar noAnn $1 Nothing) } - | '(' varid '::' ctype ')' {% acs (\cs -> sLL $1 $> (RuleTyTmVar (ApiAnn (glR $1) [mop $1,mu AnnDcolon $3,mcp $5] cs) $2 (Just $4))) } + | '(' varid '::' ctype ')' {% acs (\cs -> sLL $1 $> (RuleTyTmVar (EpAnn (glR $1) [mop $1,mu AnnDcolon $3,mcp $5] cs) $2 (Just $4))) } {- Note [Parsing explicit foralls in Rules] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1939,7 +1939,7 @@ warnings :: { OrdList (LWarnDecl GhcPs) } warning :: { OrdList (LWarnDecl GhcPs) } : namelist strings {% fmap unitOL $ acsA (\cs -> sLL $1 $> - (Warning (ApiAnn (glR $1) (fst $ unLoc $2) cs) (unLoc $1) + (Warning (EpAnn (glR $1) (fst $ unLoc $2) cs) (unLoc $1) (WarningTxt (noLoc NoSourceText) $ snd $ unLoc $2))) } deprecations :: { OrdList (LWarnDecl GhcPs) } @@ -1962,7 +1962,7 @@ deprecations :: { OrdList (LWarnDecl GhcPs) } -- SUP: TEMPORARY HACK, not checking for `module Foo' deprecation :: { OrdList (LWarnDecl GhcPs) } : namelist strings - {% fmap unitOL $ acsA (\cs -> sLL $1 $> $ (Warning (ApiAnn (glR $1) (fst $ unLoc $2) cs) (unLoc $1) + {% fmap unitOL $ acsA (\cs -> sLL $1 $> $ (Warning (EpAnn (glR $1) (fst $ unLoc $2) cs) (unLoc $1) (DeprecatedTxt (noLoc NoSourceText) $ snd $ unLoc $2))) } strings :: { Located ([AddEpAnn],[Located StringLiteral]) } @@ -1988,26 +1988,26 @@ stringlist :: { Located (OrdList (Located StringLiteral)) } annotation :: { LHsDecl GhcPs } : '{-# ANN' name_var aexp '#-}' {% runPV (unECP $3) >>= \ $3 -> acsA (\cs -> sLL $1 $> (AnnD noExtField $ HsAnnotation - (ApiAnn (glR $1) (AnnPragma (mo $1) (mc $4) []) cs) + (EpAnn (glR $1) (AnnPragma (mo $1) (mc $4) []) cs) (getANN_PRAGs $1) (ValueAnnProvenance $2) $3)) } | '{-# ANN' 'type' otycon aexp '#-}' {% runPV (unECP $4) >>= \ $4 -> acsA (\cs -> sLL $1 $> (AnnD noExtField $ HsAnnotation - (ApiAnn (glR $1) (AnnPragma (mo $1) (mc $5) [mj AnnType $2]) cs) + (EpAnn (glR $1) (AnnPragma (mo $1) (mc $5) [mj AnnType $2]) cs) (getANN_PRAGs $1) (TypeAnnProvenance $3) $4)) } | '{-# ANN' 'module' aexp '#-}' {% runPV (unECP $3) >>= \ $3 -> acsA (\cs -> sLL $1 $> (AnnD noExtField $ HsAnnotation - (ApiAnn (glR $1) (AnnPragma (mo $1) (mc $4) [mj AnnModule $2]) cs) + (EpAnn (glR $1) (AnnPragma (mo $1) (mc $4) [mj AnnModule $2]) cs) (getANN_PRAGs $1) ModuleAnnProvenance $3)) } ----------------------------------------------------------------------------- -- Foreign import and export declarations -fdecl :: { Located ([AddEpAnn],ApiAnn -> HsDecl GhcPs) } +fdecl :: { Located ([AddEpAnn],EpAnn -> HsDecl GhcPs) } fdecl : 'import' callconv safety fspec {% mkImport $2 $3 (snd $ unLoc $4) >>= \i -> return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $4),i)) } @@ -2057,7 +2057,7 @@ opt_tyconsig :: { ([AddEpAnn], Maybe (LocatedN RdrName)) } sigktype :: { LHsSigType GhcPs } : sigtype { $1 } | ctype '::' kind {% acsA (\cs -> sLLAA $1 $> $ mkHsImplicitSigType $ - sLLa (reLoc $1) (reLoc $>) $ HsKindSig (ApiAnn (glAR $1) [mu AnnDcolon $2] cs) $1 $3) } + sLLa (reLoc $1) (reLoc $>) $ HsKindSig (EpAnn (glAR $1) [mu AnnDcolon $2] cs) $1 $3) } -- Like ctype, but for types that obey the forall-or-nothing rule. -- See Note [forall-or-nothing rule] in GHC.Hs.Type. To avoid duplicating the @@ -2088,16 +2088,16 @@ unpackedness :: { Located UnpackednessPragma } forall_telescope :: { Located (HsForAllTelescope GhcPs) } : 'forall' tv_bndrs '.' {% do { hintExplicitForall $1 ; acs (\cs -> (sLL $1 $> $ - mkHsForAllInvisTele (ApiAnn (glR $1) (mu AnnForall $1,mu AnnDot $3) cs) $2 )) }} + mkHsForAllInvisTele (EpAnn (glR $1) (mu AnnForall $1,mu AnnDot $3) cs) $2 )) }} | 'forall' tv_bndrs '->' {% do { hintExplicitForall $1 ; req_tvbs <- fromSpecTyVarBndrs $2 ; acs (\cs -> (sLL $1 $> $ - mkHsForAllVisTele (ApiAnn (glR $1) (mu AnnForall $1,mu AnnRarrow $3) cs) req_tvbs )) }} + mkHsForAllVisTele (EpAnn (glR $1) (mu AnnForall $1,mu AnnRarrow $3) cs) req_tvbs )) }} -- A ktype is a ctype, possibly with a kind annotation ktype :: { LHsType GhcPs } : ctype { $1 } - | ctype '::' kind {% acsA (\cs -> sLLAA $1 $> $ HsKindSig (ApiAnn (glAR $1) [mu AnnDcolon $2] cs) $1 $3) } + | ctype '::' kind {% acsA (\cs -> sLLAA $1 $> $ HsKindSig (EpAnn (glAR $1) [mu AnnDcolon $2] cs) $1 $3) } -- A ctype is a for-all type ctype :: { LHsType GhcPs } @@ -2110,7 +2110,7 @@ ctype :: { LHsType GhcPs } , hst_xqual = NoExtField , hst_body = $3 })) } - | ipvar '::' type {% acsA (\cs -> sLL $1 (reLoc $>) (HsIParamTy (ApiAnn (glR $1) [mu AnnDcolon $2] cs) $1 $3)) } + | ipvar '::' type {% acsA (\cs -> sLL $1 (reLoc $>) (HsIParamTy (EpAnn (glR $1) [mu AnnDcolon $2] cs) $1 $3)) } | type { $1 } ---------------------- @@ -2143,16 +2143,16 @@ type :: { LHsType GhcPs } -- See Note [%shift: type -> btype] : btype %shift { $1 } | btype '->' ctype {% acsA (\cs -> sLL (reLoc $1) (reLoc $>) - $ HsFunTy (ApiAnn (glAR $1) (mau $2) cs) (HsUnrestrictedArrow (toUnicode $2)) $1 $3) } + $ HsFunTy (EpAnn (glAR $1) (mau $2) cs) (HsUnrestrictedArrow (toUnicode $2)) $1 $3) } | btype mult '->' ctype {% hintLinear (getLoc $2) >> let arr = (unLoc $2) (toUnicode $3) in acsA (\cs -> sLL (reLoc $1) (reLoc $>) - $ HsFunTy (ApiAnn (glAR $1) (mau $3) cs) arr $1 $4) } + $ HsFunTy (EpAnn (glAR $1) (mau $3) cs) arr $1 $4) } | btype '->.' ctype {% hintLinear (getLoc $2) >> acsA (\cs -> sLL (reLoc $1) (reLoc $>) - $ HsFunTy (ApiAnn (glAR $1) (mau $2) cs) (HsLinearArrow UnicodeSyntax Nothing) $1 $3) } + $ HsFunTy (EpAnn (glAR $1) (mau $2) cs) (HsLinearArrow UnicodeSyntax Nothing) $1 $3) } -- [mu AnnLollyU $2] } mult :: { Located (IsUnicodeSyntax -> HsArrow GhcPs) } @@ -2192,45 +2192,45 @@ tyop :: { LocatedN RdrName } (NameAnnQuote (glAA $1) (gl $2) []) } atype :: { LHsType GhcPs } - : ntgtycon {% acsa (\cs -> sL1a (reLocN $1) (HsTyVar (ApiAnn (glNR $1) [] cs) NotPromoted $1)) } -- Not including unit tuples + : ntgtycon {% acsa (\cs -> sL1a (reLocN $1) (HsTyVar (EpAnn (glNR $1) [] cs) NotPromoted $1)) } -- Not including unit tuples -- See Note [%shift: atype -> tyvar] - | tyvar %shift {% acsa (\cs -> sL1a (reLocN $1) (HsTyVar (ApiAnn (glNR $1) [] cs) NotPromoted $1)) } -- (See Note [Unit tuples]) + | tyvar %shift {% acsa (\cs -> sL1a (reLocN $1) (HsTyVar (EpAnn (glNR $1) [] cs) NotPromoted $1)) } -- (See Note [Unit tuples]) | '*' {% do { warnStarIsType (getLoc $1) ; return $ reLocA $ sL1 $1 (HsStarTy noExtField (isUnicode $1)) } } -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer - | PREFIX_TILDE atype {% acsA (\cs -> sLLlA $1 $> (mkBangTy (ApiAnn (glR $1) [mj AnnTilde $1] cs) SrcLazy $2)) } - | PREFIX_BANG atype {% acsA (\cs -> sLLlA $1 $> (mkBangTy (ApiAnn (glR $1) [mj AnnBang $1] cs) SrcStrict $2)) } + | PREFIX_TILDE atype {% acsA (\cs -> sLLlA $1 $> (mkBangTy (EpAnn (glR $1) [mj AnnTilde $1] cs) SrcLazy $2)) } + | PREFIX_BANG atype {% acsA (\cs -> sLLlA $1 $> (mkBangTy (EpAnn (glR $1) [mj AnnBang $1] cs) SrcStrict $2)) } - | '{' fielddecls '}' {% do { decls <- acsA (\cs -> (sLL $1 $> $ HsRecTy (ApiAnn (glR $1) (AnnList (Just $ listAsAnchor $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) $2)) + | '{' fielddecls '}' {% do { decls <- acsA (\cs -> (sLL $1 $> $ HsRecTy (EpAnn (glR $1) (AnnList (Just $ listAsAnchor $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) $2)) ; checkRecordSyntax decls }} -- Constructor sigs only - | '(' ')' {% acsA (\cs -> sLL $1 $> $ HsTupleTy (ApiAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $2)) cs) + | '(' ')' {% acsA (\cs -> sLL $1 $> $ HsTupleTy (EpAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $2)) cs) HsBoxedOrConstraintTuple []) } | '(' ktype ',' comma_types1 ')' {% do { h <- addTrailingCommaA $2 (gl $3) - ; acsA (\cs -> sLL $1 $> $ HsTupleTy (ApiAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $5)) cs) + ; acsA (\cs -> sLL $1 $> $ HsTupleTy (EpAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $5)) cs) HsBoxedOrConstraintTuple (h : $4)) }} - | '(#' '#)' {% acsA (\cs -> sLL $1 $> $ HsTupleTy (ApiAnn (glR $1) (AnnParen AnnParensHash (glAA $1) (glAA $2)) cs) HsUnboxedTuple []) } - | '(#' comma_types1 '#)' {% acsA (\cs -> sLL $1 $> $ HsTupleTy (ApiAnn (glR $1) (AnnParen AnnParensHash (glAA $1) (glAA $3)) cs) HsUnboxedTuple $2) } - | '(#' bar_types2 '#)' {% acsA (\cs -> sLL $1 $> $ HsSumTy (ApiAnn (glR $1) (AnnParen AnnParensHash (glAA $1) (glAA $3)) cs) $2) } - | '[' ktype ']' {% acsA (\cs -> sLL $1 $> $ HsListTy (ApiAnn (glR $1) (AnnParen AnnParensSquare (glAA $1) (glAA $3)) cs) $2) } - | '(' ktype ')' {% acsA (\cs -> sLL $1 $> $ HsParTy (ApiAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $3)) cs) $2) } + | '(#' '#)' {% acsA (\cs -> sLL $1 $> $ HsTupleTy (EpAnn (glR $1) (AnnParen AnnParensHash (glAA $1) (glAA $2)) cs) HsUnboxedTuple []) } + | '(#' comma_types1 '#)' {% acsA (\cs -> sLL $1 $> $ HsTupleTy (EpAnn (glR $1) (AnnParen AnnParensHash (glAA $1) (glAA $3)) cs) HsUnboxedTuple $2) } + | '(#' bar_types2 '#)' {% acsA (\cs -> sLL $1 $> $ HsSumTy (EpAnn (glR $1) (AnnParen AnnParensHash (glAA $1) (glAA $3)) cs) $2) } + | '[' ktype ']' {% acsA (\cs -> sLL $1 $> $ HsListTy (EpAnn (glR $1) (AnnParen AnnParensSquare (glAA $1) (glAA $3)) cs) $2) } + | '(' ktype ')' {% acsA (\cs -> sLL $1 $> $ HsParTy (EpAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $3)) cs) $2) } | quasiquote { mapLocA (HsSpliceTy noExtField) $1 } | splice_untyped { mapLocA (HsSpliceTy noExtField) $1 } -- see Note [Promotion] for the followings - | SIMPLEQUOTE qcon_nowiredlist {% acsA (\cs -> sLL $1 (reLocN $>) $ HsTyVar (ApiAnn (glR $1) [mj AnnSimpleQuote $1,mjN AnnName $2] cs) IsPromoted $2) } + | SIMPLEQUOTE qcon_nowiredlist {% acsA (\cs -> sLL $1 (reLocN $>) $ HsTyVar (EpAnn (glR $1) [mj AnnSimpleQuote $1,mjN AnnName $2] cs) IsPromoted $2) } | SIMPLEQUOTE '(' ktype ',' comma_types1 ')' {% do { h <- addTrailingCommaA $3 (gl $4) - ; acsA (\cs -> sLL $1 $> $ HsExplicitTupleTy (ApiAnn (glR $1) [mj AnnSimpleQuote $1,mop $2,mcp $6] cs) (h : $5)) }} - | SIMPLEQUOTE '[' comma_types0 ']' {% acsA (\cs -> sLL $1 $> $ HsExplicitListTy (ApiAnn (glR $1) [mj AnnSimpleQuote $1,mos $2,mcs $4] cs) IsPromoted $3) } - | SIMPLEQUOTE var {% acsA (\cs -> sLL $1 (reLocN $>) $ HsTyVar (ApiAnn (glR $1) [mj AnnSimpleQuote $1,mjN AnnName $2] cs) IsPromoted $2) } + ; acsA (\cs -> sLL $1 $> $ HsExplicitTupleTy (EpAnn (glR $1) [mj AnnSimpleQuote $1,mop $2,mcp $6] cs) (h : $5)) }} + | SIMPLEQUOTE '[' comma_types0 ']' {% acsA (\cs -> sLL $1 $> $ HsExplicitListTy (EpAnn (glR $1) [mj AnnSimpleQuote $1,mos $2,mcs $4] cs) IsPromoted $3) } + | SIMPLEQUOTE var {% acsA (\cs -> sLL $1 (reLocN $>) $ HsTyVar (EpAnn (glR $1) [mj AnnSimpleQuote $1,mjN AnnName $2] cs) IsPromoted $2) } -- Two or more [ty, ty, ty] must be a promoted list type, just as -- if you had written '[ty, ty, ty] -- (One means a list type, zero means the list type constructor, -- so you have to quote those.) | '[' ktype ',' comma_types1 ']' {% do { h <- addTrailingCommaA $2 (gl $3) - ; acsA (\cs -> sLL $1 $> $ HsExplicitListTy (ApiAnn (glR $1) [mos $1,mcs $5] cs) NotPromoted (h:$4)) }} + ; acsA (\cs -> sLL $1 $> $ HsExplicitListTy (EpAnn (glR $1) [mos $1,mcs $5] cs) NotPromoted (h:$4)) }} | INTEGER { reLocA $ sLL $1 $> $ HsTyLit noExtField $ HsNumTy (getINTEGERs $1) (il_value (getINTEGER $1)) } | CHAR { reLocA $ sLL $1 $> $ HsTyLit noExtField $ HsCharTy (getCHARs $1) @@ -2272,12 +2272,12 @@ tv_bndrs :: { [LHsTyVarBndr Specificity GhcPs] } tv_bndr :: { LHsTyVarBndr Specificity GhcPs } : tv_bndr_no_braces { $1 } - | '{' tyvar '}' {% acsA (\cs -> sLL $1 $> (UserTyVar (ApiAnn (glR $1) [mop $1, mcp $3] cs) InferredSpec $2)) } - | '{' tyvar '::' kind '}' {% acsA (\cs -> sLL $1 $> (KindedTyVar (ApiAnn (glR $1) [mop $1,mu AnnDcolon $3 ,mcp $5] cs) InferredSpec $2 $4)) } + | '{' tyvar '}' {% acsA (\cs -> sLL $1 $> (UserTyVar (EpAnn (glR $1) [mop $1, mcp $3] cs) InferredSpec $2)) } + | '{' tyvar '::' kind '}' {% acsA (\cs -> sLL $1 $> (KindedTyVar (EpAnn (glR $1) [mop $1,mu AnnDcolon $3 ,mcp $5] cs) InferredSpec $2 $4)) } tv_bndr_no_braces :: { LHsTyVarBndr Specificity GhcPs } - : tyvar {% acsA (\cs -> (sL1 (reLocN $1) (UserTyVar (ApiAnn (glNR $1) [] cs) SpecifiedSpec $1))) } - | '(' tyvar '::' kind ')' {% acsA (\cs -> (sLL $1 $> (KindedTyVar (ApiAnn (glR $1) [mop $1,mu AnnDcolon $3 ,mcp $5] cs) SpecifiedSpec $2 $4))) } + : tyvar {% acsA (\cs -> (sL1 (reLocN $1) (UserTyVar (EpAnn (glNR $1) [] cs) SpecifiedSpec $1))) } + | '(' tyvar '::' kind ')' {% acsA (\cs -> (sLL $1 $> (KindedTyVar (EpAnn (glR $1) [mop $1,mu AnnDcolon $3 ,mcp $5] cs) SpecifiedSpec $2 $4))) } fds :: { Located ([AddEpAnn],[LHsFunDep GhcPs]) } : {- empty -} { noLoc ([],[]) } @@ -2293,7 +2293,7 @@ fds1 :: { Located [LHsFunDep GhcPs] } fd :: { LHsFunDep GhcPs } : varids0 '->' varids0 {% acsA (\cs -> L (comb3 $1 $2 $3) - (FunDep (ApiAnn (glR $1) [mu AnnRarrow $2] cs) + (FunDep (EpAnn (glR $1) [mu AnnRarrow $2] cs) (reverse (unLoc $1)) (reverse (unLoc $3)))) } @@ -2393,7 +2393,7 @@ constr :: { LConDecl GhcPs } : forall context '=>' constr_stuff {% acsA (\cs -> let (con,details) = unLoc $4 in (L (comb4 $1 (reLoc $2) $3 $4) (mkConDeclH98 - (ApiAnn (spanAsAnchor (comb4 $1 (reLoc $2) $3 $4)) + (EpAnn (spanAsAnchor (comb4 $1 (reLoc $2) $3 $4)) (mu AnnDarrow $3:(fst $ unLoc $1)) cs) con (snd $ unLoc $1) @@ -2401,7 +2401,7 @@ constr :: { LConDecl GhcPs } details))) } | forall constr_stuff {% acsA (\cs -> let (con,details) = unLoc $2 in - (L (comb2 $1 $2) (mkConDeclH98 (ApiAnn (spanAsAnchor (comb2 $1 $2)) (fst $ unLoc $1) cs) + (L (comb2 $1 $2) (mkConDeclH98 (EpAnn (spanAsAnchor (comb2 $1 $2)) (fst $ unLoc $1) cs) con (snd $ unLoc $1) Nothing -- No context @@ -2430,7 +2430,7 @@ fielddecl :: { LConDeclField GhcPs } -- A list because of f,g :: Int : sig_vars '::' ctype {% acsA (\cs -> L (comb2 $1 (reLoc $3)) - (ConDeclField (ApiAnn (glR $1) [mu AnnDcolon $2] cs) + (ConDeclField (EpAnn (glR $1) [mu AnnDcolon $2] cs) (reverse (map (\ln@(L l n) -> L (locA l) $ FieldOcc noExtField ln) (unLoc $1))) $3 Nothing))} -- Reversed! @@ -2448,15 +2448,15 @@ derivings :: { Located (HsDeriving GhcPs) } deriving :: { LHsDerivingClause GhcPs } : 'deriving' deriv_clause_types {% let { full_loc = comb2A $1 $> } - in acs (\cs -> L full_loc $ HsDerivingClause (ApiAnn (glR $1) [mj AnnDeriving $1] cs) Nothing $2) } + in acs (\cs -> L full_loc $ HsDerivingClause (EpAnn (glR $1) [mj AnnDeriving $1] cs) Nothing $2) } | 'deriving' deriv_strategy_no_via deriv_clause_types {% let { full_loc = comb2A $1 $> } - in acs (\cs -> L full_loc $ HsDerivingClause (ApiAnn (glR $1) [mj AnnDeriving $1] cs) (Just $2) $3) } + in acs (\cs -> L full_loc $ HsDerivingClause (EpAnn (glR $1) [mj AnnDeriving $1] cs) (Just $2) $3) } | 'deriving' deriv_clause_types deriv_strategy_via {% let { full_loc = comb2 $1 $> } - in acs (\cs -> L full_loc $ HsDerivingClause (ApiAnn (glR $1) [mj AnnDeriving $1] cs) (Just $3) $2) } + in acs (\cs -> L full_loc $ HsDerivingClause (EpAnn (glR $1) [mj AnnDeriving $1] cs) (Just $3) $2) } deriv_clause_types :: { LDerivClauseTys GhcPs } : qtycon { let { tc = sL1 (reLocL $1) $ mkHsImplicitSigType $ @@ -2517,7 +2517,7 @@ rhs :: { Located (GRHSs GhcPs (LHsExpr GhcPs)) } : '=' exp wherebinds {% runPV (unECP $2) >>= \ $2 -> do { let loc = (comb3 $1 (reLoc $2) (adaptWhereBinds $3)) ; acs (\cs -> - sL loc (GRHSs NoExtField (unguardedRHS (ApiAnn (anc $ rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) cs) loc $2) + sL loc (GRHSs NoExtField (unguardedRHS (EpAnn (anc $ rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) cs) loc $2) (unLoc $ (adaptWhereBinds $3)))) } } | gdrhs wherebinds { sL (comb2 $1 (adaptWhereBinds $>)) (GRHSs noExtField (reverse (unLoc $1)) (unLoc $ (adaptWhereBinds $2))) } @@ -2528,7 +2528,7 @@ gdrhs :: { Located [LGRHS GhcPs (LHsExpr GhcPs)] } gdrh :: { LGRHS GhcPs (LHsExpr GhcPs) } : '|' guardquals '=' exp {% runPV (unECP $4) >>= \ $4 -> - acs (\cs -> sL (comb2A $1 $>) $ GRHS (ApiAnn (glR $1) (GrhsAnn (Just $ glAA $1) (mj AnnEqual $3)) cs) (unLoc $2) $4) } + acs (\cs -> sL (comb2A $1 $>) $ GRHS (EpAnn (glR $1) (GrhsAnn (Just $ glAA $1) (mj AnnEqual $3)) cs) (unLoc $2) $4) } sigdecl :: { LHsDecl GhcPs } : @@ -2537,18 +2537,18 @@ sigdecl :: { LHsDecl GhcPs } {% do { $1 <- runPV (unECP $1) ; v <- checkValSigLhs $1 ; acsA (\cs -> (sLLAl $1 (reLoc $>) $ SigD noExtField $ - TypeSig (ApiAnn (glAR $1) (AnnSig (mu AnnDcolon $2) []) cs) [v] (mkHsWildCardBndrs $3)))} } + TypeSig (EpAnn (glAR $1) (AnnSig (mu AnnDcolon $2) []) cs) [v] (mkHsWildCardBndrs $3)))} } | var ',' sig_vars '::' sigtype {% do { v <- addTrailingCommaN $1 (gl $2) - ; let sig cs = TypeSig (ApiAnn (glNR $1) (AnnSig (mu AnnDcolon $4) []) cs) (v : reverse (unLoc $3)) + ; let sig cs = TypeSig (EpAnn (glNR $1) (AnnSig (mu AnnDcolon $4) []) cs) (v : reverse (unLoc $3)) (mkHsWildCardBndrs $5) ; acsA (\cs -> sLL (reLocN $1) (reLoc $>) $ SigD noExtField (sig cs) ) }} | infix prec ops {% checkPrecP $2 $3 >> acsA (\cs -> sLL $1 $> $ SigD noExtField - (FixSig (ApiAnn (glR $1) [mj AnnInfix $1,mj AnnVal $2] cs) (FixitySig noExtField (fromOL $ unLoc $3) + (FixSig (EpAnn (glR $1) [mj AnnInfix $1,mj AnnVal $2] cs) (FixitySig noExtField (fromOL $ unLoc $3) (Fixity (fst $ unLoc $2) (snd $ unLoc $2) (unLoc $1))))) } | pattern_synonym_sig { sL1 $1 . SigD noExtField . unLoc $ $1 } @@ -2557,40 +2557,40 @@ sigdecl :: { LHsDecl GhcPs } {% let (dcolon, tc) = $3 in acsA (\cs -> sLL $1 $> - (SigD noExtField (CompleteMatchSig (ApiAnn (glR $1) ([ mo $1 ] ++ dcolon ++ [mc $4]) cs) (getCOMPLETE_PRAGs $1) $2 tc))) } + (SigD noExtField (CompleteMatchSig (EpAnn (glR $1) ([ mo $1 ] ++ dcolon ++ [mc $4]) cs) (getCOMPLETE_PRAGs $1) $2 tc))) } -- This rule is for both INLINE and INLINABLE pragmas | '{-# INLINE' activation qvarcon '#-}' - {% acsA (\cs -> (sLL $1 $> $ SigD noExtField (InlineSig (ApiAnn (glR $1) ((mo $1:fst $2) ++ [mc $4]) cs) $3 + {% acsA (\cs -> (sLL $1 $> $ SigD noExtField (InlineSig (EpAnn (glR $1) ((mo $1:fst $2) ++ [mc $4]) cs) $3 (mkInlinePragma (getINLINE_PRAGs $1) (getINLINE $1) (snd $2))))) } | '{-# SCC' qvar '#-}' - {% acsA (\cs -> sLL $1 $> (SigD noExtField (SCCFunSig (ApiAnn (glR $1) [mo $1, mc $3] cs) (getSCC_PRAGs $1) $2 Nothing))) } + {% acsA (\cs -> sLL $1 $> (SigD noExtField (SCCFunSig (EpAnn (glR $1) [mo $1, mc $3] cs) (getSCC_PRAGs $1) $2 Nothing))) } | '{-# SCC' qvar STRING '#-}' {% do { scc <- getSCC $3 ; let str_lit = StringLiteral (getSTRINGs $3) scc Nothing - ; acsA (\cs -> sLL $1 $> (SigD noExtField (SCCFunSig (ApiAnn (glR $1) [mo $1, mc $4] cs) (getSCC_PRAGs $1) $2 (Just ( sL1 $3 str_lit))))) }} + ; acsA (\cs -> sLL $1 $> (SigD noExtField (SCCFunSig (EpAnn (glR $1) [mo $1, mc $4] cs) (getSCC_PRAGs $1) $2 (Just ( sL1 $3 str_lit))))) }} | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' {% acsA (\cs -> let inl_prag = mkInlinePragma (getSPEC_PRAGs $1) (NoUserInlinePrag, FunLike) (snd $2) - in sLL $1 $> $ SigD noExtField (SpecSig (ApiAnn (glR $1) (mo $1:mu AnnDcolon $4:mc $6:(fst $2)) cs) $3 (fromOL $5) inl_prag)) } + in sLL $1 $> $ SigD noExtField (SpecSig (EpAnn (glR $1) (mo $1:mu AnnDcolon $4:mc $6:(fst $2)) cs) $3 (fromOL $5) inl_prag)) } | '{-# SPECIALISE_INLINE' activation qvar '::' sigtypes1 '#-}' - {% acsA (\cs -> sLL $1 $> $ SigD noExtField (SpecSig (ApiAnn (glR $1) (mo $1:mu AnnDcolon $4:mc $6:(fst $2)) cs) $3 (fromOL $5) + {% acsA (\cs -> sLL $1 $> $ SigD noExtField (SpecSig (EpAnn (glR $1) (mo $1:mu AnnDcolon $4:mc $6:(fst $2)) cs) $3 (fromOL $5) (mkInlinePragma (getSPEC_INLINE_PRAGs $1) (getSPEC_INLINE $1) (snd $2)))) } | '{-# SPECIALISE' 'instance' inst_type '#-}' {% acsA (\cs -> sLL $1 $> - $ SigD noExtField (SpecInstSig (ApiAnn (glR $1) [mo $1,mj AnnInstance $2,mc $4] cs) (getSPEC_PRAGs $1) $3)) } + $ SigD noExtField (SpecInstSig (EpAnn (glR $1) [mo $1,mj AnnInstance $2,mc $4] cs) (getSPEC_PRAGs $1) $3)) } -- A minimal complete definition | '{-# MINIMAL' name_boolformula_opt '#-}' - {% acsA (\cs -> sLL $1 $> $ SigD noExtField (MinimalSig (ApiAnn (glR $1) [mo $1,mc $3] cs) (getMINIMAL_PRAGs $1) $2)) } + {% acsA (\cs -> sLL $1 $> $ SigD noExtField (MinimalSig (EpAnn (glR $1) [mo $1,mc $3] cs) (getMINIMAL_PRAGs $1) $2)) } activation :: { ([AddEpAnn],Maybe Activation) } -- See Note [%shift: activation -> {- empty -}] @@ -2627,22 +2627,22 @@ exp :: { ECP } | infixexp '-<' exp {% runPV (unECP $1) >>= \ $1 -> runPV (unECP $3) >>= \ $3 -> fmap ecpFromCmd $ - acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (ApiAnn (glAR $1) (mu Annlarrowtail $2) cs) $1 $3 + acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (EpAnn (glAR $1) (mu Annlarrowtail $2) cs) $1 $3 HsFirstOrderApp True) } | infixexp '>-' exp {% runPV (unECP $1) >>= \ $1 -> runPV (unECP $3) >>= \ $3 -> fmap ecpFromCmd $ - acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (ApiAnn (glAR $1) (mu Annrarrowtail $2) cs) $3 $1 + acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (EpAnn (glAR $1) (mu Annrarrowtail $2) cs) $3 $1 HsFirstOrderApp False) } | infixexp '-<<' exp {% runPV (unECP $1) >>= \ $1 -> runPV (unECP $3) >>= \ $3 -> fmap ecpFromCmd $ - acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (ApiAnn (glAR $1) (mu AnnLarrowtail $2) cs) $1 $3 + acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (EpAnn (glAR $1) (mu AnnLarrowtail $2) cs) $1 $3 HsHigherOrderApp True) } | infixexp '>>-' exp {% runPV (unECP $1) >>= \ $1 -> runPV (unECP $3) >>= \ $3 -> fmap ecpFromCmd $ - acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (ApiAnn (glAR $1) (mu AnnRarrowtail $2) cs) $3 $1 + acsA (\cs -> sLLAA $1 $> $ HsCmdArrApp (EpAnn (glAR $1) (mu AnnRarrowtail $2) cs) $3 $1 HsHigherOrderApp False) } -- See Note [%shift: exp -> infixexp] | infixexp %shift { $1 } @@ -2732,12 +2732,12 @@ prag_e :: { Located (HsPragE GhcPs) } : '{-# SCC' STRING '#-}' {% do { scc <- getSCC $2 ; acs (\cs -> (sLL $1 $> (HsPragSCC - (ApiAnn (glR $1) (AnnPragma (mo $1) (mc $3) [mj AnnValStr $2]) cs) + (EpAnn (glR $1) (AnnPragma (mo $1) (mc $3) [mj AnnValStr $2]) cs) (getSCC_PRAGs $1) (StringLiteral (getSTRINGs $2) scc Nothing))))} } | '{-# SCC' VARID '#-}' {% acs (\cs -> (sLL $1 $> (HsPragSCC - (ApiAnn (glR $1) (AnnPragma (mo $1) (mc $3) [mj AnnVal $2]) cs) + (EpAnn (glR $1) (AnnPragma (mo $1) (mc $3) [mj AnnVal $2]) cs) (getSCC_PRAGs $1) (StringLiteral NoSourceText (getVARID $2) Nothing)))) } @@ -2755,7 +2755,7 @@ fexp :: { ECP } | 'static' aexp {% runPV (unECP $2) >>= \ $2 -> fmap ecpFromExp $ - acsA (\cs -> sLL $1 (reLoc $>) $ HsStatic (ApiAnn (glR $1) [mj AnnStatic $1] cs) $2) } + acsA (\cs -> sLL $1 (reLoc $>) $ HsStatic (EpAnn (glR $1) [mj AnnStatic $1] cs) $2) } | aexp { $1 } @@ -2784,10 +2784,10 @@ aexp :: { ECP } mkHsLamPV (comb2 $1 (reLoc $>)) (\cs -> mkMatchGroup FromSource (reLocA $ sLLlA $1 $> [reLocA $ sLLlA $1 $> - $ Match { m_ext = ApiAnn (glR $1) [mj AnnLam $1] cs + $ Match { m_ext = EpAnn (glR $1) [mj AnnLam $1] cs , m_ctxt = LambdaExpr , m_pats = $2:$3 - , m_grhss = unguardedGRHSs (comb2 $4 (reLoc $5)) $5 (ApiAnn (glR $4) (GrhsAnn Nothing (mu AnnRarrow $4)) noCom) }])) } + , m_grhss = unguardedGRHSs (comb2 $4 (reLoc $5)) $5 (EpAnn (glR $4) (GrhsAnn Nothing (mu AnnRarrow $4)) noCom) }])) } | 'let' binds 'in' exp { ECP $ unECP $4 >>= \ $4 -> mkHsLetPV (comb2A $1 $>) (unLoc $2) $4 @@ -2808,13 +2808,13 @@ aexp :: { ECP } | 'if' ifgdpats {% hintMultiWayIf (getLoc $1) >>= \_ -> fmap ecpFromExp $ - acsA (\cs -> sLL $1 $> $ HsMultiIf (ApiAnn (glR $1) (mj AnnIf $1:(fst $ unLoc $2)) cs) + acsA (\cs -> sLL $1 $> $ HsMultiIf (EpAnn (glR $1) (mj AnnIf $1:(fst $ unLoc $2)) cs) (reverse $ snd $ unLoc $2)) } | 'case' exp 'of' altslist {% runPV (unECP $2) >>= \ ($2 :: LHsExpr GhcPs) -> return $ ECP $ $4 >>= \ $4 -> mkHsCasePV (comb3 $1 $3 (reLoc $4)) $2 $4 - (ApiAnnHsCase (glAA $1) (glAA $3) []) } + (EpAnnHsCase (glAA $1) (glAA $3) []) } -- QualifiedDo. | DO stmtlist {% do hintQualifiedDo $1 @@ -2830,12 +2830,12 @@ aexp :: { ECP } (mkHsDoAnns (MDoExpr $ fmap mkModuleNameFS (getMDO $1)) $2 - (ApiAnn (glR $1) (AnnList (Just $ glAR $2) Nothing Nothing [mj AnnMdo $1] []) cs) )) } + (EpAnn (glR $1) (AnnList (Just $ glAR $2) Nothing Nothing [mj AnnMdo $1] []) cs) )) } | 'proc' aexp '->' exp {% (checkPattern <=< runPV) (unECP $2) >>= \ p -> runPV (unECP $4) >>= \ $4@cmd -> fmap ecpFromExp $ - acsA (\cs -> sLLlA $1 $> $ HsProc (ApiAnn (glR $1) [mj AnnProc $1,mu AnnRarrow $3] cs) p (sLLlA $1 $> $ HsCmdTop noExtField cmd)) } + acsA (\cs -> sLLlA $1 $> $ HsProc (EpAnn (glR $1) [mj AnnProc $1,mu AnnRarrow $3] cs) p (sLLlA $1 $> $ HsCmdTop noExtField cmd)) } | aexp1 { $1 } @@ -2852,8 +2852,8 @@ aexp1 :: { ECP } | aexp1 TIGHT_INFIX_PROJ field {% runPV (unECP $1) >>= \ $1 -> fmap ecpFromExp $ acsa (\cs -> - let fl = sLL $2 $> (HsFieldLabel ((ApiAnn (glR $2) (AnnFieldLabel (Just $ glAA $2)) noCom)) $3) in - mkRdrGetField (noAnnSrcSpan $ comb2 (reLoc $1) $>) $1 fl (ApiAnn (glAR $1) NoApiAnns cs)) } + let fl = sLL $2 $> (HsFieldLabel ((EpAnn (glR $2) (AnnFieldLabel (Just $ glAA $2)) noCom)) $3) in + mkRdrGetField (noAnnSrcSpan $ comb2 (reLoc $1) $>) $1 fl (EpAnn (glAR $1) NoEpAnns cs)) } | aexp2 { $1 } @@ -2886,7 +2886,7 @@ aexp2 :: { ECP } -- This case is only possible when 'OverloadedRecordDotBit' is enabled. | '(' projection ')' { ECP $ - acsA (\cs -> sLL $1 $> $ mkRdrProjection (reverse (unLoc $2)) (ApiAnn (glR $1) (AnnProjection (glAA $1) (glAA $3)) cs)) + acsA (\cs -> sLL $1 $> $ mkRdrProjection (reverse (unLoc $2)) (EpAnn (glR $1) (AnnProjection (glAA $1) (glAA $3)) cs)) >>= ecpFromExp' } @@ -2906,40 +2906,40 @@ aexp2 :: { ECP } | splice_untyped { ECP $ pvA $ mkHsSplicePV $1 } | splice_typed { ecpFromExp $ mapLoc (HsSpliceE noAnn) (reLocA $1) } - | SIMPLEQUOTE qvar {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (ApiAnn (glR $1) [mj AnnSimpleQuote $1] cs) (VarBr noExtField True $2)) } - | SIMPLEQUOTE qcon {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (ApiAnn (glR $1) [mj AnnSimpleQuote $1] cs) (VarBr noExtField True $2)) } - | TH_TY_QUOTE tyvar {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (ApiAnn (glR $1) [mj AnnThTyQuote $1 ] cs) (VarBr noExtField False $2)) } - | TH_TY_QUOTE gtycon {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (ApiAnn (glR $1) [mj AnnThTyQuote $1 ] cs) (VarBr noExtField False $2)) } + | SIMPLEQUOTE qvar {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (EpAnn (glR $1) [mj AnnSimpleQuote $1] cs) (VarBr noExtField True $2)) } + | SIMPLEQUOTE qcon {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (EpAnn (glR $1) [mj AnnSimpleQuote $1] cs) (VarBr noExtField True $2)) } + | TH_TY_QUOTE tyvar {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (EpAnn (glR $1) [mj AnnThTyQuote $1 ] cs) (VarBr noExtField False $2)) } + | TH_TY_QUOTE gtycon {% fmap ecpFromExp $ acsA (\cs -> sLL $1 (reLocN $>) $ HsBracket (EpAnn (glR $1) [mj AnnThTyQuote $1 ] cs) (VarBr noExtField False $2)) } -- See Note [%shift: aexp2 -> TH_TY_QUOTE] | TH_TY_QUOTE %shift {% reportEmptyDoubleQuotes (getLoc $1) } | '[|' exp '|]' {% runPV (unECP $2) >>= \ $2 -> fmap ecpFromExp $ - acsA (\cs -> sLL $1 $> $ HsBracket (ApiAnn (glR $1) (if (hasE $1) then [mj AnnOpenE $1, mu AnnCloseQ $3] + acsA (\cs -> sLL $1 $> $ HsBracket (EpAnn (glR $1) (if (hasE $1) then [mj AnnOpenE $1, mu AnnCloseQ $3] else [mu AnnOpenEQ $1,mu AnnCloseQ $3]) cs) (ExpBr noExtField $2)) } | '[||' exp '||]' {% runPV (unECP $2) >>= \ $2 -> fmap ecpFromExp $ - acsA (\cs -> sLL $1 $> $ HsBracket (ApiAnn (glR $1) (if (hasE $1) then [mj AnnOpenE $1,mc $3] else [mo $1,mc $3]) cs) (TExpBr noExtField $2)) } + acsA (\cs -> sLL $1 $> $ HsBracket (EpAnn (glR $1) (if (hasE $1) then [mj AnnOpenE $1,mc $3] else [mo $1,mc $3]) cs) (TExpBr noExtField $2)) } | '[t|' ktype '|]' {% fmap ecpFromExp $ - acsA (\cs -> sLL $1 $> $ HsBracket (ApiAnn (glR $1) [mo $1,mu AnnCloseQ $3] cs) (TypBr noExtField $2)) } + acsA (\cs -> sLL $1 $> $ HsBracket (EpAnn (glR $1) [mo $1,mu AnnCloseQ $3] cs) (TypBr noExtField $2)) } | '[p|' infixexp '|]' {% (checkPattern <=< runPV) (unECP $2) >>= \p -> fmap ecpFromExp $ - acsA (\cs -> sLL $1 $> $ HsBracket (ApiAnn (glR $1) [mo $1,mu AnnCloseQ $3] cs) (PatBr noExtField p)) } + acsA (\cs -> sLL $1 $> $ HsBracket (EpAnn (glR $1) [mo $1,mu AnnCloseQ $3] cs) (PatBr noExtField p)) } | '[d|' cvtopbody '|]' {% fmap ecpFromExp $ - acsA (\cs -> sLL $1 $> $ HsBracket (ApiAnn (glR $1) (mo $1:mu AnnCloseQ $3:fst $2) cs) (DecBrL noExtField (snd $2))) } + acsA (\cs -> sLL $1 $> $ HsBracket (EpAnn (glR $1) (mo $1:mu AnnCloseQ $3:fst $2) cs) (DecBrL noExtField (snd $2))) } | quasiquote { ECP $ pvA $ mkHsSplicePV $1 } -- arrow notation extension | '(|' aexp cmdargs '|)' {% runPV (unECP $2) >>= \ $2 -> fmap ecpFromCmd $ - acsA (\cs -> sLL $1 $> $ HsCmdArrForm (ApiAnn (glR $1) (AnnList (Just $ glR $1) (Just $ mu AnnOpenB $1) (Just $ mu AnnCloseB $4) [] []) cs) $2 Prefix + acsA (\cs -> sLL $1 $> $ HsCmdArrForm (EpAnn (glR $1) (AnnList (Just $ glR $1) (Just $ mu AnnOpenB $1) (Just $ mu AnnCloseB $4) [] []) cs) $2 Prefix Nothing (reverse $3)) } projection :: { Located [Located (HsFieldLabel GhcPs)] } projection -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer : projection TIGHT_INFIX_PROJ field - {% acs (\cs -> sLL $1 $> ((sLL $2 $> $ HsFieldLabel (ApiAnn (glR $1) (AnnFieldLabel (Just $ glAA $2)) cs) $3) : unLoc $1)) } - | PREFIX_PROJ field {% acs (\cs -> sLL $1 $> [sLL $1 $> $ HsFieldLabel (ApiAnn (glR $1) (AnnFieldLabel (Just $ glAA $1)) cs) $2]) } + {% acs (\cs -> sLL $1 $> ((sLL $2 $> $ HsFieldLabel (EpAnn (glR $1) (AnnFieldLabel (Just $ glAA $2)) cs) $3) : unLoc $1)) } + | PREFIX_PROJ field {% acs (\cs -> sLL $1 $> [sLL $1 $> $ HsFieldLabel (EpAnn (glR $1) (AnnFieldLabel (Just $ glAA $1)) cs) $2]) } splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noAnn) (reLocA $1) } @@ -2948,13 +2948,13 @@ splice_exp :: { LHsExpr GhcPs } splice_untyped :: { Located (HsSplice GhcPs) } -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer : PREFIX_DOLLAR aexp2 {% runPV (unECP $2) >>= \ $2 -> - acs (\cs -> sLLlA $1 $> $ mkUntypedSplice (ApiAnn (glR $1) [mj AnnDollar $1] cs) DollarSplice $2) } + acs (\cs -> sLLlA $1 $> $ mkUntypedSplice (EpAnn (glR $1) [mj AnnDollar $1] cs) DollarSplice $2) } splice_typed :: { Located (HsSplice GhcPs) } -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer : PREFIX_DOLLAR_DOLLAR aexp2 {% runPV (unECP $2) >>= \ $2 -> - acs (\cs -> sLLlA $1 $> $ mkTypedSplice (ApiAnn (glR $1) [mj AnnDollarDollar $1] cs) DollarSplice $2) } + acs (\cs -> sLLlA $1 $> $ mkTypedSplice (EpAnn (glR $1) [mj AnnDollarDollar $1] cs) DollarSplice $2) } cmdargs :: { [LHsCmdTop GhcPs] } : cmdargs acmd { $2 : $1 } @@ -3024,7 +3024,7 @@ tup_exprs :: { forall b. DisambECP b => PV (SumOrTuple b) } ; return (Tuple (Right t : snd $2)) } } | commas tup_tail { $2 >>= \ $2 -> - do { let {cos = map (\ll -> (Left (ApiAnn (anc $ rs ll) (AR $ rs ll) noCom))) (fst $1) } + do { let {cos = map (\ll -> (Left (EpAnn (anc $ rs ll) (AR $ rs ll) noCom))) (fst $1) } ; return (Tuple (cos ++ $2)) } } | texp bars { unECP $1 >>= \ $1 -> return $ @@ -3035,14 +3035,14 @@ tup_exprs :: { forall b. DisambECP b => PV (SumOrTuple b) } (Sum (snd $1 + 1) (snd $1 + snd $3 + 1) $2 (fst $1) (fst $3)) } -- Always starts with commas; always follows an expr -commas_tup_tail :: { forall b. DisambECP b => PV (SrcSpan,[Either (ApiAnn' AnnAnchor) (LocatedA b)]) } +commas_tup_tail :: { forall b. DisambECP b => PV (SrcSpan,[Either (EpAnn' AnnAnchor) (LocatedA b)]) } commas_tup_tail : commas tup_tail { $2 >>= \ $2 -> - do { let {cos = map (\l -> (Left (ApiAnn (anc $ rs l) (AR $ rs l) noCom))) (tail $ fst $1) } + do { let {cos = map (\l -> (Left (EpAnn (anc $ rs l) (AR $ rs l) noCom))) (tail $ fst $1) } ; return ((head $ fst $1, cos ++ $2)) } } -- Always follows a comma -tup_tail :: { forall b. DisambECP b => PV [Either (ApiAnn' AnnAnchor) (LocatedA b)] } +tup_tail :: { forall b. DisambECP b => PV [Either (EpAnn' AnnAnchor) (LocatedA b)] } : texp commas_tup_tail { unECP $1 >>= \ $1 -> $2 >>= \ $2 -> do { t <- amsA $1 [AddCommaAnn (AR $ rs $ fst $2)] @@ -3064,29 +3064,29 @@ list :: { forall b. DisambECP b => SrcSpan -> (AddEpAnn, AddEpAnn) -> PV (Locate | lexps { \loc (ao,ac) -> $1 >>= \ $1 -> mkHsExplicitListPV loc (reverse $1) (AnnList Nothing (Just ao) (Just ac) [] []) } | texp '..' { \loc (ao,ac) -> unECP $1 >>= \ $1 -> - acsA (\cs -> L loc $ ArithSeq (ApiAnn (spanAsAnchor loc) [ao,mj AnnDotdot $2,ac] cs) Nothing (From $1)) + acsA (\cs -> L loc $ ArithSeq (EpAnn (spanAsAnchor loc) [ao,mj AnnDotdot $2,ac] cs) Nothing (From $1)) >>= ecpFromExp' } | texp ',' exp '..' { \loc (ao,ac) -> unECP $1 >>= \ $1 -> unECP $3 >>= \ $3 -> - acsA (\cs -> L loc $ ArithSeq (ApiAnn (spanAsAnchor loc) [ao,mj AnnComma $2,mj AnnDotdot $4,ac] cs) Nothing (FromThen $1 $3)) + acsA (\cs -> L loc $ ArithSeq (EpAnn (spanAsAnchor loc) [ao,mj AnnComma $2,mj AnnDotdot $4,ac] cs) Nothing (FromThen $1 $3)) >>= ecpFromExp' } | texp '..' exp { \loc (ao,ac) -> unECP $1 >>= \ $1 -> unECP $3 >>= \ $3 -> - acsA (\cs -> L loc $ ArithSeq (ApiAnn (spanAsAnchor loc) [ao,mj AnnDotdot $2,ac] cs) Nothing (FromTo $1 $3)) + acsA (\cs -> L loc $ ArithSeq (EpAnn (spanAsAnchor loc) [ao,mj AnnDotdot $2,ac] cs) Nothing (FromTo $1 $3)) >>= ecpFromExp' } | texp ',' exp '..' exp { \loc (ao,ac) -> unECP $1 >>= \ $1 -> unECP $3 >>= \ $3 -> unECP $5 >>= \ $5 -> - acsA (\cs -> L loc $ ArithSeq (ApiAnn (spanAsAnchor loc) [ao,mj AnnComma $2,mj AnnDotdot $4,ac] cs) Nothing (FromThenTo $1 $3 $5)) + acsA (\cs -> L loc $ ArithSeq (EpAnn (spanAsAnchor loc) [ao,mj AnnComma $2,mj AnnDotdot $4,ac] cs) Nothing (FromThenTo $1 $3 $5)) >>= ecpFromExp' } | texp '|' flattenedpquals { \loc (ao,ac) -> checkMonadComp >>= \ ctxt -> unECP $1 >>= \ $1 -> do { t <- addTrailingVbarA $1 (gl $2) - ; acsA (\cs -> L loc $ mkHsCompAnns ctxt (unLoc $3) t (ApiAnn (spanAsAnchor loc) (AnnList Nothing (Just ao) (Just ac) [] []) cs)) + ; acsA (\cs -> L loc $ mkHsCompAnns ctxt (unLoc $3) t (EpAnn (spanAsAnchor loc) (AnnList Nothing (Just ao) (Just ac) [] []) cs)) >>= ecpFromExp' } } lexps :: { forall b. DisambECP b => PV [LocatedA b] } @@ -3153,21 +3153,21 @@ transformqual :: { Located (RealSrcSpan -> [LStmt GhcPs (LHsExpr GhcPs)] -> Stmt -- Function is applied to a list of stmts *in order* : 'then' exp {% runPV (unECP $2) >>= \ $2 -> acs (\cs-> - sLLlA $1 $> (\r ss -> (mkTransformStmt (ApiAnn (anc r) [mj AnnThen $1] cs) ss $2))) } + sLLlA $1 $> (\r ss -> (mkTransformStmt (EpAnn (anc r) [mj AnnThen $1] cs) ss $2))) } | 'then' exp 'by' exp {% runPV (unECP $2) >>= \ $2 -> runPV (unECP $4) >>= \ $4 -> acs (\cs -> sLLlA $1 $> ( - \r ss -> (mkTransformByStmt (ApiAnn (anc r) [mj AnnThen $1,mj AnnBy $3] cs) ss $2 $4))) } + \r ss -> (mkTransformByStmt (EpAnn (anc r) [mj AnnThen $1,mj AnnBy $3] cs) ss $2 $4))) } | 'then' 'group' 'using' exp {% runPV (unECP $4) >>= \ $4 -> acs (\cs -> sLLlA $1 $> ( - \r ss -> (mkGroupUsingStmt (ApiAnn (anc r) [mj AnnThen $1,mj AnnGroup $2,mj AnnUsing $3] cs) ss $4))) } + \r ss -> (mkGroupUsingStmt (EpAnn (anc r) [mj AnnThen $1,mj AnnGroup $2,mj AnnUsing $3] cs) ss $4))) } | 'then' 'group' 'by' exp 'using' exp {% runPV (unECP $4) >>= \ $4 -> runPV (unECP $6) >>= \ $6 -> acs (\cs -> sLLlA $1 $> ( - \r ss -> (mkGroupByUsingStmt (ApiAnn (anc r) [mj AnnThen $1,mj AnnGroup $2,mj AnnBy $3,mj AnnUsing $5] cs) ss $4 $6))) } + \r ss -> (mkGroupByUsingStmt (EpAnn (anc r) [mj AnnThen $1,mj AnnGroup $2,mj AnnBy $3,mj AnnUsing $5] cs) ss $4 $6))) } -- Note that 'group' is a special_id, which means that you can enable -- TransformListComp while still using Data.List.group. However, this @@ -3230,7 +3230,7 @@ alts1 :: { forall b. DisambECP b => PV (Located ([AddEpAnn],[LMatch GhcPs (Loc alt :: { forall b. DisambECP b => PV (LMatch GhcPs (LocatedA b)) } : pat alt_rhs { $2 >>= \ $2 -> acsA (\cs -> sLL (reLoc $1) $> - (Match { m_ext = (ApiAnn (glAR $1) [] cs) + (Match { m_ext = (EpAnn (glAR $1) [] cs) , m_ctxt = CaseAlt , m_pats = [$1] , m_grhss = unLoc $2 }))} @@ -3241,7 +3241,7 @@ alt_rhs :: { forall b. DisambECP b => PV (Located (GRHSs GhcPs (LocatedA b))) } ralt :: { forall b. DisambECP b => PV (Located [LGRHS GhcPs (LocatedA b)]) } : '->' exp { unECP $2 >>= \ $2 -> - acs (\cs -> sLLlA $1 $> (unguardedRHS (ApiAnn (glR $1) (GrhsAnn Nothing (mu AnnRarrow $1)) cs) (comb2 $1 (reLoc $2)) $2)) } + acs (\cs -> sLLlA $1 $> (unguardedRHS (EpAnn (glR $1) (GrhsAnn Nothing (mu AnnRarrow $1)) cs) (comb2 $1 (reLoc $2)) $2)) } | gdpats { $1 >>= \gdpats -> return $ sL1 gdpats (reverse (unLoc gdpats)) } @@ -3263,7 +3263,7 @@ ifgdpats :: { Located ([AddEpAnn],[LGRHS GhcPs (LHsExpr GhcPs)]) } gdpat :: { forall b. DisambECP b => PV (LGRHS GhcPs (LocatedA b)) } : '|' guardquals '->' exp { unECP $4 >>= \ $4 -> - acs (\cs -> sL (comb2A $1 $>) $ GRHS (ApiAnn (glR $1) (GrhsAnn (Just $ glAA $1) (mu AnnRarrow $3)) cs) (unLoc $2) $4) } + acs (\cs -> sL (comb2A $1 $>) $ GRHS (EpAnn (glR $1) (GrhsAnn (Just $ glAA $1) (mu AnnRarrow $3)) cs) (unLoc $2) $4) } -- 'pat' recognises a pattern, including one with a bang at the top -- e.g. "!x" or "!(x,y)" or "C a b" etc @@ -3334,17 +3334,17 @@ stmt :: { forall b. DisambECP b => PV (LStmt GhcPs (LocatedA b)) } : qual { $1 } | 'rec' stmtlist { $2 >>= \ $2 -> acsA (\cs -> (sLL $1 (reLoc $>) $ mkRecStmt - (ApiAnn (glR $1) (hsDoAnn $1 $2 AnnRec) cs) + (EpAnn (glR $1) (hsDoAnn $1 $2 AnnRec) cs) $2)) } qual :: { forall b. DisambECP b => PV (LStmt GhcPs (LocatedA b)) } : bindpat '<-' exp { unECP $3 >>= \ $3 -> acsA (\cs -> sLLlA (reLoc $1) $> - $ mkPsBindStmt (ApiAnn (glAR $1) [mu AnnLarrow $2] cs) $1 $3) } + $ mkPsBindStmt (EpAnn (glAR $1) [mu AnnLarrow $2] cs) $1 $3) } | exp { unECP $1 >>= \ $1 -> return $ sL1 $1 $ mkBodyStmt $1 } | 'let' binds { acsA (\cs -> (sLL $1 $> - $ mkLetStmt (ApiAnn (glR $1) [mj AnnLet $1] cs) (unLoc $2))) } + $ mkLetStmt (EpAnn (glR $1) [mj AnnLet $1] cs) (unLoc $2))) } ----------------------------------------------------------------------------- -- Record Field Update/Construction @@ -3365,13 +3365,13 @@ fbinds1 :: { forall b. DisambECP b => PV ([Fbind b], Maybe SrcSpan) } fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - fmap Left $ acsA (\cs -> sLL (reLocN $1) (reLoc $>) $ HsRecField (ApiAnn (glNR $1) [mj AnnEqual $2] cs) (sL1N $1 $ mkFieldOcc $1) $3 False) } + fmap Left $ acsA (\cs -> sLL (reLocN $1) (reLoc $>) $ HsRecField (EpAnn (glNR $1) [mj AnnEqual $2] cs) (sL1N $1 $ mkFieldOcc $1) $3 False) } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - fmap Left $ acsa (\cs -> sL1a (reLocN $1) $ HsRecField (ApiAnn (glNR $1) [] cs) (sL1N $1 $ mkFieldOcc $1) rhs True) } + fmap Left $ acsa (\cs -> sL1a (reLocN $1) $ HsRecField (EpAnn (glNR $1) [] cs) (sL1N $1 $ mkFieldOcc $1) rhs True) } -- In the punning case, use a place-holder -- The renamer fills in the final value @@ -3382,7 +3382,7 @@ fbind :: { forall b. DisambECP b => PV (Fbind b) } let top = sL1 $1 $ HsFieldLabel noAnn $1 ((L lf (HsFieldLabel _ f)):t) = reverse (unLoc $3) lf' = comb2 $2 (L lf ()) - fields = top : L lf' (HsFieldLabel (ApiAnn (spanAsAnchor lf') (AnnFieldLabel (Just $ glAA $2)) noCom) f) : t + fields = top : L lf' (HsFieldLabel (EpAnn (spanAsAnchor lf') (AnnFieldLabel (Just $ glAA $2)) noCom) f) : t final = last fields l = comb2 $1 $3 isPun = False @@ -3398,7 +3398,7 @@ fbind :: { forall b. DisambECP b => PV (Fbind b) } let top = sL1 $1 $ HsFieldLabel noAnn $1 ((L lf (HsFieldLabel _ f)):t) = reverse (unLoc $3) lf' = comb2 $2 (L lf ()) - fields = top : L lf' (HsFieldLabel (ApiAnn (spanAsAnchor lf') (AnnFieldLabel (Just $ glAA $2)) noCom) f) : t + fields = top : L lf' (HsFieldLabel (EpAnn (spanAsAnchor lf') (AnnFieldLabel (Just $ glAA $2)) noCom) f) : t final = last fields l = comb2 $1 $3 isPun = True @@ -3410,9 +3410,9 @@ fieldToUpdate :: { Located [Located (HsFieldLabel GhcPs)] } fieldToUpdate -- See Note [Whitespace-sensitive operator parsing] in Lexer.x : fieldToUpdate TIGHT_INFIX_PROJ field {% getCommentsFor (getLoc $3) >>= \cs -> - return (sLL $1 $> ((sLL $2 $> (HsFieldLabel (ApiAnn (glR $2) (AnnFieldLabel $ Just $ glAA $2) cs) $3)) : unLoc $1)) } + return (sLL $1 $> ((sLL $2 $> (HsFieldLabel (EpAnn (glR $2) (AnnFieldLabel $ Just $ glAA $2) cs) $3)) : unLoc $1)) } | field {% getCommentsFor (getLoc $1) >>= \cs -> - return (sL1 $1 [sL1 $1 (HsFieldLabel (ApiAnn (glR $1) (AnnFieldLabel Nothing) cs) $1)]) } + return (sL1 $1 [sL1 $1 (HsFieldLabel (EpAnn (glR $1) (AnnFieldLabel Nothing) cs) $1)]) } ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3433,7 +3433,7 @@ dbinds :: { Located [LIPBind GhcPs] } -- reversed dbind :: { LIPBind GhcPs } dbind : ipvar '=' exp {% runPV (unECP $3) >>= \ $3 -> - acsA (\cs -> sLLlA $1 $> (IPBind (ApiAnn (glR $1) [mj AnnEqual $2] cs) (Left $1) $3)) } + acsA (\cs -> sLLlA $1 $> (IPBind (EpAnn (glR $1) [mj AnnEqual $2] cs) (Left $1) $3)) } ipvar :: { Located HsIPName } : IPDUPVARID { sL1 $1 (HsIPName (getIPDUPVARID $1)) } @@ -3661,7 +3661,7 @@ qopm :: { forall b. DisambInfixOp b => PV (LocatedN b) } -- used in section hole_op :: { forall b. DisambInfixOp b => PV (Located b) } -- used in sections hole_op : '`' '_' '`' { mkHsInfixHolePV (comb2 $1 $>) - (\cs -> ApiAnn (glR $1) (ApiAnnUnboundVar (glAA $1, glAA $3) (glAA $2)) cs) } + (\cs -> EpAnn (glR $1) (EpAnnUnboundVar (glAA $1, glAA $3) (glAA $2)) cs) } qvarop :: { LocatedN RdrName } : qvarsym { $1 } @@ -4209,14 +4209,14 @@ glNRR = AR <$> realSrcSpan . getLocA anc :: RealSrcSpan -> Anchor anc r = Anchor r UnchangedAnchor -acs :: MonadP m => (ApiAnnComments -> Located a) -> m (Located a) +acs :: MonadP m => (EpAnnComments -> Located a) -> m (Located a) acs a = do let (L l _) = a noCom cs <- getCommentsFor l return (a cs) -- Called at the very end to pick up the EOF position, as well as any comments not allocated yet. -acsFinal :: (ApiAnnComments -> Located a) -> P (Located a) +acsFinal :: (EpAnnComments -> Located a) -> P (Located a) acsFinal a = do let (L l _) = a noCom cs <- getCommentsFor l @@ -4227,16 +4227,16 @@ acsFinal a = do Just (pos, gap) -> AnnCommentsBalanced [] [L (realSpanAsAnchor pos) (AnnComment AnnEofComment gap)] return (a (cs Semi.<> csf Semi.<> ce)) -acsa :: MonadP m => (ApiAnnComments -> LocatedAn t a) -> m (LocatedAn t a) +acsa :: MonadP m => (EpAnnComments -> LocatedAn t a) -> m (LocatedAn t a) acsa a = do let (L l _) = a noCom cs <- getCommentsFor (locA l) return (a cs) -acsA :: MonadP m => (ApiAnnComments -> Located a) -> m (LocatedAn t a) +acsA :: MonadP m => (EpAnnComments -> Located a) -> m (LocatedAn t a) acsA a = reLocA <$> acs a -acsExpr :: (ApiAnnComments -> LHsExpr GhcPs) -> P ECP +acsExpr :: (EpAnnComments -> LHsExpr GhcPs) -> P ECP acsExpr a = do { expr :: (LHsExpr GhcPs) <- runPV $ acsa a ; return (ecpFromExp $ expr) } @@ -4263,7 +4263,7 @@ amsrp a@(L l _) bs = do amsrn :: MonadP m => Located a -> NameAnn -> m (LocatedN a) amsrn (L l a) an = do cs <- getCommentsFor l - let ann = (ApiAnn (spanAsAnchor l) an cs) + let ann = (EpAnn (spanAsAnchor l) an cs) return (L (SrcSpanAnn ann l) a) -- |Synonyms for AddEpAnn versions of AnnOpen and AnnClose @@ -4311,8 +4311,8 @@ pvL a = do { av <- a parseModule :: P (Located HsModule) parseModule = parseModuleNoHaddock >>= addHaddockToModule -commentsA :: (Monoid ann) => SrcSpan -> ApiAnnComments -> SrcSpanAnn' (ApiAnn' ann) -commentsA loc cs = SrcSpanAnn (ApiAnn (Anchor (rs loc) UnchangedAnchor) mempty cs) loc +commentsA :: (Monoid ann) => SrcSpan -> EpAnnComments -> SrcSpanAnn' (EpAnn' ann) +commentsA loc cs = SrcSpanAnn (EpAnn (Anchor (rs loc) UnchangedAnchor) mempty cs) loc -- | Instead of getting the *enclosed* comments, this includes the -- *preceding* ones. It is used at the top level to get comments @@ -4392,15 +4392,15 @@ addTrailingCommaS (L l sl) span = L l (sl { sl_tc = Just (annAnchorRealSrcSpan s -- ------------------------------------- -addTrailingDarrowC :: LocatedC a -> Located Token -> ApiAnnComments -> LocatedC a -addTrailingDarrowC (L (SrcSpanAnn ApiAnnNotUsed l) a) lt cs = +addTrailingDarrowC :: LocatedC a -> Located Token -> EpAnnComments -> LocatedC a +addTrailingDarrowC (L (SrcSpanAnn EpAnnNotUsed l) a) lt cs = let u = if (isUnicode lt) then UnicodeSyntax else NormalSyntax - in L (SrcSpanAnn (ApiAnn (spanAsAnchor l) (AnnContext (Just (u,glAA lt)) [] []) cs) l) a -addTrailingDarrowC (L (SrcSpanAnn (ApiAnn lr (AnnContext _ o c) csc) l) a) lt cs = + in L (SrcSpanAnn (EpAnn (spanAsAnchor l) (AnnContext (Just (u,glAA lt)) [] []) cs) l) a +addTrailingDarrowC (L (SrcSpanAnn (EpAnn lr (AnnContext _ o c) csc) l) a) lt cs = let u = if (isUnicode lt) then UnicodeSyntax else NormalSyntax - in L (SrcSpanAnn (ApiAnn lr (AnnContext (Just (u,glAA lt)) o c) (cs Semi.<> csc)) l) a + in L (SrcSpanAnn (EpAnn lr (AnnContext (Just (u,glAA lt)) o c) (cs Semi.<> csc)) l) a -- ------------------------------------- diff --git a/compiler/GHC/Parser/Annotation.hs b/compiler/GHC/Parser/Annotation.hs index fe769a2783..6acb712833 100644 --- a/compiler/GHC/Parser/Annotation.hs +++ b/compiler/GHC/Parser/Annotation.hs @@ -4,27 +4,27 @@ {-# LANGUAGE FlexibleInstances #-} module GHC.Parser.Annotation ( - -- * Core API Annotation types + -- * Core Exact Print Annotation types AnnKeywordId(..), AnnotationComment(..), AnnotationCommentTok(..), IsUnicodeSyntax(..), unicodeAnn, HasE(..), - -- * In-tree Api Annotations + -- * In-tree Exact Print Annotations AddEpAnn(..), AnnAnchor(..), annAnchorRealSrcSpan, DeltaPos(..), - ApiAnn, ApiAnn'(..), Anchor(..), AnchorOperation(..), + EpAnn, EpAnn'(..), Anchor(..), AnchorOperation(..), spanAsAnchor, realSpanAsAnchor, noAnn, -- ** Comments in Annotations - ApiAnnComments(..), LAnnotationComment, com, noCom, + EpAnnComments(..), LAnnotationComment, com, noCom, getFollowingComments, setFollowingComments, setPriorComments, - ApiAnnCO, + EpAnnCO, -- ** Annotations in 'GenLocated' LocatedA, LocatedL, LocatedC, LocatedN, LocatedAn, LocatedP, @@ -37,7 +37,7 @@ module GHC.Parser.Annotation ( AnnPragma(..), AnnContext(..), NameAnn(..), NameAdornment(..), - NoApiAnns(..), + NoEpAnns(..), AnnSortKey(..), -- ** Trailing annotations in lists @@ -75,7 +75,7 @@ module GHC.Parser.Annotation ( -- ** Working with comments in annotations noComments, comment, addCommentsToSrcAnn, setCommentsSrcAnn, - addCommentsToApiAnn, setCommentsApiAnn, + addCommentsToEpAnn, setCommentsEpAnn, transferComments, placeholderRealSpan, @@ -153,9 +153,9 @@ PARSER EMISSION OF ANNOTATIONS The parser interacts with the lexer using the functions -> getCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments -> getPriorCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments -> getFinalCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments +> getCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments +> getPriorCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments +> getFinalCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments The 'getCommentsFor' function is the one used most often. It takes the AST element SrcSpan and removes and returns any comments in the @@ -343,7 +343,7 @@ instance Outputable AnnotationComment where -- | Certain tokens can have alternate representations when unicode syntax is -- enabled. This flag is attached to those tokens in the lexer so that the -- original source representation can be reproduced in the corresponding --- 'ApiAnnotation' +-- 'EpAnnotation' data IsUnicodeSyntax = UnicodeSyntax | NormalSyntax deriving (Eq, Ord, Data, Show) @@ -473,29 +473,29 @@ See Note [XRec and Anno in the AST] for details of how this is done. -- specialised to the specific set of locations of original API -- Annotation elements. So for 'HsLet' we have -- --- type instance XLet GhcPs = ApiAnn' AnnsLet +-- type instance XLet GhcPs = EpAnn' AnnsLet -- data AnnsLet -- = AnnsLet { -- alLet :: AnnAnchor, -- alIn :: AnnAnchor -- } deriving Data -- --- The spacing between the items under the scope of a given ApiAnn' is +-- The spacing between the items under the scope of a given EpAnn' is -- derived from the original 'Anchor'. But there is no requirement -- that the items included in the sub-element have a "matching" -- location in their relative anchors. This allows us to freely move -- elements around, and stitch together new AST fragments out of old -- ones, and have them still printed out in a reasonable way. -data ApiAnn' ann - = ApiAnn { entry :: Anchor +data EpAnn' ann + = EpAnn { entry :: Anchor -- ^ Base location for the start of the syntactic element -- holding the annotations. , anns :: ann -- ^ Annotations added by the Parser - , comments :: ApiAnnComments + , comments :: EpAnnComments -- ^ Comments enclosed in the SrcSpan of the element - -- this `ApiAnn'` is attached to + -- this `EpAnn'` is attached to } - | ApiAnnNotUsed -- ^ No Annotation for generated code, + | EpAnnNotUsed -- ^ No Annotation for generated code, -- e.g. from TH, deriving, etc. deriving (Data, Eq, Functor) @@ -536,7 +536,7 @@ realSpanAsAnchor s = Anchor s UnchangedAnchor -- comments into those occuring before the AST element and those -- following it. The 'AnnCommentsBalanced' constructor is used to do -- this. The GHC parser will only insert the 'AnnComments' form. -data ApiAnnComments = AnnComments +data EpAnnComments = AnnComments { priorComments :: ![LAnnotationComment] } | AnnCommentsBalanced { priorComments :: ![LAnnotationComment] @@ -545,19 +545,19 @@ data ApiAnnComments = AnnComments type LAnnotationComment = GenLocated Anchor AnnotationComment -noCom :: ApiAnnComments +noCom :: EpAnnComments noCom = AnnComments [] -com :: [LAnnotationComment] -> ApiAnnComments +com :: [LAnnotationComment] -> EpAnnComments com cs = AnnComments cs -- --------------------------------------------------------------------- --- | This type is the most direct mapping of the previous API --- Annotations model. It captures the containing `SrcSpan' in its --- `entry` `Anchor`, has a list of `AddEpAnn` as before, and keeps --- track of the comments associated with the anchor. -type ApiAnn = ApiAnn' [AddEpAnn] +-- | This type is the "vanilla" Exact Print Annotation. It captures +-- the containing `SrcSpan' in its `entry` `Anchor`, has a list of +-- `AddEpAnn`, and keeps track of the comments associated with the +-- anchor. +type EpAnn = EpAnn' [AddEpAnn] -- --------------------------------------------------------------------- -- Annotations attached to a 'SrcSpan'. @@ -570,8 +570,8 @@ data SrcSpanAnn' a = SrcSpanAnn { ann :: a, locA :: SrcSpan } deriving (Data, Eq) -- See Note [XRec and Anno in the AST] --- | We mostly use 'SrcSpanAnn\'' with an 'ApiAnn\'' -type SrcAnn ann = SrcSpanAnn' (ApiAnn' ann) +-- | We mostly use 'SrcSpanAnn\'' with an 'EpAnn\'' +type SrcAnn ann = SrcSpanAnn' (EpAnn' ann) -- AZ: is SrcAnn the right abbreviation here? Any better suggestions? -- AZ: should we rename LocatedA to LocatedL? The name comes from @@ -760,7 +760,7 @@ data NameAnn nann_trailing :: [TrailingAnn] } -- | Used when adding a 'TrailingAnn' to an existing 'LocatedN' - -- which has no Api Annotation (via the 'ApiAnnNotUsed' constructor. + -- which has no Api Annotation (via the 'EpAnnNotUsed' constructor. | NameAnnTrailing { nann_trailing :: [TrailingAnn] } @@ -805,10 +805,10 @@ data AnnSortKey -- | Helper function used in the parser to add a 'TrailingAnn' items -- to an existing annotation. -addTrailingAnnToL :: SrcSpan -> TrailingAnn -> ApiAnnComments - -> ApiAnn' AnnList -> ApiAnn' AnnList -addTrailingAnnToL s t cs ApiAnnNotUsed - = ApiAnn (spanAsAnchor s) (AnnList (Just $ spanAsAnchor s) Nothing Nothing [] [t]) cs +addTrailingAnnToL :: SrcSpan -> TrailingAnn -> EpAnnComments + -> EpAnn' AnnList -> EpAnn' AnnList +addTrailingAnnToL s t cs EpAnnNotUsed + = EpAnn (spanAsAnchor s) (AnnList (Just $ spanAsAnchor s) Nothing Nothing [] [t]) cs addTrailingAnnToL _ t cs n = n { anns = addTrailing (anns n) , comments = comments n <> cs } where @@ -816,10 +816,10 @@ addTrailingAnnToL _ t cs n = n { anns = addTrailing (anns n) -- | Helper function used in the parser to add a 'TrailingAnn' items -- to an existing annotation. -addTrailingAnnToA :: SrcSpan -> TrailingAnn -> ApiAnnComments - -> ApiAnn' AnnListItem -> ApiAnn' AnnListItem -addTrailingAnnToA s t cs ApiAnnNotUsed - = ApiAnn (spanAsAnchor s) (AnnListItem [t]) cs +addTrailingAnnToA :: SrcSpan -> TrailingAnn -> EpAnnComments + -> EpAnn' AnnListItem -> EpAnn' AnnListItem +addTrailingAnnToA s t cs EpAnnNotUsed + = EpAnn (spanAsAnchor s) (AnnListItem [t]) cs addTrailingAnnToA _ t cs n = n { anns = addTrailing (anns n) , comments = comments n <> cs } where @@ -827,9 +827,9 @@ addTrailingAnnToA _ t cs n = n { anns = addTrailing (anns n) -- | Helper function used in the parser to add a comma location to an -- existing annotation. -addTrailingCommaToN :: SrcSpan -> ApiAnn' NameAnn -> AnnAnchor -> ApiAnn' NameAnn -addTrailingCommaToN s ApiAnnNotUsed l - = ApiAnn (spanAsAnchor s) (NameAnnTrailing [AddCommaAnn l]) noCom +addTrailingCommaToN :: SrcSpan -> EpAnn' NameAnn -> AnnAnchor -> EpAnn' NameAnn +addTrailingCommaToN s EpAnnNotUsed l + = EpAnn (spanAsAnchor s) (NameAnnTrailing [AddCommaAnn l]) noCom addTrailingCommaToN _ n l = n { anns = addTrailing (anns n) l } where addTrailing :: NameAnn -> AnnAnchor -> NameAnn @@ -867,7 +867,7 @@ reLoc :: LocatedAn a e -> Located e reLoc (L (SrcSpanAnn _ l) a) = L l a reLocA :: Located e -> LocatedAn ann e -reLocA (L l a) = (L (SrcSpanAnn ApiAnnNotUsed l) a) +reLocA (L l a) = (L (SrcSpanAnn EpAnnNotUsed l) a) reLocL :: LocatedN e -> LocatedA e reLocL (L l a) = (L (na2la l) a) @@ -892,53 +892,53 @@ la2r l = realSrcSpan (locA l) extraToAnnList :: AnnList -> [AddEpAnn] -> AnnList extraToAnnList (AnnList a o c e t) as = AnnList a o c (e++as) t -reAnn :: [TrailingAnn] -> ApiAnnComments -> Located a -> LocatedA a -reAnn anns cs (L l a) = L (SrcSpanAnn (ApiAnn (spanAsAnchor l) (AnnListItem anns) cs) l) a +reAnn :: [TrailingAnn] -> EpAnnComments -> Located a -> LocatedA a +reAnn anns cs (L l a) = L (SrcSpanAnn (EpAnn (spanAsAnchor l) (AnnListItem anns) cs) l) a -reAnnC :: AnnContext -> ApiAnnComments -> Located a -> LocatedC a -reAnnC anns cs (L l a) = L (SrcSpanAnn (ApiAnn (spanAsAnchor l) anns cs) l) a +reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a +reAnnC anns cs (L l a) = L (SrcSpanAnn (EpAnn (spanAsAnchor l) anns cs) l) a -reAnnL :: ann -> ApiAnnComments -> Located e -> GenLocated (SrcAnn ann) e -reAnnL anns cs (L l a) = L (SrcSpanAnn (ApiAnn (spanAsAnchor l) anns cs) l) a +reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e +reAnnL anns cs (L l a) = L (SrcSpanAnn (EpAnn (spanAsAnchor l) anns cs) l) a getLocAnn :: Located a -> SrcSpanAnnA -getLocAnn (L l _) = SrcSpanAnn ApiAnnNotUsed l +getLocAnn (L l _) = SrcSpanAnn EpAnnNotUsed l getLocA :: GenLocated (SrcSpanAnn' a) e -> SrcSpan getLocA (L (SrcSpanAnn _ l) _) = l noLocA :: a -> LocatedAn an a -noLocA = L (SrcSpanAnn ApiAnnNotUsed noSrcSpan) +noLocA = L (SrcSpanAnn EpAnnNotUsed noSrcSpan) noAnnSrcSpan :: SrcSpan -> SrcAnn ann -noAnnSrcSpan l = SrcSpanAnn ApiAnnNotUsed l +noAnnSrcSpan l = SrcSpanAnn EpAnnNotUsed l noSrcSpanA :: SrcAnn ann noSrcSpanA = noAnnSrcSpan noSrcSpan --- | Short form for 'ApiAnnNotUsed' -noAnn :: ApiAnn' a -noAnn = ApiAnnNotUsed +-- | Short form for 'EpAnnNotUsed' +noAnn :: EpAnn' a +noAnn = EpAnnNotUsed -addAnns :: ApiAnn -> [AddEpAnn] -> ApiAnnComments -> ApiAnn -addAnns (ApiAnn l as1 cs) as2 cs2 - = ApiAnn (widenAnchor l (as1 ++ as2)) (as1 ++ as2) (cs <> cs2) -addAnns ApiAnnNotUsed [] (AnnComments []) = ApiAnnNotUsed -addAnns ApiAnnNotUsed [] (AnnCommentsBalanced [] []) = ApiAnnNotUsed -addAnns ApiAnnNotUsed as cs = ApiAnn (Anchor placeholderRealSpan UnchangedAnchor) as cs +addAnns :: EpAnn -> [AddEpAnn] -> EpAnnComments -> EpAnn +addAnns (EpAnn l as1 cs) as2 cs2 + = EpAnn (widenAnchor l (as1 ++ as2)) (as1 ++ as2) (cs <> cs2) +addAnns EpAnnNotUsed [] (AnnComments []) = EpAnnNotUsed +addAnns EpAnnNotUsed [] (AnnCommentsBalanced [] []) = EpAnnNotUsed +addAnns EpAnnNotUsed as cs = EpAnn (Anchor placeholderRealSpan UnchangedAnchor) as cs -- AZ:TODO use widenSpan here too -addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> ApiAnnComments -> SrcSpanAnnA -addAnnsA (SrcSpanAnn (ApiAnn l as1 cs) loc) as2 cs2 - = SrcSpanAnn (ApiAnn l (AnnListItem (lann_trailing as1 ++ as2)) (cs <> cs2)) loc -addAnnsA (SrcSpanAnn ApiAnnNotUsed loc) [] (AnnComments []) - = SrcSpanAnn ApiAnnNotUsed loc -addAnnsA (SrcSpanAnn ApiAnnNotUsed loc) [] (AnnCommentsBalanced [] []) - = SrcSpanAnn ApiAnnNotUsed loc -addAnnsA (SrcSpanAnn ApiAnnNotUsed loc) as cs - = SrcSpanAnn (ApiAnn (spanAsAnchor loc) (AnnListItem as) cs) loc +addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA +addAnnsA (SrcSpanAnn (EpAnn l as1 cs) loc) as2 cs2 + = SrcSpanAnn (EpAnn l (AnnListItem (lann_trailing as1 ++ as2)) (cs <> cs2)) loc +addAnnsA (SrcSpanAnn EpAnnNotUsed loc) [] (AnnComments []) + = SrcSpanAnn EpAnnNotUsed loc +addAnnsA (SrcSpanAnn EpAnnNotUsed loc) [] (AnnCommentsBalanced [] []) + = SrcSpanAnn EpAnnNotUsed loc +addAnnsA (SrcSpanAnn EpAnnNotUsed loc) as cs + = SrcSpanAnn (EpAnn (spanAsAnchor loc) (AnnListItem as) cs) loc -- | The annotations need to all come after the anchor. Make sure -- this is the case. @@ -967,24 +967,24 @@ widenAnchorR (Anchor s op) r = Anchor (combineRealSrcSpans s r) op widenLocatedAn :: SrcSpanAnn' an -> [AddEpAnn] -> SrcSpanAnn' an widenLocatedAn (SrcSpanAnn a l) as = SrcSpanAnn a (widenSpan l as) -apiAnnAnnsL :: ApiAnn' a -> [a] -apiAnnAnnsL ApiAnnNotUsed = [] -apiAnnAnnsL (ApiAnn _ anns _) = [anns] +apiAnnAnnsL :: EpAnn' a -> [a] +apiAnnAnnsL EpAnnNotUsed = [] +apiAnnAnnsL (EpAnn _ anns _) = [anns] -apiAnnAnns :: ApiAnn -> [AddEpAnn] -apiAnnAnns ApiAnnNotUsed = [] -apiAnnAnns (ApiAnn _ anns _) = anns +apiAnnAnns :: EpAnn -> [AddEpAnn] +apiAnnAnns EpAnnNotUsed = [] +apiAnnAnns (EpAnn _ anns _) = anns -annParen2AddEpAnn :: ApiAnn' AnnParen -> [AddEpAnn] -annParen2AddEpAnn ApiAnnNotUsed = [] -annParen2AddEpAnn (ApiAnn _ (AnnParen pt o c) _) +annParen2AddEpAnn :: EpAnn' AnnParen -> [AddEpAnn] +annParen2AddEpAnn EpAnnNotUsed = [] +annParen2AddEpAnn (EpAnn _ (AnnParen pt o c) _) = [AddEpAnn ai o, AddEpAnn ac c] where (ai,ac) = parenTypeKws pt -apiAnnComments :: ApiAnn' an -> ApiAnnComments -apiAnnComments ApiAnnNotUsed = AnnComments [] -apiAnnComments (ApiAnn _ _ cs) = cs +apiAnnComments :: EpAnn' an -> EpAnnComments +apiAnnComments EpAnnNotUsed = AnnComments [] +apiAnnComments (EpAnn _ _ cs) = cs -- --------------------------------------------------------------------- -- sortLocatedA :: [LocatedA a] -> [LocatedA a] @@ -1011,18 +1011,18 @@ addCLocAA :: GenLocated (SrcSpanAnn' a1) e1 -> GenLocated (SrcSpanAnn' a2) e2 -> addCLocAA a b c = L (noAnnSrcSpan $ combineSrcSpans (locA $ getLoc a) (locA $ getLoc b)) c -- --------------------------------------------------------------------- --- Utilities for manipulating ApiAnnComments +-- Utilities for manipulating EpAnnComments -- --------------------------------------------------------------------- -getFollowingComments :: ApiAnnComments -> [LAnnotationComment] +getFollowingComments :: EpAnnComments -> [LAnnotationComment] getFollowingComments (AnnComments _) = [] getFollowingComments (AnnCommentsBalanced _ cs) = cs -setFollowingComments :: ApiAnnComments -> [LAnnotationComment] -> ApiAnnComments +setFollowingComments :: EpAnnComments -> [LAnnotationComment] -> EpAnnComments setFollowingComments (AnnComments ls) cs = AnnCommentsBalanced ls cs setFollowingComments (AnnCommentsBalanced ls _) cs = AnnCommentsBalanced ls cs -setPriorComments :: ApiAnnComments -> [LAnnotationComment] -> ApiAnnComments +setPriorComments :: EpAnnComments -> [LAnnotationComment] -> EpAnnComments setPriorComments (AnnComments _) cs = AnnComments cs setPriorComments (AnnCommentsBalanced _ ts) cs = AnnCommentsBalanced cs ts @@ -1030,66 +1030,66 @@ setPriorComments (AnnCommentsBalanced _ ts) cs = AnnCommentsBalanced cs ts -- Comment-only annotations -- --------------------------------------------------------------------- --- TODO:AZ I think ApiAnnCO is not needed -type ApiAnnCO = ApiAnn' NoApiAnns -- ^ Api Annotations for comments only +-- TODO:AZ I think EpAnnCO is not needed +type EpAnnCO = EpAnn' NoEpAnns -- ^ Api Annotations for comments only -data NoApiAnns = NoApiAnns +data NoEpAnns = NoEpAnns deriving (Data,Eq,Ord) -noComments ::ApiAnnCO -noComments = ApiAnn (Anchor placeholderRealSpan UnchangedAnchor) NoApiAnns noCom +noComments ::EpAnnCO +noComments = EpAnn (Anchor placeholderRealSpan UnchangedAnchor) NoEpAnns noCom -- TODO:AZ get rid of this placeholderRealSpan :: RealSrcSpan placeholderRealSpan = realSrcLocSpan (mkRealSrcLoc (mkFastString "placeholder") (-1) (-1)) -comment :: RealSrcSpan -> ApiAnnComments -> ApiAnnCO -comment loc cs = ApiAnn (Anchor loc UnchangedAnchor) NoApiAnns cs +comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO +comment loc cs = EpAnn (Anchor loc UnchangedAnchor) NoEpAnns cs -- --------------------------------------------------------------------- --- Utilities for managing comments in an `ApiAnn' a` structure. +-- Utilities for managing comments in an `EpAnn' a` structure. -- --------------------------------------------------------------------- -- | Add additional comments to a 'SrcAnn', used for manipulating the -- AST prior to exact printing the changed one. -addCommentsToSrcAnn :: (Monoid ann) => SrcAnn ann -> ApiAnnComments -> SrcAnn ann -addCommentsToSrcAnn (SrcSpanAnn ApiAnnNotUsed loc) cs - = SrcSpanAnn (ApiAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs) loc -addCommentsToSrcAnn (SrcSpanAnn (ApiAnn a an cs) loc) cs' - = SrcSpanAnn (ApiAnn a an (cs <> cs')) loc +addCommentsToSrcAnn :: (Monoid ann) => SrcAnn ann -> EpAnnComments -> SrcAnn ann +addCommentsToSrcAnn (SrcSpanAnn EpAnnNotUsed loc) cs + = SrcSpanAnn (EpAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs) loc +addCommentsToSrcAnn (SrcSpanAnn (EpAnn a an cs) loc) cs' + = SrcSpanAnn (EpAnn a an (cs <> cs')) loc -- | Replace any existing comments on a 'SrcAnn', used for manipulating the -- AST prior to exact printing the changed one. -setCommentsSrcAnn :: (Monoid ann) => SrcAnn ann -> ApiAnnComments -> SrcAnn ann -setCommentsSrcAnn (SrcSpanAnn ApiAnnNotUsed loc) cs - = SrcSpanAnn (ApiAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs) loc -setCommentsSrcAnn (SrcSpanAnn (ApiAnn a an _) loc) cs - = SrcSpanAnn (ApiAnn a an cs) loc +setCommentsSrcAnn :: (Monoid ann) => SrcAnn ann -> EpAnnComments -> SrcAnn ann +setCommentsSrcAnn (SrcSpanAnn EpAnnNotUsed loc) cs + = SrcSpanAnn (EpAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs) loc +setCommentsSrcAnn (SrcSpanAnn (EpAnn a an _) loc) cs + = SrcSpanAnn (EpAnn a an cs) loc -- | Add additional comments, used for manipulating the -- AST prior to exact printing the changed one. -addCommentsToApiAnn :: (Monoid a) - => SrcSpan -> ApiAnn' a -> ApiAnnComments -> ApiAnn' a -addCommentsToApiAnn loc ApiAnnNotUsed cs - = ApiAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs -addCommentsToApiAnn _ (ApiAnn a an ocs) ncs = ApiAnn a an (ocs <> ncs) +addCommentsToEpAnn :: (Monoid a) + => SrcSpan -> EpAnn' a -> EpAnnComments -> EpAnn' a +addCommentsToEpAnn loc EpAnnNotUsed cs + = EpAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs +addCommentsToEpAnn _ (EpAnn a an ocs) ncs = EpAnn a an (ocs <> ncs) -- | Replace any existing comments, used for manipulating the -- AST prior to exact printing the changed one. -setCommentsApiAnn :: (Monoid a) - => SrcSpan -> ApiAnn' a -> ApiAnnComments -> ApiAnn' a -setCommentsApiAnn loc ApiAnnNotUsed cs - = ApiAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs -setCommentsApiAnn _ (ApiAnn a an _) cs = ApiAnn a an cs +setCommentsEpAnn :: (Monoid a) + => SrcSpan -> EpAnn' a -> EpAnnComments -> EpAnn' a +setCommentsEpAnn loc EpAnnNotUsed cs + = EpAnn (Anchor (realSrcSpan loc) UnchangedAnchor) mempty cs +setCommentsEpAnn _ (EpAnn a an _) cs = EpAnn a an cs -- | Transfer comments from the annotations in one 'SrcAnn' to those -- in another. The originals are not changed. This is used when -- manipulating an AST prior to exact printing, transferComments :: (Monoid ann) => SrcAnn ann -> SrcAnn ann -> (SrcAnn ann, SrcAnn ann) -transferComments from@(SrcSpanAnn ApiAnnNotUsed _) to = (from, to) -transferComments (SrcSpanAnn (ApiAnn a an cs) l) to - = ((SrcSpanAnn (ApiAnn a an noCom) l), addCommentsToSrcAnn to cs) +transferComments from@(SrcSpanAnn EpAnnNotUsed _) to = (from, to) +transferComments (SrcSpanAnn (EpAnn a an cs) l) to + = ((SrcSpanAnn (EpAnn a an noCom) l), addCommentsToSrcAnn to cs) -- --------------------------------------------------------------------- -- Semigroup instances, to allow easy combination of annotaion elements @@ -1101,10 +1101,10 @@ instance (Semigroup an) => Semigroup (SrcSpanAnn' an) where -- annotations must follow it. So we combine them which yields the -- largest span -instance (Semigroup a) => Semigroup (ApiAnn' a) where - ApiAnnNotUsed <> x = x - x <> ApiAnnNotUsed = x - (ApiAnn l1 a1 b1) <> (ApiAnn l2 a2 b2) = ApiAnn (l1 <> l2) (a1 <> a2) (b1 <> b2) +instance (Semigroup a) => Semigroup (EpAnn' a) where + EpAnnNotUsed <> x = x + x <> EpAnnNotUsed = x + (EpAnn l1 a1 b1) <> (EpAnn l2 a2 b2) = EpAnn (l1 <> l2) (a1 <> a2) (b1 <> b2) -- The critical part about the anchor is its left edge, and all -- annotations must follow it. So we combine them which yields the -- largest span @@ -1115,15 +1115,15 @@ instance Ord Anchor where instance Semigroup Anchor where Anchor r1 o1 <> Anchor r2 _ = Anchor (combineRealSrcSpans r1 r2) o1 -instance Semigroup ApiAnnComments where +instance Semigroup EpAnnComments where AnnComments cs1 <> AnnComments cs2 = AnnComments (cs1 ++ cs2) AnnComments cs1 <> AnnCommentsBalanced cs2 as2 = AnnCommentsBalanced (cs1 ++ cs2) as2 AnnCommentsBalanced cs1 as1 <> AnnComments cs2 = AnnCommentsBalanced (cs1 ++ cs2) as1 AnnCommentsBalanced cs1 as1 <> AnnCommentsBalanced cs2 as2 = AnnCommentsBalanced (cs1 ++ cs2) (as1++as2) -instance (Monoid a) => Monoid (ApiAnn' a) where - mempty = ApiAnnNotUsed +instance (Monoid a) => Monoid (EpAnn' a) where + mempty = EpAnnNotUsed instance Semigroup AnnListItem where (AnnListItem l1) <> (AnnListItem l2) = AnnListItem (l1 <> l2) @@ -1159,9 +1159,9 @@ instance Semigroup AnnSortKey where instance Monoid AnnSortKey where mempty = NoAnnSortKey -instance (Outputable a) => Outputable (ApiAnn' a) where - ppr (ApiAnn l a c) = text "ApiAnn" <+> ppr l <+> ppr a <+> ppr c - ppr ApiAnnNotUsed = text "ApiAnnNotUsed" +instance (Outputable a) => Outputable (EpAnn' a) where + ppr (EpAnn l a c) = text "EpAnn" <+> ppr l <+> ppr a <+> ppr c + ppr EpAnnNotUsed = text "EpAnnNotUsed" instance Outputable Anchor where ppr (Anchor a o) = text "Anchor" <+> ppr a <+> ppr o @@ -1176,7 +1176,7 @@ instance Outputable DeltaPos where instance Outputable (GenLocated Anchor AnnotationComment) where ppr (L l c) = text "L" <+> ppr l <+> ppr c -instance Outputable ApiAnnComments where +instance Outputable EpAnnComments where ppr (AnnComments cs) = text "AnnComments" <+> ppr cs ppr (AnnCommentsBalanced cs ts) = text "AnnCommentsBalanced" <+> ppr cs <+> ppr ts diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x index 8eea1aea62..125e6aaaf6 100644 --- a/compiler/GHC/Parser/Lexer.x +++ b/compiler/GHC/Parser/Lexer.x @@ -65,7 +65,7 @@ module GHC.Parser.Lexer ( ExtBits(..), xtest, xunset, xset, lexTokenStream, - mkParensApiAnn, + mkParensEpAnn, getCommentsFor, getPriorCommentsFor, getFinalCommentsFor, getEofPos, commentToAnnotation, @@ -2892,13 +2892,13 @@ class Monad m => MonadP m where getBit :: ExtBits -> m Bool -- | Go through the @comment_q@ in @PState@ and remove all comments -- that belong within the given span - allocateCommentsP :: RealSrcSpan -> m ApiAnnComments + allocateCommentsP :: RealSrcSpan -> m EpAnnComments -- | Go through the @comment_q@ in @PState@ and remove all comments -- that come before or within the given span - allocatePriorCommentsP :: RealSrcSpan -> m ApiAnnComments + allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments -- | Go through the @comment_q@ in @PState@ and remove all comments -- that come after the given span - allocateFinalCommentsP :: RealSrcSpan -> m ApiAnnComments + allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments instance MonadP P where addError err @@ -2934,15 +2934,15 @@ instance MonadP P where comment_q = comment_q' } (AnnCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns)) -getCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments +getCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments getCommentsFor (RealSrcSpan l _) = allocateCommentsP l getCommentsFor _ = return noCom -getPriorCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments +getPriorCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments getPriorCommentsFor (RealSrcSpan l _) = allocatePriorCommentsP l getPriorCommentsFor _ = return noCom -getFinalCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments +getFinalCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments getFinalCommentsFor (RealSrcSpan l _) = allocateFinalCommentsP l getFinalCommentsFor _ = return noCom @@ -3437,9 +3437,9 @@ clean_pragma prag = canon_ws (map toLower (unprefix prag)) -- |Given a 'SrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate -- 'AddEpAnn' values for the opening and closing bordering on the start -- and end of the span -mkParensApiAnn :: SrcSpan -> [AddEpAnn] -mkParensApiAnn (UnhelpfulSpan _) = [] -mkParensApiAnn (RealSrcSpan ss _) = [AddEpAnn AnnOpenP (AR lo),AddEpAnn AnnCloseP (AR lc)] +mkParensEpAnn :: SrcSpan -> [AddEpAnn] +mkParensEpAnn (UnhelpfulSpan _) = [] +mkParensEpAnn (RealSrcSpan ss _) = [AddEpAnn AnnOpenP (AR lo),AddEpAnn AnnCloseP (AR lc)] where f = srcSpanFile ss sl = srcSpanStartLine ss diff --git a/compiler/GHC/Parser/PostProcess.hs b/compiler/GHC/Parser/PostProcess.hs index 56564ef908..d6248bd107 100644 --- a/compiler/GHC/Parser/PostProcess.hs +++ b/compiler/GHC/Parser/PostProcess.hs @@ -189,7 +189,7 @@ mkClassDecl loc' (L _ (mcxt, tycl_hdr)) fds where_cls layoutInfo annsIn ; (cls, tparams, fixity, ann) <- checkTyClHdr True tycl_hdr ; (tyvars,annst) <- checkTyVars (text "class") whereDots cls tparams ; cs <- getCommentsFor (locA loc) -- Get any remaining comments - ; let anns' = addAnns (ApiAnn (spanAsAnchor $ locA loc) annsIn noCom) (ann++annst) cs + ; let anns' = addAnns (EpAnn (spanAsAnchor $ locA loc) annsIn noCom) (ann++annst) cs ; return (L loc (ClassDecl { tcdCExt = (anns', NoAnnSortKey, layoutInfo) , tcdCtxt = mcxt , tcdLName = cls, tcdTyVars = tyvars @@ -215,7 +215,7 @@ mkTyData loc' new_or_data cType (L _ (mcxt, tycl_hdr)) ; (tc, tparams, fixity, ann) <- checkTyClHdr False tycl_hdr ; (tyvars, anns) <- checkTyVars (ppr new_or_data) equalsDots tc tparams ; cs <- getCommentsFor (locA loc) -- Get any remaining comments - ; let anns' = addAnns (ApiAnn (spanAsAnchor $ locA loc) annsIn noCom) (ann ++ anns) cs + ; let anns' = addAnns (EpAnn (spanAsAnchor $ locA loc) annsIn noCom) (ann ++ anns) cs ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv anns' ; return (L loc (DataDecl { tcdDExt = anns', -- AZ: do we need these? tcdLName = tc, tcdTyVars = tyvars, @@ -228,7 +228,7 @@ mkDataDefn :: NewOrData -> Maybe (LHsKind GhcPs) -> [LConDecl GhcPs] -> HsDeriving GhcPs - -> ApiAnn + -> EpAnn -> P (HsDataDefn GhcPs) mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv ann = do { checkDatatypeContext mcxt @@ -250,7 +250,7 @@ mkTySynonym loc lhs rhs annsIn ; cs1 <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan [temp] ; (tyvars, anns) <- checkTyVars (text "type") equalsDots tc tparams ; cs2 <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan [temp] - ; let anns' = addAnns (ApiAnn (spanAsAnchor loc) annsIn noCom) (ann ++ anns) (cs1 Semi.<> cs2) + ; let anns' = addAnns (EpAnn (spanAsAnchor loc) annsIn noCom) (ann ++ anns) (cs1 Semi.<> cs2) ; return (L (noAnnSrcSpan loc) (SynDecl { tcdSExt = anns' , tcdLName = tc, tcdTyVars = tyvars @@ -268,7 +268,7 @@ mkStandaloneKindSig loc lhs rhs anns = ; v <- check_singular_lhs (reverse vs) ; cs <- getCommentsFor loc ; return $ L (noAnnSrcSpan loc) - $ StandaloneKindSig (ApiAnn (spanAsAnchor loc) anns cs) v rhs } + $ StandaloneKindSig (EpAnn (spanAsAnchor loc) anns cs) v rhs } where check_lhs_name v@(unLoc->name) = if isUnqual name && isTcOcc (rdrNameOcc name) @@ -290,7 +290,7 @@ mkTyFamInstEqn loc bndrs lhs rhs anns = do { (tc, tparams, fixity, ann) <- checkTyClHdr False lhs ; cs <- getCommentsFor loc ; return (L (noAnnSrcSpan loc) $ FamEqn - { feqn_ext = ApiAnn (spanAsAnchor loc) (anns `mappend` ann) cs + { feqn_ext = EpAnn (spanAsAnchor loc) (anns `mappend` ann) cs , feqn_tycon = tc , feqn_bndrs = bndrs , feqn_pats = tparams @@ -312,7 +312,7 @@ mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr) = do { (tc, tparams, fixity, ann) <- checkTyClHdr False tycl_hdr ; -- AZ:TODO: deal with these comments ; cs <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan [temp] - ; let anns' = addAnns (ApiAnn (spanAsAnchor loc) ann cs) anns noCom + ; let anns' = addAnns (EpAnn (spanAsAnchor loc) ann cs) anns noCom ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv anns' ; return (L (noAnnSrcSpan loc) (DataFamInstD anns' (DataFamInstDecl (FamEqn { feqn_ext = noAnn -- AZ: get anns @@ -329,7 +329,7 @@ mkTyFamInst :: SrcSpan mkTyFamInst loc eqn anns = do cs <- getCommentsFor loc return (L (noAnnSrcSpan loc) (TyFamInstD noExtField - (TyFamInstDecl (ApiAnn (spanAsAnchor loc) anns cs) eqn))) + (TyFamInstDecl (EpAnn (spanAsAnchor loc) anns cs) eqn))) mkFamDecl :: SrcSpan -> FamilyInfo GhcPs @@ -344,7 +344,7 @@ mkFamDecl loc info topLevel lhs ksig injAnn annsIn ; cs1 <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan [temp] ; (tyvars, anns) <- checkTyVars (ppr info) equals_or_where tc tparams ; cs2 <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan [temp] - ; let anns' = addAnns (ApiAnn (spanAsAnchor loc) annsIn noCom) (ann++anns) (cs1 Semi.<> cs2) + ; let anns' = addAnns (EpAnn (spanAsAnchor loc) annsIn noCom) (ann++anns) (cs1 Semi.<> cs2) ; return (L (noAnnSrcSpan loc) (FamDecl noExtField (FamilyDecl { fdExt = anns' @@ -394,7 +394,7 @@ mkRoleAnnotDecl loc tycon roles anns = do { roles' <- mapM parse_role roles ; cs <- getCommentsFor loc ; return $ L (noAnnSrcSpan loc) - $ RoleAnnotDecl (ApiAnn (spanAsAnchor loc) anns cs) tycon roles' } + $ RoleAnnotDecl (EpAnn (spanAsAnchor loc) anns cs) tycon roles' } where role_data_type = dataTypeOf (undefined :: Role) all_roles = map fromConstr $ dataTypeConstrs role_data_type @@ -436,14 +436,14 @@ annBinds a (HsValBinds an bs) = (HsValBinds (add_where a an) bs) annBinds a (HsIPBinds an bs) = (HsIPBinds (add_where a an) bs) annBinds _ (EmptyLocalBinds x) = (EmptyLocalBinds x) -add_where :: AddEpAnn -> ApiAnn' AnnList -> ApiAnn' AnnList -add_where an@(AddEpAnn _ (AR rs)) (ApiAnn a (AnnList anc o c r t) cs) +add_where :: AddEpAnn -> EpAnn' AnnList -> EpAnn' AnnList +add_where an@(AddEpAnn _ (AR rs)) (EpAnn a (AnnList anc o c r t) cs) | valid_anchor (anchor a) - = ApiAnn (widenAnchor a [an]) (AnnList anc o c (an:r) t) cs + = EpAnn (widenAnchor a [an]) (AnnList anc o c (an:r) t) cs | otherwise - = ApiAnn (patch_anchor rs a) (AnnList (fmap (patch_anchor rs) anc) o c (an:r) t) cs -add_where an@(AddEpAnn _ (AR rs)) ApiAnnNotUsed - = ApiAnn (Anchor rs UnchangedAnchor) + = EpAnn (patch_anchor rs a) (AnnList (fmap (patch_anchor rs) anc) o c (an:r) t) cs +add_where an@(AddEpAnn _ (AR rs)) EpAnnNotUsed + = EpAnn (Anchor rs UnchangedAnchor) (AnnList (Just $ Anchor rs UnchangedAnchor) Nothing Nothing [an] []) noCom add_where (AddEpAnn _ (AD _)) _ = panic "add_where" -- AD should only be used for transformations @@ -679,7 +679,7 @@ recordPatSynErr :: SrcSpan -> LPat GhcPs -> P a recordPatSynErr loc pat = addFatalError $ PsError (PsErrRecordSyntaxInPatSynDecl pat) [] loc -mkConDeclH98 :: ApiAnn -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs] +mkConDeclH98 :: EpAnn -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs] -> Maybe (LHsContext GhcPs) -> HsConDeclH98Details GhcPs -> ConDecl GhcPs @@ -719,7 +719,7 @@ mkGadtDecl loc names ty annsIn = do in (PrefixConGADT arg_types, res_type, anns, cs) an = case outer_bndrs of - _ -> ApiAnn (spanAsAnchor loc) (annsIn ++ annsa) (cs Semi.<> csa) + _ -> EpAnn (spanAsAnchor loc) (annsIn ++ annsa) (cs Semi.<> csa) pure $ L l ConDeclGADT { con_g_ext = an @@ -836,16 +836,16 @@ checkTyVars pp_what equals_or_where tc tparms check (HsValArg ty) = chkParens [] noCom ty check (HsArgPar sp) = addFatalError $ PsError (PsErrMalformedDecl pp_what (unLoc tc)) [] sp -- Keep around an action for adjusting the annotations of extra parens - chkParens :: [AddEpAnn] -> ApiAnnComments -> LHsType GhcPs + chkParens :: [AddEpAnn] -> EpAnnComments -> LHsType GhcPs -> P (LHsTyVarBndr () GhcPs, [AddEpAnn]) chkParens acc cs (L l (HsParTy an ty)) - = chkParens (mkParensApiAnn (locA l) ++ acc) (cs Semi.<> apiAnnComments an) ty + = chkParens (mkParensEpAnn (locA l) ++ acc) (cs Semi.<> apiAnnComments an) ty chkParens acc cs ty = do tv <- chk acc cs ty return (tv, reverse acc) -- Check that the name space is correct! - chk :: [AddEpAnn] -> ApiAnnComments -> LHsType GhcPs -> P (LHsTyVarBndr () GhcPs) + chk :: [AddEpAnn] -> EpAnnComments -> LHsType GhcPs -> P (LHsTyVarBndr () GhcPs) chk an cs (L l (HsKindSig annk (L annt (HsTyVar ann _ (L lv tv))) k)) | isRdrTyVar tv = return (L (widenLocatedAn (l Semi.<> annt) an) @@ -869,7 +869,7 @@ checkDatatypeContext (Just c) unless allowed $ addError $ PsError (PsErrIllegalDataTypeContext c) [] (getLocA c) type LRuleTyTmVar = Located RuleTyTmVar -data RuleTyTmVar = RuleTyTmVar ApiAnn (LocatedN RdrName) (Maybe (LHsType GhcPs)) +data RuleTyTmVar = RuleTyTmVar EpAnn (LocatedN RdrName) (Maybe (LHsType GhcPs)) -- ^ Essentially a wrapper for a @RuleBndr GhcPs@ -- turns RuleTyTmVars into RuleBnrs - this is straightforward @@ -944,7 +944,7 @@ checkTyClHdr is_cls ty | isRdrTc tc = return (ltc, acc, fix, ann) go _ (HsOpTy _ t1 ltc@(L _ tc) t2) acc ann _fix | isRdrTc tc = return (ltc, HsValArg t1:HsValArg t2:acc, Infix, ann) - go l (HsParTy _ ty) acc ann fix = goL ty acc (ann ++mkParensApiAnn l) fix + go l (HsParTy _ ty) acc ann fix = goL ty acc (ann ++mkParensEpAnn l) fix go _ (HsAppTy _ t1 t2) acc ann fix = goL t1 (HsValArg t2:acc) ann fix go _ (HsAppKindTy l ty ki) acc ann fix = goL ty (HsTypeArg l ki:acc) ann fix go l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ann fix @@ -960,18 +960,18 @@ checkTyClHdr is_cls ty -- Combine the annotations from the HsParTy and HsStarTy into a -- new one for the LocatedN RdrName - newAnns :: SrcSpanAnnA -> ApiAnn' AnnParen -> SrcSpanAnnN - newAnns (SrcSpanAnn ApiAnnNotUsed l) (ApiAnn as (AnnParen _ o c) cs) = + newAnns :: SrcSpanAnnA -> EpAnn' AnnParen -> SrcSpanAnnN + newAnns (SrcSpanAnn EpAnnNotUsed l) (EpAnn as (AnnParen _ o c) cs) = let lr = combineRealSrcSpans (realSrcSpan l) (anchor as) -- lr = widenAnchorR as (realSrcSpan l) - an = (ApiAnn (Anchor lr UnchangedAnchor) (NameAnn NameParens o (AR $ realSrcSpan l) c []) cs) + an = (EpAnn (Anchor lr UnchangedAnchor) (NameAnn NameParens o (AR $ realSrcSpan l) c []) cs) in SrcSpanAnn an (RealSrcSpan lr Nothing) - newAnns _ ApiAnnNotUsed = panic "missing AnnParen" - newAnns (SrcSpanAnn (ApiAnn ap (AnnListItem ta) csp) l) (ApiAnn as (AnnParen _ o c) cs) = + newAnns _ EpAnnNotUsed = panic "missing AnnParen" + newAnns (SrcSpanAnn (EpAnn ap (AnnListItem ta) csp) l) (EpAnn as (AnnParen _ o c) cs) = let lr = combineRealSrcSpans (anchor ap) (anchor as) - an = (ApiAnn (Anchor lr UnchangedAnchor) (NameAnn NameParens o (AR $ realSrcSpan l) c ta) (csp Semi.<> cs)) + an = (EpAnn (Anchor lr UnchangedAnchor) (NameAnn NameParens o (AR $ realSrcSpan l) c ta) (csp Semi.<> cs)) in SrcSpanAnn an (RealSrcSpan lr Nothing) -- | Yield a parse error if we have a function applied directly to a do block @@ -1019,7 +1019,7 @@ checkContext :: LHsType GhcPs -> P (LHsContext GhcPs) checkContext orig_t@(L (SrcSpanAnn _ l) _orig_t) = check ([],[],noCom) orig_t where - check :: ([AnnAnchor],[AnnAnchor],ApiAnnComments) + check :: ([AnnAnchor],[AnnAnchor],EpAnnComments) -> LHsType GhcPs -> P (LHsContext GhcPs) check (oparens,cparens,cs) (L _l (HsTupleTy ann' HsBoxedOrConstraintTuple ts)) -- (Eq a, Ord b) shows up as a tuple type. Only boxed tuples can @@ -1027,22 +1027,22 @@ checkContext orig_t@(L (SrcSpanAnn _ l) _orig_t) = -- Ditto () = do let (op,cp,cs') = case ann' of - ApiAnnNotUsed -> ([],[],noCom) - ApiAnn _ (AnnParen _ o c) cs -> ([o],[c],cs) - return (L (SrcSpanAnn (ApiAnn (spanAsAnchor l) + EpAnnNotUsed -> ([],[],noCom) + EpAnn _ (AnnParen _ o c) cs -> ([o],[c],cs) + return (L (SrcSpanAnn (EpAnn (spanAsAnchor l) (AnnContext Nothing (op Semi.<> oparens) (cp Semi.<> cparens)) (cs Semi.<> cs')) l) ts) check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty)) -- to be sure HsParTy doesn't get into the way = do let (op,cp,cs') = case ann' of - ApiAnnNotUsed -> ([],[],noCom) - ApiAnn _ (AnnParen _ open close ) cs -> ([open],[close],cs) + EpAnnNotUsed -> ([],[],noCom) + EpAnn _ (AnnParen _ open close ) cs -> ([open],[close],cs) check (op++opi,cp++cpi,cs' Semi.<> csi) ty -- No need for anns, returning original check (_opi,_cpi,_csi) _t = - return (L (SrcSpanAnn (ApiAnn (spanAsAnchor l) (AnnContext Nothing [] []) noCom) l) [orig_t]) + return (L (SrcSpanAnn (EpAnn (spanAsAnchor l) (AnnContext Nothing [] []) noCom) l) [orig_t]) checkImportDecl :: Maybe AnnAnchor -> Maybe AnnAnchor @@ -1148,7 +1148,7 @@ checkAPat loc e0 = do (L l p) <- checkLPat e let aa = [AddEpAnn ai o, AddEpAnn ac c] (ai,ac) = parenTypeKws pt - return (ParPat (ApiAnn (spanAsAnchor $ (widenSpan (locA l) aa)) an noCom) (L l p)) + return (ParPat (EpAnn (spanAsAnchor $ (widenSpan (locA l) aa)) an noCom) (L l p)) _ -> patFail (locA loc) (ppr e0) placeHolderPunRhs :: DisambECP b => PV (LocatedA b) @@ -1211,7 +1211,7 @@ checkFunBind strictness locF ann lhs_loc fun is_infix pats (L rhs_span grhss) let match_span = noAnnSrcSpan $ combineSrcSpans lhs_loc rhs_span cs <- getCommentsFor locF return (makeFunBind fun (L (noAnnSrcSpan $ locA match_span) - [L match_span (Match { m_ext = ApiAnn (spanAsAnchor locF) ann cs + [L match_span (Match { m_ext = EpAnn (spanAsAnchor locF) ann cs , m_ctxt = FunRhs { mc_fun = fun , mc_fixity = is_infix @@ -1240,10 +1240,10 @@ checkPatBind :: SrcSpan -> LPat GhcPs -> Located (GRHSs GhcPs (LHsExpr GhcPs)) -> P (HsBind GhcPs) -checkPatBind loc annsIn (L _ (BangPat (ApiAnn _ ans cs) (L _ (VarPat _ v)))) +checkPatBind loc annsIn (L _ (BangPat (EpAnn _ ans cs) (L _ (VarPat _ v)))) (L _match_span grhss) = return (makeFunBind v (L (noAnnSrcSpan loc) - [L (noAnnSrcSpan loc) (m (ApiAnn (spanAsAnchor loc) (ans++annsIn) cs) v)])) + [L (noAnnSrcSpan loc) (m (EpAnn (spanAsAnchor loc) (ans++annsIn) cs) v)])) where m a v = Match { m_ext = a , m_ctxt = FunRhs { mc_fun = v @@ -1254,7 +1254,7 @@ checkPatBind loc annsIn (L _ (BangPat (ApiAnn _ ans cs) (L _ (VarPat _ v)))) checkPatBind loc annsIn lhs (L _ grhss) = do cs <- getCommentsFor loc - return (PatBind (ApiAnn (spanAsAnchor loc) annsIn cs) lhs grhss ([],[])) + return (PatBind (EpAnn (spanAsAnchor loc) annsIn cs) lhs grhss ([],[])) checkValSigLhs :: LHsExpr GhcPs -> P (LocatedN RdrName) checkValSigLhs (L _ (HsVar _ lrdr@(L _ v))) @@ -1291,8 +1291,8 @@ isFunLhs e = go e [] [] | not (isRdrDataCon f) = return (Just (L loc f, Prefix, es, ann)) go (L _ (PatBuilderApp f e)) es ann = go f (e:es) ann go (L l (PatBuilderPar e _an)) es@(_:_) ann - = go e es (ann ++ mkParensApiAnn (locA l)) - go (L loc (PatBuilderOpApp l (L loc' op) r (ApiAnn loca anns cs))) es ann + = go e es (ann ++ mkParensEpAnn (locA l)) + go (L loc (PatBuilderOpApp l (L loc' op) r (EpAnn loca anns cs))) es ann | not (isRdrDataCon op) -- We have found the function! = return (Just (L loc' op, Infix, (l:r:es), (anns ++ ann))) | otherwise -- Infix data con; keep going @@ -1302,11 +1302,11 @@ isFunLhs e = go e [] [] -> return (Just (op', Infix, j : op_app : es', ann')) where op_app = L loc (PatBuilderOpApp k - (L loc' op) r (ApiAnn loca anns cs)) + (L loc' op) r (EpAnn loca anns cs)) _ -> return Nothing } go _ _ _ = return Nothing -mkBangTy :: ApiAnn -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs +mkBangTy :: EpAnn -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs mkBangTy anns strictness = HsBangTy anns (HsSrcBang NoSourceText NoSrcUnpack strictness) @@ -1319,7 +1319,7 @@ addUnpackednessP :: MonadP m => Located UnpackednessPragma -> LHsType GhcPs -> m addUnpackednessP (L lprag (UnpackednessPragma anns prag unpk)) ty = do let l' = combineSrcSpans lprag (getLocA ty) cs <- getCommentsFor l' - let an = ApiAnn (spanAsAnchor l') anns cs + let an = EpAnn (spanAsAnchor l') anns cs t' = addUnpackedness an ty return (L (noAnnSrcSpan l') t') where @@ -1381,7 +1381,7 @@ type Fbind b = Either (LHsRecField GhcPs (LocatedA b)) (LHsRecProj GhcPs (Locate class DisambInfixOp b where mkHsVarOpPV :: LocatedN RdrName -> PV (LocatedN b) mkHsConOpPV :: LocatedN RdrName -> PV (LocatedN b) - mkHsInfixHolePV :: SrcSpan -> (ApiAnnComments -> ApiAnn' ApiAnnUnboundVar) -> PV (Located b) + mkHsInfixHolePV :: SrcSpan -> (EpAnnComments -> EpAnn' EpAnnUnboundVar) -> PV (Located b) instance DisambInfixOp (HsExpr GhcPs) where mkHsVarOpPV v = return $ L (getLoc v) (HsVar noExtField v) @@ -1418,7 +1418,7 @@ class (b ~ (Body b) GhcPs, AnnoBody b) => DisambECP b where -> LocatedA b -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV - :: SrcSpan -> (ApiAnnComments -> MatchGroup GhcPs (LocatedA b)) -> PV (LocatedA b) + :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA b)) -> PV (LocatedA b) -- | Disambiguate "let ... in ..." mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA b -> AnnsLet -> PV (LocatedA b) @@ -1433,7 +1433,7 @@ class (b ~ (Body b) GhcPs, AnnoBody b) => DisambECP b where -> PV (LocatedA b) -- | Disambiguate "case ... of ..." mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> (LocatedL [LMatch GhcPs (LocatedA b)]) - -> ApiAnnHsCase -> PV (LocatedA b) + -> EpAnnHsCase -> PV (LocatedA b) mkHsLamCasePV :: SrcSpan -> (LocatedL [LMatch GhcPs (LocatedA b)]) -> [AddEpAnn] -> PV (LocatedA b) @@ -1563,21 +1563,21 @@ instance DisambECP (HsCmd GhcPs) where return $ L (noAnnSrcSpan l) (HsCmdLam NoExtField (mg cs)) mkHsLetPV l bs e anns = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (HsCmdLet (ApiAnn (spanAsAnchor l) anns cs) bs e) + return $ L (noAnnSrcSpan l) (HsCmdLet (EpAnn (spanAsAnchor l) anns cs) bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs superInfixOp m = m mkHsOpAppPV l c1 op c2 = do let cmdArg c = L (getLocA c) $ HsCmdTop noExtField c cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) $ HsCmdArrForm (ApiAnn (spanAsAnchor l) (AnnList Nothing Nothing Nothing [] []) cs) (reLocL op) Infix Nothing [cmdArg c1, cmdArg c2] + return $ L (noAnnSrcSpan l) $ HsCmdArrForm (EpAnn (spanAsAnchor l) (AnnList Nothing Nothing Nothing [] []) cs) (reLocL op) Infix Nothing [cmdArg c1, cmdArg c2] mkHsCasePV l c (L lm m) anns = do cs <- getCommentsFor l let mg = mkMatchGroup FromSource (L lm m) - return $ L (noAnnSrcSpan l) (HsCmdCase (ApiAnn (spanAsAnchor l) anns cs) c mg) + return $ L (noAnnSrcSpan l) (HsCmdCase (EpAnn (spanAsAnchor l) anns cs) c mg) mkHsLamCasePV l (L lm m) anns = do cs <- getCommentsFor l let mg = mkMatchGroup FromSource (L lm m) - return $ L (noAnnSrcSpan l) (HsCmdLamCase (ApiAnn (spanAsAnchor l) anns cs) mg) + return $ L (noAnnSrcSpan l) (HsCmdLamCase (EpAnn (spanAsAnchor l) anns cs) mg) type FunArg (HsCmd GhcPs) = HsExpr GhcPs superFunArg m = m mkHsAppPV l c e = do @@ -1589,14 +1589,14 @@ instance DisambECP (HsCmd GhcPs) where mkHsIfPV l c semi1 a semi2 b anns = do checkDoAndIfThenElse PsErrSemiColonsInCondCmd c semi1 a semi2 b cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (mkHsCmdIf c a b (ApiAnn (spanAsAnchor l) anns cs)) + return $ L (noAnnSrcSpan l) (mkHsCmdIf c a b (EpAnn (spanAsAnchor l) anns cs)) mkHsDoPV l Nothing stmts anns = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (HsCmdDo (ApiAnn (spanAsAnchor l) anns cs) stmts) + return $ L (noAnnSrcSpan l) (HsCmdDo (EpAnn (spanAsAnchor l) anns cs) stmts) mkHsDoPV l (Just m) _ _ = addFatalError $ PsError (PsErrQualifiedDoInCmd m) [] l mkHsParPV l c ann = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (HsCmdPar (ApiAnn (spanAsAnchor l) ann cs) c) + return $ L (noAnnSrcSpan l) (HsCmdPar (EpAnn (spanAsAnchor l) ann cs) c) mkHsVarPV (L l v) = cmdFail (locA l) (ppr v) mkHsLitPV (L l a) = cmdFail l (ppr a) mkHsOverLitPV (L l a) = cmdFail l (ppr a) @@ -1637,26 +1637,26 @@ instance DisambECP (HsExpr GhcPs) where ecpFromExp' = return mkHsProjUpdatePV l fields arg isPun anns = do cs <- getCommentsFor l - return $ mkRdrProjUpdate (noAnnSrcSpan l) fields arg isPun (ApiAnn (spanAsAnchor l) anns cs) + return $ mkRdrProjUpdate (noAnnSrcSpan l) fields arg isPun (EpAnn (spanAsAnchor l) anns cs) mkHsLamPV l mg = do cs <- getCommentsFor l return $ L (noAnnSrcSpan l) (HsLam NoExtField (mg cs)) mkHsLetPV l bs c anns = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (HsLet (ApiAnn (spanAsAnchor l) anns cs) bs c) + return $ L (noAnnSrcSpan l) (HsLet (EpAnn (spanAsAnchor l) anns cs) bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs superInfixOp m = m mkHsOpAppPV l e1 op e2 = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) $ OpApp (ApiAnn (spanAsAnchor l) [] cs) e1 (reLocL op) e2 + return $ L (noAnnSrcSpan l) $ OpApp (EpAnn (spanAsAnchor l) [] cs) e1 (reLocL op) e2 mkHsCasePV l e (L lm m) anns = do cs <- getCommentsFor l let mg = mkMatchGroup FromSource (L lm m) - return $ L (noAnnSrcSpan l) (HsCase (ApiAnn (spanAsAnchor l) anns cs) e mg) + return $ L (noAnnSrcSpan l) (HsCase (EpAnn (spanAsAnchor l) anns cs) e mg) mkHsLamCasePV l (L lm m) anns = do cs <- getCommentsFor l let mg = mkMatchGroup FromSource (L lm m) - return $ L (noAnnSrcSpan l) (HsLamCase (ApiAnn (spanAsAnchor l) anns cs) mg) + return $ L (noAnnSrcSpan l) (HsLamCase (EpAnn (spanAsAnchor l) anns cs) mg) type FunArg (HsExpr GhcPs) = HsExpr GhcPs superFunArg m = m mkHsAppPV l e1 e2 = do @@ -1670,13 +1670,13 @@ instance DisambECP (HsExpr GhcPs) where mkHsIfPV l c semi1 a semi2 b anns = do checkDoAndIfThenElse PsErrSemiColonsInCondExpr c semi1 a semi2 b cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (mkHsIf c a b (ApiAnn (spanAsAnchor l) anns cs)) + return $ L (noAnnSrcSpan l) (mkHsIf c a b (EpAnn (spanAsAnchor l) anns cs)) mkHsDoPV l mod stmts anns = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (HsDo (ApiAnn (spanAsAnchor l) anns cs) (DoExpr mod) stmts) + return $ L (noAnnSrcSpan l) (HsDo (EpAnn (spanAsAnchor l) anns cs) (DoExpr mod) stmts) mkHsParPV l e ann = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (HsPar (ApiAnn (spanAsAnchor l) ann cs) e) + return $ L (noAnnSrcSpan l) (HsPar (EpAnn (spanAsAnchor l) ann cs) e) mkHsVarPV v@(L l _) = return $ L (na2la l) (HsVar noExtField v) mkHsLitPV (L l a) = do cs <- getCommentsFor l @@ -1687,20 +1687,20 @@ instance DisambECP (HsExpr GhcPs) where mkHsWildCardPV l = return $ L l (hsHoleExpr noAnn) mkHsTySigPV l a sig anns = do cs <- getCommentsFor (locA l) - return $ L l (ExprWithTySig (ApiAnn (spanAsAnchor $ locA l) anns cs) a (hsTypeToHsSigWcType sig)) + return $ L l (ExprWithTySig (EpAnn (spanAsAnchor $ locA l) anns cs) a (hsTypeToHsSigWcType sig)) mkHsExplicitListPV l xs anns = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (ExplicitList (ApiAnn (spanAsAnchor l) anns cs) xs) + return $ L (noAnnSrcSpan l) (ExplicitList (EpAnn (spanAsAnchor l) anns cs) xs) mkHsSplicePV sp@(L l _) = do cs <- getCommentsFor l - return $ mapLoc (HsSpliceE (ApiAnn (spanAsAnchor l) NoApiAnns cs)) sp + return $ mapLoc (HsSpliceE (EpAnn (spanAsAnchor l) NoEpAnns cs)) sp mkHsRecordPV opts l lrec a (fbinds, ddLoc) anns = do cs <- getCommentsFor l - r <- mkRecConstrOrUpdate opts a lrec (fbinds, ddLoc) (ApiAnn (spanAsAnchor l) anns cs) + r <- mkRecConstrOrUpdate opts a lrec (fbinds, ddLoc) (EpAnn (spanAsAnchor l) anns cs) checkRecordSyntax (L (noAnnSrcSpan l) r) mkHsNegAppPV l a anns = do cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (NegApp (ApiAnn (spanAsAnchor l) anns cs) a noSyntaxExpr) + return $ L (noAnnSrcSpan l) (NegApp (EpAnn (spanAsAnchor l) anns cs) a noSyntaxExpr) mkHsSectionR_PV l op e = do cs <- getCommentsFor l return $ L l (SectionR (comment (realSrcSpan l) cs) op e) @@ -1719,7 +1719,7 @@ instance DisambECP (HsExpr GhcPs) where rejectPragmaPV (L l (HsPragE _ prag _)) = addError $ PsError (PsErrUnallowedPragma prag) [] (locA l) rejectPragmaPV _ = return () -hsHoleExpr :: ApiAnn' ApiAnnUnboundVar -> HsExpr GhcPs +hsHoleExpr :: EpAnn' EpAnnUnboundVar -> HsExpr GhcPs hsHoleExpr anns = HsUnboundVar anns (mkVarOcc "_") type instance Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) = SrcSpan @@ -1738,7 +1738,7 @@ instance DisambECP (PatBuilder GhcPs) where superInfixOp m = m mkHsOpAppPV l p1 op p2 = do cs <- getCommentsFor l - let anns = ApiAnn (spanAsAnchor l) [] cs + let anns = EpAnn (spanAsAnchor l) [] cs return $ L (noAnnSrcSpan l) $ PatBuilderOpApp p1 op p2 anns mkHsCasePV l _ _ _ = addFatalError $ PsError PsErrCaseInPat [] l mkHsLamCasePV l _ _ = addFatalError $ PsError PsErrLambdaCaseInPat [] l @@ -1758,11 +1758,11 @@ instance DisambECP (PatBuilder GhcPs) where mkHsTySigPV l b sig anns = do p <- checkLPat b cs <- getCommentsFor (locA l) - return $ L l (PatBuilderPat (SigPat (ApiAnn (spanAsAnchor $ locA l) anns cs) p (mkHsPatSigType sig))) + return $ L l (PatBuilderPat (SigPat (EpAnn (spanAsAnchor $ locA l) anns cs) p (mkHsPatSigType sig))) mkHsExplicitListPV l xs anns = do ps <- traverse checkLPat xs cs <- getCommentsFor l - return (L (noAnnSrcSpan l) (PatBuilderPat (ListPat (ApiAnn (spanAsAnchor l) anns cs) ps))) + return (L (noAnnSrcSpan l) (PatBuilderPat (ListPat (EpAnn (spanAsAnchor l) anns cs) ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) mkHsRecordPV _ l _ a (fbinds, ddLoc) anns = do let (fs, ps) = partitionEithers fbinds @@ -1770,32 +1770,32 @@ instance DisambECP (PatBuilder GhcPs) where then addFatalError $ PsError PsErrOverloadedRecordDotInvalid [] l else do cs <- getCommentsFor l - r <- mkPatRec a (mk_rec_fields fs ddLoc) (ApiAnn (spanAsAnchor l) anns cs) + r <- mkPatRec a (mk_rec_fields fs ddLoc) (EpAnn (spanAsAnchor l) anns cs) checkRecordSyntax (L (noAnnSrcSpan l) r) mkHsNegAppPV l (L lp p) anns = do lit <- case p of PatBuilderOverLit pos_lit -> return (L (locA lp) pos_lit) _ -> patFail l (text "-" <> ppr p) cs <- getCommentsFor l - let an = ApiAnn (spanAsAnchor l) anns cs + let an = EpAnn (spanAsAnchor l) anns cs return $ L (noAnnSrcSpan l) (PatBuilderPat (mkNPat lit (Just noSyntaxExpr) an)) mkHsSectionR_PV l op p = patFail l (pprInfixOcc (unLoc op) <> ppr p) mkHsViewPatPV l a b anns = do p <- checkLPat b cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (PatBuilderPat (ViewPat (ApiAnn (spanAsAnchor l) anns cs) a p)) + return $ L (noAnnSrcSpan l) (PatBuilderPat (ViewPat (EpAnn (spanAsAnchor l) anns cs) a p)) mkHsAsPatPV l v e a = do p <- checkLPat e cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (PatBuilderPat (AsPat (ApiAnn (spanAsAnchor l) a cs) v p)) + return $ L (noAnnSrcSpan l) (PatBuilderPat (AsPat (EpAnn (spanAsAnchor l) a cs) v p)) mkHsLazyPatPV l e a = do p <- checkLPat e cs <- getCommentsFor l - return $ L (noAnnSrcSpan l) (PatBuilderPat (LazyPat (ApiAnn (spanAsAnchor l) a cs) p)) + return $ L (noAnnSrcSpan l) (PatBuilderPat (LazyPat (EpAnn (spanAsAnchor l) a cs) p)) mkHsBangPatPV l e an = do p <- checkLPat e cs <- getCommentsFor l - let pb = BangPat (ApiAnn (spanAsAnchor l) an cs) p + let pb = BangPat (EpAnn (spanAsAnchor l) an cs) p hintBangPat l pb return $ L (noAnnSrcSpan l) (PatBuilderPat pb) mkSumOrTuplePV = mkSumOrTuplePat @@ -1811,7 +1811,7 @@ checkUnboxedStringLitPat (L loc lit) = mkPatRec :: LocatedA (PatBuilder GhcPs) -> HsRecFields GhcPs (LocatedA (PatBuilder GhcPs)) -> - ApiAnn -> + EpAnn -> PV (PatBuilder GhcPs) mkPatRec (unLoc -> PatBuilderVar c) (HsRecFields fs dd) anns | isRdrDataCon (unLoc c) @@ -2377,7 +2377,7 @@ mkRecConstrOrUpdate -> LHsExpr GhcPs -> SrcSpan -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) - -> ApiAnn + -> EpAnn -> PV (HsExpr GhcPs) mkRecConstrOrUpdate _ (L _ (HsVar _ (L l c))) _lrec (fbinds,dd) anns | isRdrDataCon c @@ -2390,7 +2390,7 @@ mkRecConstrOrUpdate overloaded_update exp _ (fs,dd) anns | Just dd_loc <- dd = addFatalError $ PsError PsErrDotsInRecordUpdate [] dd_loc | otherwise = mkRdrRecordUpd overloaded_update exp fs anns -mkRdrRecordUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> ApiAnn -> PV (HsExpr GhcPs) +mkRdrRecordUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> EpAnn -> PV (HsExpr GhcPs) mkRdrRecordUpd overloaded_on exp@(L loc _) fbinds anns = do -- We do not need to know if OverloadedRecordDot is in effect. We do -- however need to know if OverloadedRecordUpdate (passed in @@ -2443,7 +2443,7 @@ mkRdrRecordUpd overloaded_on exp@(L loc _) fbinds anns = do punnedVar f = if not pun then arg else noLocA . HsVar noExtField . noLocA . mkRdrUnqual . mkVarOccFS $ f mkRdrRecordCon - :: LocatedN RdrName -> HsRecordBinds GhcPs -> ApiAnn -> HsExpr GhcPs + :: LocatedN RdrName -> HsRecordBinds GhcPs -> EpAnn -> HsExpr GhcPs mkRdrRecordCon con flds anns = RecordCon { rcon_ext = anns, rcon_con = con, rcon_flds = flds } @@ -2482,7 +2482,7 @@ mkInlinePragma src (inl, match_info) mb_act mkImport :: Located CCallConv -> Located Safety -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs) - -> P (ApiAnn -> HsDecl GhcPs) + -> P (EpAnn -> HsDecl GhcPs) mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) = case unLoc cconv of CCallConv -> mkCImport @@ -2583,7 +2583,7 @@ parseCImport cconv safety nm str sourceText = -- mkExport :: Located CCallConv -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs) - -> P (ApiAnn -> HsDecl GhcPs) + -> P (EpAnn -> HsDecl GhcPs) mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty) = return $ \ann -> ForD noExtField $ ForeignExport { fd_e_ext = ann, fd_name = v, fd_sig_ty = ty @@ -2617,7 +2617,7 @@ data ImpExpQcSpec = ImpExpQcName (LocatedN RdrName) mkModuleImpExp :: [AddEpAnn] -> LocatedA ImpExpQcSpec -> ImpExpSubSpec -> P (IE GhcPs) mkModuleImpExp anns (L l specname) subs = do cs <- getCommentsFor (locA l) -- AZ: IEVar can discard comments - let ann = ApiAnn (spanAsAnchor $ locA l) anns cs + let ann = EpAnn (spanAsAnchor $ locA l) anns cs case subs of ImpExpAbs | isVarNameSpace (rdrNameSpace name) @@ -2883,9 +2883,9 @@ mkSumOrTupleExpr :: SrcSpanAnnA -> Boxity -> SumOrTuple (HsExpr GhcPs) -- Tuple mkSumOrTupleExpr l boxity (Tuple es) anns = do cs <- getCommentsFor (locA l) - return $ L l (ExplicitTuple (ApiAnn (spanAsAnchor $ locA l) anns cs) (map toTupArg es) boxity) + return $ L l (ExplicitTuple (EpAnn (spanAsAnchor $ locA l) anns cs) (map toTupArg es) boxity) where - toTupArg :: Either (ApiAnn' AnnAnchor) (LHsExpr GhcPs) -> HsTupArg GhcPs + toTupArg :: Either (EpAnn' AnnAnchor) (LHsExpr GhcPs) -> HsTupArg GhcPs toTupArg (Left ann) = missingTupArg ann toTupArg (Right a) = Present noAnn a @@ -2898,7 +2898,7 @@ mkSumOrTupleExpr l Unboxed (Sum alt arity e barsp barsa) anns = do AnnExplicitSum o barsp barsa c _ -> panic "mkSumOrTupleExpr" cs <- getCommentsFor (locA l) - return $ L l (ExplicitSum (ApiAnn (spanAsAnchor $ locA l) an cs) alt arity e) + return $ L l (ExplicitSum (EpAnn (spanAsAnchor $ locA l) an cs) alt arity e) mkSumOrTupleExpr l Boxed a@Sum{} _ = addFatalError $ PsError (PsErrUnsupportedBoxedSumExpr a) [] (locA l) @@ -2910,9 +2910,9 @@ mkSumOrTuplePat mkSumOrTuplePat l boxity (Tuple ps) anns = do ps' <- traverse toTupPat ps cs <- getCommentsFor (locA l) - return $ L l (PatBuilderPat (TuplePat (ApiAnn (spanAsAnchor $ locA l) anns cs) ps' boxity)) + return $ L l (PatBuilderPat (TuplePat (EpAnn (spanAsAnchor $ locA l) anns cs) ps' boxity)) where - toTupPat :: Either (ApiAnn' AnnAnchor) (LocatedA (PatBuilder GhcPs)) -> PV (LPat GhcPs) + toTupPat :: Either (EpAnn' AnnAnchor) (LocatedA (PatBuilder GhcPs)) -> PV (LPat GhcPs) -- Ignore the element location so that the error message refers to the -- entire tuple. See #19504 (and the discussion) for details. toTupPat p = case p of @@ -2923,7 +2923,7 @@ mkSumOrTuplePat l boxity (Tuple ps) anns = do mkSumOrTuplePat l Unboxed (Sum alt arity p barsb barsa) anns = do p' <- checkLPat p cs <- getCommentsFor (locA l) - let an = ApiAnn (spanAsAnchor $ locA l) (ApiAnnSumPat anns barsb barsa) cs + let an = EpAnn (spanAsAnchor $ locA l) (EpAnnSumPat anns barsb barsa) cs return $ L l (PatBuilderPat (SumPat an p' alt arity)) mkSumOrTuplePat l Boxed a@Sum{} _ = addFatalError $ PsError (PsErrUnsupportedBoxedSumPat a) [] (locA l) @@ -2950,7 +2950,7 @@ starSym False = "*" -- Bits and pieces for RecordDotSyntax. mkRdrGetField :: SrcSpanAnnA -> LHsExpr GhcPs -> Located (HsFieldLabel GhcPs) - -> ApiAnnCO -> LHsExpr GhcPs + -> EpAnnCO -> LHsExpr GhcPs mkRdrGetField loc arg field anns = L loc HsGetField { gf_ext = anns @@ -2958,7 +2958,7 @@ mkRdrGetField loc arg field anns = , gf_field = field } -mkRdrProjection :: [Located (HsFieldLabel GhcPs)] -> ApiAnn' AnnProjection -> HsExpr GhcPs +mkRdrProjection :: [Located (HsFieldLabel GhcPs)] -> EpAnn' AnnProjection -> HsExpr GhcPs mkRdrProjection [] _ = panic "mkRdrProjection: The impossible has happened!" mkRdrProjection flds anns = HsProjection { @@ -2967,7 +2967,7 @@ mkRdrProjection flds anns = } mkRdrProjUpdate :: SrcSpanAnnA -> Located [Located (HsFieldLabel GhcPs)] - -> LHsExpr GhcPs -> Bool -> ApiAnn + -> LHsExpr GhcPs -> Bool -> EpAnn -> LHsRecProj GhcPs (LHsExpr GhcPs) mkRdrProjUpdate _ (L _ []) _ _ _ = panic "mkRdrProjUpdate: The impossible has happened!" mkRdrProjUpdate loc (L l flds) arg isPun anns = diff --git a/compiler/GHC/Parser/Types.hs b/compiler/GHC/Parser/Types.hs index 843685ea36..5c3ff72597 100644 --- a/compiler/GHC/Parser/Types.hs +++ b/compiler/GHC/Parser/Types.hs @@ -28,7 +28,7 @@ import Language.Haskell.Syntax data SumOrTuple b = Sum ConTag Arity (LocatedA b) [AnnAnchor] [AnnAnchor] -- ^ Last two are the locations of the '|' before and after the payload - | Tuple [Either (ApiAnn' AnnAnchor) (LocatedA b)] + | Tuple [Either (EpAnn' AnnAnchor) (LocatedA b)] pprSumOrTuple :: Outputable b => Boxity -> SumOrTuple b -> SDoc pprSumOrTuple boxity = \case @@ -56,7 +56,7 @@ data PatBuilder p | PatBuilderApp (LocatedA (PatBuilder p)) (LocatedA (PatBuilder p)) | PatBuilderAppType (LocatedA (PatBuilder p)) SrcSpan (HsPatSigType GhcPs) | PatBuilderOpApp (LocatedA (PatBuilder p)) (LocatedN RdrName) - (LocatedA (PatBuilder p)) ApiAnn + (LocatedA (PatBuilder p)) EpAnn | PatBuilderVar (LocatedN RdrName) | PatBuilderOverLit (HsOverLit GhcPs) diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs index 26af5166ff..8833abe03d 100644 --- a/compiler/GHC/Tc/Module.hs +++ b/compiler/GHC/Tc/Module.hs @@ -2929,7 +2929,7 @@ tcDump env full_dump = pprLHsBinds (tcg_binds env) -- NB: foreign x-d's have undefined's in their types; -- hence can't show the tc_fords - ast_dump = showAstData NoBlankSrcSpan NoBlankApiAnnotations (tcg_binds env) + ast_dump = showAstData NoBlankSrcSpan NoBlankEpAnnotations (tcg_binds env) -- It's unpleasant having both pprModGuts and pprModDetails here pprTcGblEnv :: TcGblEnv -> SDoc diff --git a/compiler/GHC/ThToHs.hs b/compiler/GHC/ThToHs.hs index 63055bbd48..77c436c912 100644 --- a/compiler/GHC/ThToHs.hs +++ b/compiler/GHC/ThToHs.hs @@ -131,7 +131,7 @@ returnL :: a -> CvtM (Located a) returnL x = CvtM (\_ loc -> Right (loc, L loc x)) -- returnLA :: a -> CvtM (LocatedA a) -returnLA :: e -> CvtM (GenLocated (SrcSpanAnn' (ApiAnn' ann)) e) +returnLA :: e -> CvtM (GenLocated (SrcSpanAnn' (EpAnn' ann)) e) returnLA x = CvtM (\_ loc -> Right (loc, L (noAnnSrcSpan loc) x)) returnJustLA :: a -> CvtM (Maybe (LocatedA a)) |