diff options
Diffstat (limited to 'compiler/GHC/Hs')
-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 |
9 files changed, 217 insertions, 217 deletions
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 |