summaryrefslogtreecommitdiff
path: root/compiler/GHC
diff options
context:
space:
mode:
authorAlan Zimmerman <alan.zimm@gmail.com>2021-03-25 21:38:13 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-03-31 11:13:28 -0400
commitd03005e642710d0f1f78757292e0fe65287e5f0a (patch)
tree2bd2c11a00577649ac19ddc6aa9705efa19bc8e5 /compiler/GHC
parent0fe5175ac537c0ce2afe969ec82a0d1c73a4ae38 (diff)
downloadhaskell-d03005e642710d0f1f78757292e0fe65287e5f0a.tar.gz
EPA : rename 'api annotations' to 'exact print annotations'
In comments, and notes. Follow-up from !2418, see #19579
Diffstat (limited to 'compiler/GHC')
-rw-r--r--compiler/GHC/Core/Class.hs2
-rw-r--r--compiler/GHC/Core/DataCon.hs2
-rw-r--r--compiler/GHC/Hs.hs8
-rw-r--r--compiler/GHC/Hs/ImpExp.hs16
-rw-r--r--compiler/GHC/Hs/Type.hs4
-rw-r--r--compiler/GHC/Parser.y2
-rw-r--r--compiler/GHC/Parser/Annotation.hs26
-rw-r--r--compiler/GHC/Parser/Lexer.x2
-rw-r--r--compiler/GHC/Parser/PostProcess.hs6
-rw-r--r--compiler/GHC/Types/Basic.hs2
-rw-r--r--compiler/GHC/Types/ForeignCall.hs2
-rw-r--r--compiler/GHC/Types/Name/Reader.hs2
12 files changed, 37 insertions, 37 deletions
diff --git a/compiler/GHC/Core/Class.hs b/compiler/GHC/Core/Class.hs
index 57e6defca6..dfb651c279 100644
--- a/compiler/GHC/Core/Class.hs
+++ b/compiler/GHC/Core/Class.hs
@@ -80,7 +80,7 @@ data Class
--
-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow'',
--- For details on above see note [Api annotations] in GHC.Parser.Annotation
+-- For details on above see note [exact print annotations] in GHC.Parser.Annotation
type FunDep a = ([a],[a])
type ClassOpItem = (Id, DefMethInfo)
diff --git a/compiler/GHC/Core/DataCon.hs b/compiler/GHC/Core/DataCon.hs
index 3239c80b2e..1c7b83b475 100644
--- a/compiler/GHC/Core/DataCon.hs
+++ b/compiler/GHC/Core/DataCon.hs
@@ -308,7 +308,7 @@ Note that (Foo a) might not be an instance of Ord.
-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
-- 'GHC.Parser.Annotation.AnnClose','GHC.Parser.Annotation.AnnComma'
--- For details on above see note [Api annotations] in GHC.Parser.Annotation
+-- For details on above see note [exact print annotations] in GHC.Parser.Annotation
data DataCon
= MkData {
dcName :: Name, -- This is the name of the *source data con*
diff --git a/compiler/GHC/Hs.hs b/compiler/GHC/Hs.hs
index 8b645ac5fc..17825119e7 100644
--- a/compiler/GHC/Hs.hs
+++ b/compiler/GHC/Hs.hs
@@ -89,7 +89,7 @@ data HsModule
-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen'
-- ,'GHC.Parser.Annotation.AnnClose'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
hsmodImports :: [LImportDecl GhcPs],
-- ^ We snaffle interesting stuff out of the imported interfaces early
-- on, adding that info to TyDecls/etc; so this list is often empty,
@@ -103,14 +103,14 @@ data HsModule
-- ,'GHC.Parser.Annotation.AnnClose'
--
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
hsmodHaddockModHeader :: Maybe LHsDocString
-- ^ Haddock module info and description, unparsed
--
-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen'
-- ,'GHC.Parser.Annotation.AnnClose'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
}
-- ^ 'GHC.Parser.Annotation.AnnKeywordId's
--
@@ -120,7 +120,7 @@ data HsModule
-- 'GHC.Parser.Annotation.AnnClose' for explicit braces and semi around
-- hsmodImports,hsmodDecls if this style is used.
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
deriving instance Data HsModule
diff --git a/compiler/GHC/Hs/ImpExp.hs b/compiler/GHC/Hs/ImpExp.hs
index 309d0d8c62..2622f243ae 100644
--- a/compiler/GHC/Hs/ImpExp.hs
+++ b/compiler/GHC/Hs/ImpExp.hs
@@ -51,7 +51,7 @@ type LImportDecl pass = XRec pass (ImportDecl pass)
--
-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
type instance Anno (ImportDecl (GhcPass p)) = SrcSpanAnnA
-- | If/how an import is 'qualified'.
@@ -111,7 +111,7 @@ data ImportDecl pass
-- 'GHC.Parser.Annotation.AnnClose' attached
-- to location in ideclHiding
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
type instance XCImportDecl GhcPs = EpAnn' EpAnnImportDecl
type instance XCImportDecl GhcRn = NoExtField
@@ -217,7 +217,7 @@ data IEWrappedName name
-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnType',
-- 'GHC.Parser.Annotation.AnnPattern'
type LIEWrappedName name = LocatedA (IEWrappedName name)
--- For details on above see note [Api annotations] in GHC.Parser.Annotation
+-- For details on above see note [exact print annotations] in GHC.Parser.Annotation
-- | Located Import or Export
@@ -226,7 +226,7 @@ type LIE pass = XRec pass (IE pass)
--
-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
type instance Anno (IE (GhcPass p)) = SrcSpanAnnA
-- | Imported or exported entity.
@@ -241,7 +241,7 @@ data IE pass
-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnPattern',
-- 'GHC.Parser.Annotation.AnnType','GHC.Parser.Annotation.AnnVal'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
-- See Note [Located RdrNames] in GHC.Hs.Expr
| IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass))
-- ^ Imported or exported Thing with All imported or exported
@@ -252,7 +252,7 @@ data IE pass
-- 'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnClose',
-- 'GHC.Parser.Annotation.AnnType'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
-- See Note [Located RdrNames] in GHC.Hs.Expr
| IEThingWith (XIEThingWith pass)
@@ -268,7 +268,7 @@ data IE pass
-- 'GHC.Parser.Annotation.AnnComma',
-- 'GHC.Parser.Annotation.AnnType'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
| IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName)
-- ^ Imported or exported module contents
--
@@ -276,7 +276,7 @@ data IE pass
--
-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnModule'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- For details on above see note [exact print annotations] in GHC.Parser.Annotation
| IEGroup (XIEGroup pass) Int HsDocString -- ^ Doc section heading
| IEDoc (XIEDoc pass) HsDocString -- ^ Some documentation
| IEDocNamed (XIEDocNamed pass) String -- ^ Reference to named doc
diff --git a/compiler/GHC/Hs/Type.hs b/compiler/GHC/Hs/Type.hs
index ba07ad35b7..9c494d6aa7 100644
--- a/compiler/GHC/Hs/Type.hs
+++ b/compiler/GHC/Hs/Type.hs
@@ -483,12 +483,12 @@ splitHsFunType ty = go ty
= let
(anns, cs, args, res) = splitHsFunType ty
anns' = anns ++ annParen2AddEpAnn an
- cs' = cs S.<> apiAnnComments (ann l) S.<> apiAnnComments an
+ cs' = cs S.<> epAnnComments (ann l) S.<> epAnnComments an
in (anns', cs', args, res)
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)
+ = (anns, csy S.<> epAnnComments (ann ll), HsScaled mult x':args, res)
where
(L (SrcSpanAnn a l) t) = x
an' = addTrailingAnnToA l an cs a
diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y
index 19b5642ff0..478e2d27d5 100644
--- a/compiler/GHC/Parser.y
+++ b/compiler/GHC/Parser.y
@@ -4140,7 +4140,7 @@ reportEmptyDoubleQuotes span = do
%* *
%************************************************************************
-For the general principles of the following routines, see Note [Api annotations]
+For the general principles of the following routines, see Note [exact print annotations]
in GHC.Parser.Annotation
-}
diff --git a/compiler/GHC/Parser/Annotation.hs b/compiler/GHC/Parser/Annotation.hs
index 6acb712833..23b0864246 100644
--- a/compiler/GHC/Parser/Annotation.hs
+++ b/compiler/GHC/Parser/Annotation.hs
@@ -57,9 +57,9 @@ module GHC.Parser.Annotation (
-- ** Querying annotations
getLocAnn,
- apiAnnAnns, apiAnnAnnsL,
+ epAnnAnns, epAnnAnnsL,
annParen2AddEpAnn,
- apiAnnComments,
+ epAnnComments,
-- ** Working with locations of annotations
sortLocatedA,
@@ -95,7 +95,7 @@ import GHC.Utils.Outputable hiding ( (<>) )
import GHC.Utils.Panic
{-
-Note [Api annotations]
+Note [exact print annotations]
~~~~~~~~~~~~~~~~~~~~~~
Given a parse tree of a Haskell module, how can we reconstruct
the original Haskell source code, retaining all whitespace and
@@ -195,7 +195,7 @@ https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations
--
-- Note: in general the names of these are taken from the
-- corresponding token, unless otherwise noted
--- See note [Api annotations] above for details of the usage
+-- See note [exact print annotations] above for details of the usage
data AnnKeywordId
= AnnAnyclass
| AnnAs
@@ -967,13 +967,13 @@ 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 :: EpAnn' a -> [a]
-apiAnnAnnsL EpAnnNotUsed = []
-apiAnnAnnsL (EpAnn _ anns _) = [anns]
+epAnnAnnsL :: EpAnn' a -> [a]
+epAnnAnnsL EpAnnNotUsed = []
+epAnnAnnsL (EpAnn _ anns _) = [anns]
-apiAnnAnns :: EpAnn -> [AddEpAnn]
-apiAnnAnns EpAnnNotUsed = []
-apiAnnAnns (EpAnn _ anns _) = anns
+epAnnAnns :: EpAnn -> [AddEpAnn]
+epAnnAnns EpAnnNotUsed = []
+epAnnAnns (EpAnn _ anns _) = anns
annParen2AddEpAnn :: EpAnn' AnnParen -> [AddEpAnn]
annParen2AddEpAnn EpAnnNotUsed = []
@@ -982,9 +982,9 @@ annParen2AddEpAnn (EpAnn _ (AnnParen pt o c) _)
where
(ai,ac) = parenTypeKws pt
-apiAnnComments :: EpAnn' an -> EpAnnComments
-apiAnnComments EpAnnNotUsed = AnnComments []
-apiAnnComments (EpAnn _ _ cs) = cs
+epAnnComments :: EpAnn' an -> EpAnnComments
+epAnnComments EpAnnNotUsed = AnnComments []
+epAnnComments (EpAnn _ _ cs) = cs
-- ---------------------------------------------------------------------
-- sortLocatedA :: [LocatedA a] -> [LocatedA a]
diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x
index 125e6aaaf6..be99757176 100644
--- a/compiler/GHC/Parser/Lexer.x
+++ b/compiler/GHC/Parser/Lexer.x
@@ -2346,7 +2346,7 @@ data PState = PState {
-- The next three are used to implement Annotations giving the
-- locations of 'noise' tokens in the source, so that users of
-- the GHC API can do source to source conversions.
- -- See note [Api annotations] in GHC.Parser.Annotation
+ -- See note [exact print annotations] in GHC.Parser.Annotation
eof_pos :: Maybe (RealSrcSpan, RealSrcSpan), -- pos, gap to prior token
header_comments :: Maybe [LAnnotationComment],
comment_q :: [LAnnotationComment],
diff --git a/compiler/GHC/Parser/PostProcess.hs b/compiler/GHC/Parser/PostProcess.hs
index d6248bd107..18881dbe4c 100644
--- a/compiler/GHC/Parser/PostProcess.hs
+++ b/compiler/GHC/Parser/PostProcess.hs
@@ -713,7 +713,7 @@ mkGadtDecl loc names ty annsIn = do
= let
an' = addTrailingAnnToL (locA loc') (anns af) (comments af) an
in ( RecConGADT (L (SrcSpanAnn an' (locA loc')) rf), res_ty
- , [], apiAnnComments (ann ll))
+ , [], epAnnComments (ann ll))
| otherwise
= let (anns, cs, arg_types, res_type) = splitHsFunType body_ty
in (PrefixConGADT arg_types, res_type, anns, cs)
@@ -839,7 +839,7 @@ checkTyVars pp_what equals_or_where tc tparms
chkParens :: [AddEpAnn] -> EpAnnComments -> LHsType GhcPs
-> P (LHsTyVarBndr () GhcPs, [AddEpAnn])
chkParens acc cs (L l (HsParTy an ty))
- = chkParens (mkParensEpAnn (locA l) ++ acc) (cs Semi.<> apiAnnComments an) ty
+ = chkParens (mkParensEpAnn (locA l) ++ acc) (cs Semi.<> epAnnComments an) ty
chkParens acc cs ty = do
tv <- chk acc cs ty
return (tv, reverse acc)
@@ -1329,7 +1329,7 @@ addUnpackednessP (L lprag (UnpackednessPragma anns prag unpk)) ty = do
-- Otherwise, wrap the type in a new HsBangTy constructor.
addUnpackedness an (L _ (HsBangTy x bang t))
| HsSrcBang NoSourceText NoSrcUnpack strictness <- bang
- = HsBangTy (addAnns an (apiAnnAnns x) (apiAnnComments x)) (HsSrcBang prag unpk strictness) t
+ = HsBangTy (addAnns an (epAnnAnns x) (epAnnComments x)) (HsSrcBang prag unpk strictness) t
addUnpackedness an t
= HsBangTy an (HsSrcBang prag unpk NoSrcStrict) t
diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs
index c1947fab17..f8725bf8fc 100644
--- a/compiler/GHC/Types/Basic.hs
+++ b/compiler/GHC/Types/Basic.hs
@@ -580,7 +580,7 @@ instance Outputable Origin where
-- @'\{-\# INCOHERENT'@,
-- 'GHC.Parser.Annotation.AnnClose' @`\#-\}`@,
--- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
+-- For details on above see note [exact print annotations] in "GHC.Parser.Annotation"
data OverlapFlag = OverlapFlag
{ overlapMode :: OverlapMode
, isSafeOverlap :: Bool
diff --git a/compiler/GHC/Types/ForeignCall.hs b/compiler/GHC/Types/ForeignCall.hs
index ac24d4ea4d..0c9032af91 100644
--- a/compiler/GHC/Types/ForeignCall.hs
+++ b/compiler/GHC/Types/ForeignCall.hs
@@ -241,7 +241,7 @@ instance Outputable Header where
-- 'GHC.Parser.Annotation.AnnHeader','GHC.Parser.Annotation.AnnVal',
-- 'GHC.Parser.Annotation.AnnClose' @'\#-}'@,
--- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
+-- For details on above see note [exact print annotations] in "GHC.Parser.Annotation"
data CType = CType SourceText -- Note [Pragma source text] in GHC.Types.SourceText
(Maybe Header) -- header to include for this type
(SourceText,FastString) -- the type itself
diff --git a/compiler/GHC/Types/Name/Reader.hs b/compiler/GHC/Types/Name/Reader.hs
index a4ec4bea8d..c14a0865ee 100644
--- a/compiler/GHC/Types/Name/Reader.hs
+++ b/compiler/GHC/Types/Name/Reader.hs
@@ -127,7 +127,7 @@ import Data.List( sortBy )
-- 'GHC.Parser.Annotation.AnnVal'
-- 'GHC.Parser.Annotation.AnnTilde',
--- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
+-- For details on above see note [exact print annotations] in "GHC.Parser.Annotation"
data RdrName
= Unqual OccName
-- ^ Unqualified name