diff options
author | Alan Zimmerman <alan.zimm@gmail.com> | 2021-03-25 21:38:13 +0000 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2021-03-29 16:17:36 -0400 |
commit | 2930ce79ccd1629999696d902441e995881b4e7e (patch) | |
tree | d57c27e9f3c99254ca78a8a13dd65858f12592ee | |
parent | ac36a3aa50e8eda602a102b0512971ca1ced029f (diff) | |
download | haskell-2930ce79ccd1629999696d902441e995881b4e7e.tar.gz |
EPA : rename 'api annotations' to 'exact print annotations'
In comments, and notes.
Follow-up from !2418, see #19579
(cherry picked from commit 4241899c2013bdf3187cbfa9d646346c120e0d57)
-rw-r--r-- | compiler/GHC.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Core/Class.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Core/DataCon.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Hs.hs | 8 | ||||
-rw-r--r-- | compiler/GHC/Hs/ImpExp.hs | 16 | ||||
-rw-r--r-- | compiler/GHC/Hs/Type.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Parser.y | 2 | ||||
-rw-r--r-- | compiler/GHC/Parser/Annotation.hs | 26 | ||||
-rw-r--r-- | compiler/GHC/Parser/Lexer.x | 2 | ||||
-rw-r--r-- | compiler/GHC/Parser/PostProcess.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Types/Basic.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Types/ForeignCall.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Types/Name/Reader.hs | 2 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Binds.hs | 26 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Decls.hs | 59 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Expr.hs | 102 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Extension.hs | 7 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Pat.hs | 24 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Type.hs | 50 | ||||
-rw-r--r-- | utils/check-exact/ExactPrint.hs | 10 | ||||
-rw-r--r-- | utils/check-exact/Transform.hs | 10 | ||||
-rw-r--r-- | utils/check-ppr/Main.hs | 2 |
22 files changed, 182 insertions, 184 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs index 0c55bfbea1..546d610737 100644 --- a/compiler/GHC.hs +++ b/compiler/GHC.hs @@ -1114,7 +1114,7 @@ parseModule ms = do let hsc_env_tmp = hsc_env { hsc_dflags = ms_hspp_opts ms } hpm <- liftIO $ hscParse hsc_env_tmp ms return (ParsedModule ms (hpm_module hpm) (hpm_src_files hpm)) - -- See Note [Api annotations] in GHC.Parser.Annotation + -- See Note [exact print annotations] in GHC.Parser.Annotation -- | Typecheck and rename a parsed module. -- 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 4d13294514..8868852bf7 100644 --- a/compiler/GHC/Hs/Type.hs +++ b/compiler/GHC/Hs/Type.hs @@ -485,12 +485,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 969e311a95..123b0914dd 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 diff --git a/compiler/Language/Haskell/Syntax/Binds.hs b/compiler/Language/Haskell/Syntax/Binds.hs index 3a369fd37e..ed093f9f68 100644 --- a/compiler/Language/Haskell/Syntax/Binds.hs +++ b/compiler/Language/Haskell/Syntax/Binds.hs @@ -201,7 +201,7 @@ data HsBindLR idL idR -- - 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnWhere', -- '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 FunBind { fun_ext :: XFunBind idL idR, @@ -242,7 +242,7 @@ data HsBindLR idL idR -- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnWhere', -- '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 | PatBind { pat_ext :: XPatBind idL idR, -- ^ See Note [Bind free vars] pat_lhs :: LPat idL, @@ -293,7 +293,7 @@ data HsBindLR idL idR -- 'GHC.Parser.Annotation.AnnWhere' -- '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 | XHsBindsLR !(XXHsBindsLR idL idR) @@ -327,7 +327,7 @@ data ABExport p -- 'GHC.Parser.Annotation.AnnWhere','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 -- | Pattern Synonym binding data PatSynBind idL idR @@ -597,7 +597,7 @@ type LIPBind id = XRec id (IPBind id) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' when in a -- list --- 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 -- | Implicit parameter bindings. -- @@ -608,7 +608,7 @@ type LIPBind id = XRec id (IPBind id) -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual' --- 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 IPBind id = IPBind (XCIPBind id) @@ -649,7 +649,7 @@ data Sig pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon', -- '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 TypeSig (XTypeSig pass) [LIdP pass] -- LHS of the signature; e.g. f,g,h :: blah @@ -663,7 +663,7 @@ data Sig pass -- 'GHC.Parser.Annotation.AnnDcolon','GHC.Parser.Annotation.AnnForall' -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDarrow' - -- 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 | PatSynSig (XPatSynSig pass) [LIdP pass] (LHsSigType pass) -- P :: forall a b. Req => Prov => ty @@ -694,7 +694,7 @@ data Sig pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnInfix', -- '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 | FixSig (XFixSig pass) (FixitySig pass) -- | An inline pragma @@ -707,7 +707,7 @@ data Sig pass -- 'GHC.Parser.Annotation.AnnVal','GHC.Parser.Annotation.AnnTilde', -- '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 | InlineSig (XInlineSig pass) (LIdP pass) -- Function name InlinePragma -- Never defaultInlinePragma @@ -723,7 +723,7 @@ data Sig pass -- 'GHC.Parser.Annotation.AnnClose' @']'@ and @'\#-}'@, -- 'GHC.Parser.Annotation.AnnDcolon' - -- 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 | SpecSig (XSpecSig pass) (LIdP pass) -- Specialise a function or datatype ... [LHsSigType pass] -- ... to these types @@ -741,7 +741,7 @@ data Sig pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen', -- 'GHC.Parser.Annotation.AnnInstance','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 | SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass) -- Note [Pragma source text] in GHC.Types.SourceText @@ -753,7 +753,7 @@ data Sig pass -- 'GHC.Parser.Annotation.AnnVbar','GHC.Parser.Annotation.AnnComma', -- '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 | MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (LIdP pass)) -- Note [Pragma source text] in GHC.Types.SourceText diff --git a/compiler/Language/Haskell/Syntax/Decls.hs b/compiler/Language/Haskell/Syntax/Decls.hs index 81369c3b09..1e8a8d2609 100644 --- a/compiler/Language/Haskell/Syntax/Decls.hs +++ b/compiler/Language/Haskell/Syntax/Decls.hs @@ -134,7 +134,7 @@ type LHsDecl p = XRec p (HsDecl p) -- - '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 -- | A Haskell Declaration data HsDecl p @@ -402,7 +402,7 @@ data TyClDecl pass -- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnRarrow', -- 'GHC.Parser.Annotation.AnnVbar' - -- 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 FamDecl { tcdFExt :: XFamDecl pass, tcdFam :: FamilyDecl pass } | -- | @type@ declaration @@ -410,7 +410,7 @@ data TyClDecl pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType', -- 'GHC.Parser.Annotation.AnnEqual', - -- 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 SynDecl { tcdSExt :: XSynDecl pass -- ^ Post renameer, FVs , tcdLName :: LIdP pass -- ^ Type constructor , tcdTyVars :: LHsQTyVars pass -- ^ Type variables; for an @@ -427,7 +427,7 @@ data TyClDecl pass -- 'GHC.Parser.Annotation.AnnNewType','GHC.Parser.Annotation.AnnDcolon' -- 'GHC.Parser.Annotation.AnnWhere', - -- 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 DataDecl { tcdDExt :: XDataDecl pass -- ^ Post renamer, CUSK flag, FVs , tcdLName :: LIdP pass -- ^ Type constructor , tcdTyVars :: LHsQTyVars pass -- ^ Type variables @@ -454,7 +454,7 @@ data TyClDecl pass -- 'GHC.Parser.Annotation.AnnComma' -- '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 | XTyClDecl !(XXTyClDecl pass) data FunDep pass @@ -799,14 +799,14 @@ data FamilyResultSig pass = -- see Note [FamilyResultSig] NoSig (XNoSig pass) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 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 | KindSig (XCKindSig pass) (LHsKind pass) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnOpenP','GHC.Parser.Annotation.AnnDcolon', -- 'GHC.Parser.Annotation.AnnCloseP' - -- 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 | TyVarSig (XTyVarSig pass) (LHsTyVarBndr () pass) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : @@ -814,7 +814,7 @@ data FamilyResultSig pass = -- see Note [FamilyResultSig] -- 'GHC.Parser.Annotation.AnnCloseP', 'GHC.Parser.Annotation.AnnEqual' | XFamilyResultSig !(XXFamilyResultSig pass) - -- 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 type Family Declaration @@ -840,7 +840,7 @@ data FamilyDecl pass = FamilyDecl -- 'GHC.Parser.Annotation.AnnEqual', 'GHC.Parser.Annotation.AnnRarrow', -- 'GHC.Parser.Annotation.AnnVbar' - -- 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 Injectivity Annotation @@ -860,7 +860,7 @@ data InjectivityAnn pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnRarrow', 'GHC.Parser.Annotation.AnnVbar' - -- 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 | XInjectivityAnn !(XXInjectivityAnn pass) data FamilyInfo pass @@ -920,7 +920,7 @@ data HsDataDefn pass -- The payload of a data type defn dd_derivs :: HsDeriving pass -- ^ Optional 'deriving' clause - -- 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 } | XHsDataDefn !(XXHsDataDefn pass) @@ -940,7 +940,7 @@ type LHsDerivingClause pass = XRec pass (HsDerivingClause pass) -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnDeriving', 'GHC.Parser.Annotation.AnnStock', --- 'GHC.Parser.Annotation.AnnAnyClass', 'Api.AnnNewtype', +-- 'GHC.Parser.Annotation.AnnAnyClass', 'GHC.Parser.Annotation.AnnNewtype', -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose' data HsDerivingClause pass -- See Note [Deriving strategies] in GHC.Tc.Deriv @@ -1023,7 +1023,7 @@ type LConDecl pass = XRec pass (ConDecl pass) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' when -- in a GADT constructor list - -- 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 -- | -- @@ -1047,7 +1047,7 @@ type LConDecl pass = XRec pass (ConDecl pass) -- 'GHC.Parser.Annotation.AnnDarrow','GHC.Parser.Annotation.AnnDarrow', -- 'GHC.Parser.Annotation.AnnForall','GHC.Parser.Annotation.AnnDot' --- 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 Constructor Declaration data ConDecl pass @@ -1058,8 +1058,9 @@ data ConDecl pass -- The following fields describe the type after the '::' -- See Note [GADT abstract syntax] , con_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass) - -- ^ The outermost type variable binders, be they explicit or implicit. - -- The 'XRec' is used to anchor API annotations, AnnForall and AnnDot. + -- ^ The outermost type variable binders, be they explicit or + -- implicit. The 'XRec' is used to anchor exact print + -- annotations, AnnForall and AnnDot. , con_mb_cxt :: Maybe (LHsContext pass) -- ^ User-written context (if any) , con_g_args :: HsConDeclGADTDetails pass -- ^ Arguments; never infix , con_res_ty :: LHsType pass -- ^ Result type @@ -1258,7 +1259,7 @@ type LTyFamInstEqn pass = XRec pass (TyFamInstEqn pass) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' -- when in a list --- 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 -- | Haskell Type Patterns type HsTyPats pass = [LHsTypeArg pass] @@ -1318,7 +1319,7 @@ data TyFamInstDecl pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType', -- 'GHC.Parser.Annotation.AnnInstance', - -- 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 | XTyFamInstDecl !(XXTyFamInstDecl pass) ----------------- Data family instances ------------- @@ -1336,7 +1337,7 @@ newtype DataFamInstDecl pass -- 'GHC.Parser.Annotation.AnnWhere','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 ----------------- Family instances (common types) ------------- @@ -1359,7 +1360,7 @@ data FamEqn pass rhs -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual' | XFamEqn !(XXFamEqn pass rhs) - -- 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 ----------------- Class instances ------------- @@ -1381,14 +1382,14 @@ data ClsInstDecl pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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' : 'GHC.Parser.Annotation.AnnInstance', -- 'GHC.Parser.Annotation.AnnWhere', -- '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 | XClsInstDecl !(XXClsInstDecl pass) ----------------- Instances of all kinds ------------- @@ -1439,10 +1440,10 @@ data DerivDecl pass = DerivDecl , deriv_overlap_mode :: Maybe (XRec pass OverlapMode) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDeriving', -- 'GHC.Parser.Annotation.AnnInstance', 'GHC.Parser.Annotation.AnnStock', - -- 'GHC.Parser.Annotation.AnnAnyClass', 'Api.AnnNewtype', + -- 'GHC.Parser.Annotation.AnnAnyClass', 'GHC.Parser.Annotation.AnnNewtype', -- '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 } | XDerivDecl !(XXDerivDecl pass) @@ -1501,7 +1502,7 @@ data DefaultDecl pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnDefault', -- '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 | XDefaultDecl !(XXDefaultDecl pass) {- @@ -1539,7 +1540,7 @@ data ForeignDecl pass -- 'GHC.Parser.Annotation.AnnImport','GHC.Parser.Annotation.AnnExport', -- 'GHC.Parser.Annotation.AnnDcolon' - -- 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 | XForeignDecl !(XXForeignDecl pass) {- @@ -1689,7 +1690,7 @@ data RuleBndr pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen', -- 'GHC.Parser.Annotation.AnnDcolon','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 collectRuleBndrSigTys :: [RuleBndr pass] -> [HsPatSigType pass] collectRuleBndrSigTys bndrs = [ty | RuleBndrSig _ _ ty <- bndrs] @@ -1775,7 +1776,7 @@ data AnnDecl pass = HsAnnotation -- 'GHC.Parser.Annotation.AnnModule' -- '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 | XAnnDecl !(XXAnnDecl pass) -- | Annotation Provenance @@ -1813,5 +1814,5 @@ data RoleAnnotDecl pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType', -- 'GHC.Parser.Annotation.AnnRole' - -- 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 | XRoleAnnotDecl !(XXRoleAnnotDecl pass) diff --git a/compiler/Language/Haskell/Syntax/Expr.hs b/compiler/Language/Haskell/Syntax/Expr.hs index 15b74e4ce5..4121e5cc30 100644 --- a/compiler/Language/Haskell/Syntax/Expr.hs +++ b/compiler/Language/Haskell/Syntax/Expr.hs @@ -190,7 +190,7 @@ type LHsExpr p = XRec p (HsExpr p) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma' when -- in a list - -- 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 ------------------------- {- Note [NoSyntaxExpr] @@ -312,7 +312,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLam', -- '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 | HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p)) -- ^ Lambda-case -- @@ -320,7 +320,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnCase','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 | HsApp (XApp p) (LHsExpr p) (LHsExpr p) -- ^ Application @@ -349,7 +349,7 @@ data HsExpr p -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnMinus' - -- 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 | NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p) @@ -357,7 +357,7 @@ data HsExpr p -- | - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsPar (XPar p) (LHsExpr p) -- ^ Parenthesised expr; see Note [Parens in HsSyn] @@ -373,7 +373,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : '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 -- Note [ExplicitTuple] | ExplicitTuple (XExplicitTuple p) @@ -397,7 +397,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnOf','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 | HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p)) @@ -407,7 +407,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnThen','GHC.Parser.Annotation.AnnSemi', -- 'GHC.Parser.Annotation.AnnElse', - -- 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 | HsIf (XIf p) -- GhcPs: this is a Bool; False <=> do not use -- rebindable syntax (LHsExpr p) -- predicate @@ -419,7 +419,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnIf' -- '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 | HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)] -- | let(rec) @@ -428,7 +428,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnOpen' @'{'@, -- 'GHC.Parser.Annotation.AnnClose' @'}'@,'GHC.Parser.Annotation.AnnIn' - -- 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 | HsLet (XLet p) (HsLocalBinds p) (LHsExpr p) @@ -438,7 +438,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnVbar', -- '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 | HsDo (XDo p) -- Type of the whole expression (HsStmtContext (HsDoRn p)) -- The parameterisation of the above is unimportant @@ -451,7 +451,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : '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 -- See Note [Empty lists] | ExplicitList (XExplicitList p) -- Gives type of components of list @@ -462,7 +462,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, -- 'GHC.Parser.Annotation.AnnDotdot','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 | RecordCon { rcon_ext :: XRecordCon p , rcon_con :: XRec p (ConLikeP p) -- The constructor @@ -475,7 +475,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnComma, 'GHC.Parser.Annotation.AnnDot', -- '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 | RecordUpd { rupd_ext :: XRecordUpd p , rupd_expr :: LHsExpr p @@ -514,7 +514,7 @@ data HsExpr p -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- 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 | ExprWithTySig (XExprWithTySig p) @@ -527,14 +527,14 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnComma','GHC.Parser.Annotation.AnnDotdot', -- '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 | ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) -- For OverloadedLists, the fromList witness (ArithSeqInfo p) - -- 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 ----------------------------------------------------------- -- MetaHaskell Extensions @@ -543,7 +543,7 @@ data HsExpr p -- 'GHC.Parser.Annotation.AnnOpenE','GHC.Parser.Annotation.AnnOpenEQ', -- 'GHC.Parser.Annotation.AnnClose','GHC.Parser.Annotation.AnnCloseQ' - -- 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 | HsBracket (XBracket p) (HsBracket p) -- See Note [Pending Splices] @@ -565,7 +565,7 @@ data HsExpr p -- | - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsSpliceE (XSpliceE p) (HsSplice p) ----------------------------------------------------------- @@ -576,7 +576,7 @@ data HsExpr p -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnProc', -- '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 | HsProc (XProc p) (LPat p) -- arrow abstraction, proc (LHsCmdTop p) -- body of the abstraction @@ -586,7 +586,7 @@ data HsExpr p -- static pointers extension -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnStatic', - -- 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 | HsStatic (XStatic p) -- Free variables of the body (LHsExpr p) -- Body @@ -657,7 +657,7 @@ data HsPragE p type LHsTupArg id = XRec id (HsTupArg id) -- | - '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 -- | Haskell Tuple Argument data HsTupArg id @@ -732,14 +732,15 @@ the RHS so that we can build the expression. Note [Located RdrNames] ~~~~~~~~~~~~~~~~~~~~~~~ -A number of syntax elements have seemingly redundant locations attached to them. -This is deliberate, to allow transformations making use of the API Annotations -to easily correlate a Located Name in the RenamedSource with a Located RdrName -in the ParsedSource. +A number of syntax elements have seemingly redundant locations +attached to them. This is deliberate, to allow transformations making +use of the exact print annotations to easily correlate a Located Name +in the RenamedSource with a Located RdrName in the ParsedSource. -There are unfortunately enough differences between the ParsedSource and the -RenamedSource that the API Annotations cannot be used directly with -RenamedSource, so this allows a simple mapping to be used based on the location. +There are unfortunately enough differences between the ParsedSource +and the RenamedSource that the exact print annotations cannot be used +directly with RenamedSource, so this allows a simple mapping to be +used based on the location. Note [ExplicitTuple] ~~~~~~~~~~~~~~~~~~~~ @@ -844,7 +845,7 @@ data HsCmd id -- 'GHC.Parser.Annotation.Annrarrowtail','GHC.Parser.Annotation.AnnLarrowtail', -- 'GHC.Parser.Annotation.AnnRarrowtail' - -- 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 = HsCmdArrApp -- Arrow tail, or arrow application (f -< arg) (XCmdArrApp id) -- type of the arrow expressions f, -- of the form a t t', where arg :: t @@ -857,7 +858,7 @@ data HsCmd id -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenB' @'(|'@, -- 'GHC.Parser.Annotation.AnnCloseB' @'|)'@ - -- 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 | HsCmdArrForm -- Command formation, (| e cmd1 .. cmdn |) (XCmdArrForm id) (LHsExpr id) -- The operator. @@ -878,14 +879,14 @@ data HsCmd id -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLam', -- '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 | HsCmdPar (XCmdPar id) (LHsCmd id) -- parenthesised command -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsCmdCase (XCmdCase id) (LHsExpr id) @@ -894,7 +895,7 @@ data HsCmd id -- 'GHC.Parser.Annotation.AnnOf','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 | HsCmdLamCase (XCmdLamCase id) (MatchGroup id (LHsCmd id)) -- bodies are HsCmd's @@ -902,7 +903,7 @@ data HsCmd id -- 'GHC.Parser.Annotation.AnnCase','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 | HsCmdIf (XCmdIf id) (SyntaxExpr id) -- cond function @@ -914,7 +915,7 @@ data HsCmd id -- 'GHC.Parser.Annotation.AnnThen','GHC.Parser.Annotation.AnnSemi', -- 'GHC.Parser.Annotation.AnnElse', - -- 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 | HsCmdLet (XCmdLet id) (HsLocalBinds id) -- let(rec) @@ -923,7 +924,7 @@ data HsCmd id -- 'GHC.Parser.Annotation.AnnOpen' @'{'@, -- 'GHC.Parser.Annotation.AnnClose' @'}'@,'GHC.Parser.Annotation.AnnIn' - -- 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 | HsCmdDo (XCmdDo id) -- Type of the whole expression (XRec id [CmdLStmt id]) @@ -932,7 +933,7 @@ data HsCmd id -- 'GHC.Parser.Annotation.AnnVbar', -- '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 | XCmd !(XXCmd id) -- Note [Trees that Grow] extension point @@ -1011,7 +1012,7 @@ type LMatch id body = XRec id (Match id body) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' when in a -- list --- 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 Match p body = Match { m_ext :: XCMatch p body, @@ -1032,8 +1033,8 @@ so on. In order to simplify tooling processing and pretty print output, the provenance is captured in an HsMatchContext. -This is particularly important for the API Annotations for a multi-equation -FunBind. +This is particularly important for the exact print annotations for a +multi-equation FunBind. The parser initially creates a FunBind with a single Match in it for every function definition it sees. @@ -1044,11 +1045,12 @@ where all the Matches are combined. In the process, all the original FunBind fun_id's bar one are discarded, including the locations. -This causes a problem for source to source conversions via API -Annotations, so the original fun_ids and infix flags are preserved in +This causes a problem for source to source conversions via exact print +annotations, so the original fun_ids and infix flags are preserved in the Match, when it originates from a FunBind. -Example infix function definition requiring individual API Annotations +Example infix function definition requiring individual exact print +annotations (&&& ) [] [] = [] xs &&& [] = xs @@ -1073,7 +1075,7 @@ isInfixMatch match = case m_ctxt match of -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose' -- 'GHC.Parser.Annotation.AnnRarrow','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 data GRHSs p body = GRHSs { grhssExt :: XCGRHSs p body, @@ -1136,13 +1138,13 @@ type GhciStmt id = Stmt id (LHsExpr id) -- The SyntaxExprs in here are used *only* for do-notation and monad -- comprehensions, which have rebindable syntax. Otherwise they are unused. --- | API Annotations when in qualifier lists or guards +-- | Exact print annotations when in qualifier lists or guards -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVbar', -- 'GHC.Parser.Annotation.AnnComma','GHC.Parser.Annotation.AnnThen', -- 'GHC.Parser.Annotation.AnnBy','GHC.Parser.Annotation.AnnBy', -- 'GHC.Parser.Annotation.AnnGroup','GHC.Parser.Annotation.AnnUsing' --- 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 StmtLR idL idR body -- body should always be (LHs**** idR) = LastStmt -- Always the last Stmt in ListComp, MonadComp, -- and (after the renamer, see GHC.Rename.Expr.checkLastStmt) DoExpr, MDoExpr @@ -1160,7 +1162,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- See Note [Monad Comprehensions] -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLarrow' - -- 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 | BindStmt (XBindStmt idL idR body) -- ^ Post renaming has optional fail and bind / (>>=) operator. -- Post typechecking, also has multiplicity of the argument @@ -1194,7 +1196,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLet' -- '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 | LetStmt (XLetStmt idL idR body) (HsLocalBindsLR idL idR) -- ParStmts only occur in a list/monad comprehension @@ -1232,7 +1234,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- Recursive statement (see Note [How RecStmt works] below) -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRec' - -- 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 | RecStmt { recS_ext :: XRecStmt idL idR body , recS_stmts :: XRec idR [LStmtLR idL idR body] diff --git a/compiler/Language/Haskell/Syntax/Extension.hs b/compiler/Language/Haskell/Syntax/Extension.hs index cd9804b7f9..892e93892d 100644 --- a/compiler/Language/Haskell/Syntax/Extension.hs +++ b/compiler/Language/Haskell/Syntax/Extension.hs @@ -117,9 +117,10 @@ SrcSpans everywhere. instead of `Located (HsExpr p)` or similar types, we will now have `XRec p (HsExpr p)` -XRec allows annotating certain points in the AST with extra information. This -maybe be source spans (for GHC), nothing (for TH), types (for HIE files), api -annotations (for exactprint) or anything else. +XRec allows annotating certain points in the AST with extra +information. This maybe be source spans (for GHC), nothing (for TH), +types (for HIE files), exact print annotations (for exactprint) or +anything else. This should hopefully bring us one step closer to sharing the AST between GHC and TH. diff --git a/compiler/Language/Haskell/Syntax/Pat.hs b/compiler/Language/Haskell/Syntax/Pat.hs index 8c3309f477..7f776f1d39 100644 --- a/compiler/Language/Haskell/Syntax/Pat.hs +++ b/compiler/Language/Haskell/Syntax/Pat.hs @@ -52,7 +52,7 @@ type LPat p = XRec p (Pat p) -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' --- 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 Pat p = ------------ Simple patterns --------------- WildPat (XWildPat p) -- ^ Wildcard Pattern @@ -68,13 +68,13 @@ data Pat p (LPat p) -- ^ Lazy Pattern -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | AsPat (XAsPat p) (LIdP p) (LPat p) -- ^ As pattern -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt' - -- 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 | ParPat (XParPat p) (LPat p) -- ^ Parenthesised pattern @@ -82,12 +82,12 @@ data Pat p -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | BangPat (XBangPat p) (LPat p) -- ^ Bang pattern -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' - -- 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 ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) @@ -101,7 +101,7 @@ data Pat p -- - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | TuplePat (XTuplePat p) -- after typechecking, holds the types of the tuple components @@ -139,7 +139,7 @@ data Pat p -- '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 ------------ Constructor patterns --------------- | ConPat { @@ -152,7 +152,7 @@ data Pat p ------------ View patterns --------------- -- | - '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 | ViewPat (XViewPat p) -- The overall type of the pattern -- (= the argument type of the view function) -- for hsPatType. @@ -164,7 +164,7 @@ data Pat p -- | - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | SplicePat (XSplicePat p) (HsSplice p) -- ^ Splice Pattern (Includes quasi-quotes) @@ -190,7 +190,7 @@ data Pat p -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | NPlusKPat (XNPlusKPat p) -- Type of overall pattern (LIdP p) -- n+k pattern (XRec p (HsOverLit p)) -- It'll always be an HsIntegral @@ -205,7 +205,7 @@ data Pat p ------------ Pattern type signatures --------------- -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- 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 | SigPat (XSigPat p) -- After typechecker: Type (LPat p) -- Pattern with a type signature (HsPatSigType (NoGhcTc p)) -- Signature can bind both @@ -277,7 +277,7 @@ type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p) -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual', -- --- 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 HsRecField' id arg = HsRecField { hsRecFieldAnn :: XHsRecField id, hsRecFieldLbl :: Located id, diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs index 63b5bb353b..720f7c615c 100644 --- a/compiler/Language/Haskell/Syntax/Type.hs +++ b/compiler/Language/Haskell/Syntax/Type.hs @@ -279,7 +279,7 @@ quantified in left-to-right order in kind signatures is nice since: -- | Located Haskell Context type LHsContext pass = XRec pass (HsContext pass) -- ^ 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnUnit' - -- 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 -- | Haskell Context type HsContext pass = [LHsType pass] @@ -289,7 +289,7 @@ type LHsType pass = XRec pass (HsType pass) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma' when -- in a list - -- 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 -- | Haskell Kind type HsKind pass = HsType pass @@ -298,7 +298,7 @@ type HsKind pass = HsType pass type LHsKind pass = XRec pass (HsKind pass) -- ^ 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- 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 -------------------------------------------------- -- LHsQTyVars @@ -711,7 +711,7 @@ data HsTyVarBndr flag pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen', -- 'GHC.Parser.Annotation.AnnDcolon', '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 | XTyVarBndr !(XXTyVarBndr pass) @@ -732,7 +732,7 @@ data HsType pass } -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnForall', -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDarrow' - -- 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" | HsQualTy -- See Note [HsType binders] { hst_xqual :: XQualTy pass @@ -748,14 +748,14 @@ data HsType pass -- See Note [Located RdrNames] in GHC.Hs.Expr -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -- 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 | HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -- 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 | HsAppKindTy (XAppKindTy pass) -- type level type app (LHsType pass) @@ -767,14 +767,14 @@ data HsType pass (LHsType pass) -- ^ - '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 | HsListTy (XListTy pass) (LHsType pass) -- Element type -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsTupleTy (XTupleTy pass) HsTupleSort @@ -782,20 +782,20 @@ data HsType pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'(' or '(#'@, -- 'GHC.Parser.Annotation.AnnClose' @')' or '#)'@ - -- 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 | HsSumTy (XSumTy pass) [LHsType pass] -- Element types (length gives arity) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsOpTy (XOpTy pass) (LHsType pass) (LIdP pass) (LHsType pass) -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -- 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 | HsParTy (XParTy pass) (LHsType pass) -- See Note [Parens in HsSyn] in GHC.Hs.Expr @@ -805,7 +805,7 @@ data HsType pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsIParamTy (XIParamTy pass) (XRec pass HsIPName) -- (?x :: ty) @@ -816,7 +816,7 @@ data HsType pass -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- 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 | HsStarTy (XStarTy pass) Bool -- Is this the Unicode variant? @@ -832,20 +832,20 @@ data HsType pass -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@, -- 'GHC.Parser.Annotation.AnnDcolon','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 | HsSpliceTy (XSpliceTy pass) (HsSplice pass) -- Includes quasi-quotes -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsDocTy (XDocTy pass) (LHsType pass) LHsDocString -- A documented type -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -- 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 | HsBangTy (XBangTy pass) HsSrcBang (LHsType pass) -- Bang-style type annotations @@ -854,14 +854,14 @@ data HsType pass -- 'GHC.Parser.Annotation.AnnClose' @'#-}'@ -- 'GHC.Parser.Annotation.AnnBang' @\'!\'@ - -- 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 | HsRecTy (XRecTy pass) [LConDeclField pass] -- Only in data type declarations -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsExplicitListTy -- A promoted explicit list (XExplicitListTy pass) @@ -870,7 +870,7 @@ data HsType pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsExplicitTupleTy -- A promoted explicit tuple (XExplicitTupleTy pass) @@ -878,18 +878,18 @@ data HsType pass -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : '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 | HsTyLit (XTyLit pass) HsTyLit -- A promoted numeric literal. -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -- 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 | HsWildCardTy (XWildCardTy pass) -- A type wildcard -- See Note [The wildcard story for types] -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -- 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 -- For adding new constructors via Trees that Grow | XHsType @@ -1045,7 +1045,7 @@ type LConDeclField pass = XRec pass (ConDeclField pass) -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma' when -- in a list - -- 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 -- | Constructor Declaration Field data ConDeclField pass -- Record fields have Haddock docs on them @@ -1056,7 +1056,7 @@ data ConDeclField pass -- Record fields have Haddock docs on them cd_fld_doc :: Maybe LHsDocString } -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- 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 | XConDeclField !(XXConDeclField pass) -- | Describes the arguments to a data constructor. This is a common diff --git a/utils/check-exact/ExactPrint.hs b/utils/check-exact/ExactPrint.hs index 2415e73db9..e1fcc88219 100644 --- a/utils/check-exact/ExactPrint.hs +++ b/utils/check-exact/ExactPrint.hs @@ -2688,7 +2688,7 @@ instance ExactPrint (TyClDecl GhcPs) where markEpAnn an AnnCloseC where top_matter = do - annotationsToComments (apiAnnAnns an) [AnnOpenP, AnnCloseP] + annotationsToComments (epAnnAnns an) [AnnOpenP, AnnCloseP] markEpAnn an AnnClass exactVanillaDeclHead an lclas tyvars fixity context unless (null fds) $ do @@ -3282,7 +3282,7 @@ instance ExactPrint (ConDecl GhcPs) where mapM_ markAnnotated doc mapM_ markAnnotated cons markEpAnn an AnnDcolon - annotationsToComments (apiAnnAnns an) [AnnOpenP, AnnCloseP] + annotationsToComments (epAnnAnns an) [AnnOpenP, AnnCloseP] -- when has_forall $ markEpAnn an AnnForall markAnnotated bndrs -- mapM_ markAnnotated qvars @@ -4011,12 +4011,6 @@ setLayoutOffsetP c = do debugM $ "setLayoutOffsetP:" ++ show c modify (\s -> s { pLHS = c }) --- getEofPos :: (Monad m, Monoid w) => EP w m RealSrcSpan --- getEofPos = do --- as <- gets epEpAnns --- case apiAnnEofPos as of --- Nothing -> return placeholderRealSpan --- Just ss -> return ss -- --------------------------------------------------------------------- ------------------------------------------------------------------------- diff --git a/utils/check-exact/Transform.hs b/utils/check-exact/Transform.hs index 559e848ae2..f4e97c2bc7 100644 --- a/utils/check-exact/Transform.hs +++ b/utils/check-exact/Transform.hs @@ -663,7 +663,7 @@ balanceCommentsMatch (L l (Match am mctxt pats (GRHSs xg grhss binds))) = do where simpleBreak (r,_) = r /= 0 (SrcSpanAnn an1 _loc1) = l - anc1 = addCommentOrigDeltas $ apiAnnComments an1 + anc1 = addCommentOrigDeltas $ epAnnComments an1 cs1f = getFollowingComments anc1 -- (move',stay') = break simpleBreak (commentsDeltas (anchorFromLocatedA (L l ())) cs1f) (move',stay') = break simpleBreak (trailingCommentsDeltas (anchorFromLocatedA (L l ())) cs1f) @@ -734,8 +734,8 @@ balanceComments' la1 la2 = do simpleBreak n (r,_) = r > n L (SrcSpanAnn an1 loc1) f = la1 L (SrcSpanAnn an2 loc2) s = la2 - anc1 = addCommentOrigDeltas $ apiAnnComments an1 - anc2 = addCommentOrigDeltas $ apiAnnComments an2 + anc1 = addCommentOrigDeltas $ epAnnComments an1 + anc2 = addCommentOrigDeltas $ epAnnComments an2 cs1f = getFollowingComments anc1 cs2b = priorComments anc2 (stay'',move') = break (simpleBreak 1) (priorCommentsDeltas (anchorFromLocatedA la2) cs2b) @@ -854,7 +854,7 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb))) = do (L lg (GRHS ga gs rhs):grs) -> (la'',reverse $ (L lg (GRHS ga' gs rhs)):grs,[(gac,(csp,csf))]) where (SrcSpanAnn an1 _loc1) = la - anc1 = addCommentOrigDeltas $ apiAnnComments an1 + anc1 = addCommentOrigDeltas $ epAnnComments an1 (EpAnn anc an _) = ga :: EpAnn' GrhsAnn (csp,csf) = case anc1 of AnnComments cs -> ([],cs) @@ -864,7 +864,7 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb))) = do stay = map snd stay' cs1 = AnnCommentsBalanced csp stay - gac = addCommentOrigDeltas $ apiAnnComments ga + gac = addCommentOrigDeltas $ epAnnComments ga gfc = getFollowingComments gac gac' = setFollowingComments gac (sort $ gfc ++ move) ga' = (EpAnn anc an gac') diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index 548acd365d..4e49cfdd12 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -105,7 +105,7 @@ getPragmas (L _ (HsModule { hsmodAnn = anns'})) = pragmaStr tokComment _ = "" cmp (L l1 _) (L l2 _) = compare (anchor l1) (anchor l2) - comments' = map tokComment $ sortBy cmp $ priorComments $ apiAnnComments anns' + comments' = map tokComment $ sortBy cmp $ priorComments $ epAnnComments anns' pragmas = filter (\c -> isPrefixOf "{-#" c ) comments' pragmaStr = intercalate "\n" pragmas |