diff options
author | Alan Zimmerman <alan.zimm@gmail.com> | 2021-03-25 22:54:15 +0000 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2021-03-31 11:13:28 -0400 |
commit | 798d8f80e1562891e4bbd8e4d8f42926cecf32b3 (patch) | |
tree | 927e558a1849636d6fb5e4924adf56fdb283b128 /compiler/GHC/Parser | |
parent | 49bc1e9ec854e571dfa78ac43565073586579f31 (diff) | |
download | haskell-798d8f80e1562891e4bbd8e4d8f42926cecf32b3.tar.gz |
EPA : Rename AnnComment to EpaComment
Follow-up from !2418, see #19579
Diffstat (limited to 'compiler/GHC/Parser')
-rw-r--r-- | compiler/GHC/Parser/Annotation.hs | 119 | ||||
-rw-r--r-- | compiler/GHC/Parser/Lexer.x | 46 | ||||
-rw-r--r-- | compiler/GHC/Parser/PostProcess.hs | 10 |
3 files changed, 90 insertions, 85 deletions
diff --git a/compiler/GHC/Parser/Annotation.hs b/compiler/GHC/Parser/Annotation.hs index 6fba7baa94..c62bdce65e 100644 --- a/compiler/GHC/Parser/Annotation.hs +++ b/compiler/GHC/Parser/Annotation.hs @@ -6,7 +6,7 @@ module GHC.Parser.Annotation ( -- * Core Exact Print Annotation types AnnKeywordId(..), - AnnotationComment(..), AnnotationCommentTok(..), + EpaComment(..), EpaCommentTok(..), IsUnicodeSyntax(..), unicodeAnn, HasE(..), @@ -22,7 +22,7 @@ module GHC.Parser.Annotation ( -- ** Comments in Annotations - EpAnnComments(..), LAnnotationComment, com, noCom, + EpAnnComments(..), LEpaComment, com, noCom, getFollowingComments, setFollowingComments, setPriorComments, EpAnnCO, @@ -103,7 +103,7 @@ source code comments? We need to track the locations of all elements from the original source: this includes keywords such as 'let' / 'in' / 'do' etc as well as punctuation such as commas and braces, and also comments. We collectively refer to this -metadata as the "API annotations". +metadata as the "exact print annotations". NON-COMMENT ELEMENTS @@ -132,8 +132,8 @@ PARSER STATE There are three fields in PState (the parser state) which play a role with annotation comments. -> comment_q :: [LAnnotationComment], -> header_comments :: Maybe [LAnnotationComment], +> comment_q :: [LEpaComment], +> header_comments :: Maybe [LEpaComment], > eof_pos :: Maybe (RealSrcSpan, RealSrcSpan), -- pos, gap to prior token The 'comment_q' field captures comments as they are seen in the token stream, @@ -181,10 +181,10 @@ https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations -- -------------------------------------------------------------------- --- | API Annotations exist so that tools can perform source to source --- conversions of Haskell code. They are used to keep track of the --- various syntactic keywords that are not captured in the existing --- AST. +-- | Exact print annotations exist so that tools can perform source to +-- source conversions of Haskell code. They are used to keep track of +-- the various syntactic keywords that are not captured in the +-- existing AST. -- -- The annotations, together with original source comments are made available in -- the @'pm_parsed_source@ field of @'GHC.Driver.Env.HsParsedModule'@. @@ -255,7 +255,10 @@ data AnnKeywordId | AnnNewtype | AnnName -- ^ where a name loses its location in the AST, this carries it | AnnOf - | AnnOpen -- ^ '{-\# LANGUAGE' etc + | AnnOpen -- ^ '{-\# DEPRECATED' etc. Opening of pragmas where + -- the capitalisation of the string can be changed by + -- the user. The actual text used is stored in a + -- 'SourceText' on the relevant pragma item. | AnnOpenB -- ^ '(|' | AnnOpenBU -- ^ '(|', unicode variant | AnnOpenC -- ^ '{' @@ -309,29 +312,31 @@ instance Outputable AnnKeywordId where -- --------------------------------------------------------------------- -data AnnotationComment = AnnComment { ac_tok :: AnnotationCommentTok - , ac_prior_tok :: RealSrcSpan - -- ^ The location of the prior - -- token, used for exact printing - } +data EpaComment = + EpaComment + { ac_tok :: EpaCommentTok + , ac_prior_tok :: RealSrcSpan + -- ^ The location of the prior + -- token, used for exact printing + } deriving (Eq, Ord, Data, Show) -data AnnotationCommentTok = +data EpaCommentTok = -- Documentation annotations - AnnDocCommentNext String -- ^ something beginning '-- |' - | AnnDocCommentPrev String -- ^ something beginning '-- ^' - | AnnDocCommentNamed String -- ^ something beginning '-- $' - | AnnDocSection Int String -- ^ a section heading - | AnnDocOptions String -- ^ doc options (prune, ignore-exports, etc) - | AnnLineComment String -- ^ comment starting by "--" - | AnnBlockComment String -- ^ comment in {- -} - | AnnEofComment -- ^ empty comment, capturing + EpaDocCommentNext String -- ^ something beginning '-- |' + | EpaDocCommentPrev String -- ^ something beginning '-- ^' + | EpaDocCommentNamed String -- ^ something beginning '-- $' + | EpaDocSection Int String -- ^ a section heading + | EpaDocOptions String -- ^ doc options (prune, ignore-exports, etc) + | EpaLineComment String -- ^ comment starting by "--" + | EpaBlockComment String -- ^ comment in {- -} + | EpaEofComment -- ^ empty comment, capturing -- location of EOF deriving (Eq, Ord, Data, Show) -- Note: these are based on the Token versions, but the Token type is -- defined in GHC.Parser.Lexer and bringing it in here would create a loop -instance Outputable AnnotationComment where +instance Outputable EpaComment where ppr x = text (show x) -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen', @@ -534,22 +539,22 @@ realSpanAsAnchor s = Anchor s UnchangedAnchor -- them into the output stream. But when editin the AST, to move -- fragments around, it is useful to be able to first separate the -- comments into those occuring before the AST element and those --- following it. The 'AnnCommentsBalanced' constructor is used to do --- this. The GHC parser will only insert the 'AnnComments' form. -data EpAnnComments = AnnComments - { priorComments :: ![LAnnotationComment] } - | AnnCommentsBalanced - { priorComments :: ![LAnnotationComment] - , followingComments :: ![LAnnotationComment] } +-- following it. The 'EpaCommentsBalanced' constructor is used to do +-- this. The GHC parser will only insert the 'EpaComments' form. +data EpAnnComments = EpaComments + { priorComments :: ![LEpaComment] } + | EpaCommentsBalanced + { priorComments :: ![LEpaComment] + , followingComments :: ![LEpaComment] } deriving (Data, Eq) -type LAnnotationComment = GenLocated Anchor AnnotationComment +type LEpaComment = GenLocated Anchor EpaComment noCom :: EpAnnComments -noCom = AnnComments [] +noCom = EpaComments [] -com :: [LAnnotationComment] -> EpAnnComments -com cs = AnnComments cs +com :: [LEpaComment] -> EpAnnComments +com cs = EpaComments cs -- --------------------------------------------------------------------- @@ -925,17 +930,17 @@ noAnn = EpAnnNotUsed addAnns :: EpAnn -> [AddEpAnn] -> EpAnnComments -> EpAnn addAnns (EpAnn l as1 cs) as2 cs2 = EpAnn (widenAnchor l (as1 ++ as2)) (as1 ++ as2) (cs <> cs2) -addAnns EpAnnNotUsed [] (AnnComments []) = EpAnnNotUsed -addAnns EpAnnNotUsed [] (AnnCommentsBalanced [] []) = EpAnnNotUsed +addAnns EpAnnNotUsed [] (EpaComments []) = EpAnnNotUsed +addAnns EpAnnNotUsed [] (EpaCommentsBalanced [] []) = EpAnnNotUsed addAnns EpAnnNotUsed as cs = EpAnn (Anchor placeholderRealSpan UnchangedAnchor) as cs -- AZ:TODO use widenSpan here too addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA addAnnsA (SrcSpanAnn (EpAnn l as1 cs) loc) as2 cs2 = SrcSpanAnn (EpAnn l (AnnListItem (lann_trailing as1 ++ as2)) (cs <> cs2)) loc -addAnnsA (SrcSpanAnn EpAnnNotUsed loc) [] (AnnComments []) +addAnnsA (SrcSpanAnn EpAnnNotUsed loc) [] (EpaComments []) = SrcSpanAnn EpAnnNotUsed loc -addAnnsA (SrcSpanAnn EpAnnNotUsed loc) [] (AnnCommentsBalanced [] []) +addAnnsA (SrcSpanAnn EpAnnNotUsed loc) [] (EpaCommentsBalanced [] []) = SrcSpanAnn EpAnnNotUsed loc addAnnsA (SrcSpanAnn EpAnnNotUsed loc) as cs = SrcSpanAnn (EpAnn (spanAsAnchor loc) (AnnListItem as) cs) loc @@ -983,7 +988,7 @@ annParen2AddEpAnn (EpAnn _ (AnnParen pt o c) _) (ai,ac) = parenTypeKws pt epAnnComments :: EpAnn' an -> EpAnnComments -epAnnComments EpAnnNotUsed = AnnComments [] +epAnnComments EpAnnNotUsed = EpaComments [] epAnnComments (EpAnn _ _ cs) = cs -- --------------------------------------------------------------------- @@ -1014,17 +1019,17 @@ addCLocAA a b c = L (noAnnSrcSpan $ combineSrcSpans (locA $ getLoc a) (locA $ ge -- Utilities for manipulating EpAnnComments -- --------------------------------------------------------------------- -getFollowingComments :: EpAnnComments -> [LAnnotationComment] -getFollowingComments (AnnComments _) = [] -getFollowingComments (AnnCommentsBalanced _ cs) = cs +getFollowingComments :: EpAnnComments -> [LEpaComment] +getFollowingComments (EpaComments _) = [] +getFollowingComments (EpaCommentsBalanced _ cs) = cs -setFollowingComments :: EpAnnComments -> [LAnnotationComment] -> EpAnnComments -setFollowingComments (AnnComments ls) cs = AnnCommentsBalanced ls cs -setFollowingComments (AnnCommentsBalanced ls _) cs = AnnCommentsBalanced ls cs +setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments +setFollowingComments (EpaComments ls) cs = EpaCommentsBalanced ls cs +setFollowingComments (EpaCommentsBalanced ls _) cs = EpaCommentsBalanced ls cs -setPriorComments :: EpAnnComments -> [LAnnotationComment] -> EpAnnComments -setPriorComments (AnnComments _) cs = AnnComments cs -setPriorComments (AnnCommentsBalanced _ ts) cs = AnnCommentsBalanced cs ts +setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments +setPriorComments (EpaComments _) cs = EpaComments cs +setPriorComments (EpaCommentsBalanced _ ts) cs = EpaCommentsBalanced cs ts -- --------------------------------------------------------------------- -- Comment-only annotations @@ -1116,10 +1121,10 @@ instance Semigroup Anchor where Anchor r1 o1 <> Anchor r2 _ = Anchor (combineRealSrcSpans r1 r2) o1 instance Semigroup EpAnnComments where - AnnComments cs1 <> AnnComments cs2 = AnnComments (cs1 ++ cs2) - AnnComments cs1 <> AnnCommentsBalanced cs2 as2 = AnnCommentsBalanced (cs1 ++ cs2) as2 - AnnCommentsBalanced cs1 as1 <> AnnComments cs2 = AnnCommentsBalanced (cs1 ++ cs2) as1 - AnnCommentsBalanced cs1 as1 <> AnnCommentsBalanced cs2 as2 = AnnCommentsBalanced (cs1 ++ cs2) (as1++as2) + EpaComments cs1 <> EpaComments cs2 = EpaComments (cs1 ++ cs2) + EpaComments cs1 <> EpaCommentsBalanced cs2 as2 = EpaCommentsBalanced (cs1 ++ cs2) as2 + EpaCommentsBalanced cs1 as1 <> EpaComments cs2 = EpaCommentsBalanced (cs1 ++ cs2) as1 + EpaCommentsBalanced cs1 as1 <> EpaCommentsBalanced cs2 as2 = EpaCommentsBalanced (cs1 ++ cs2) (as1++as2) instance (Monoid a) => Monoid (EpAnn' a) where @@ -1173,12 +1178,12 @@ instance Outputable AnchorOperation where instance Outputable DeltaPos where ppr (DP l c) = text "DP" <+> ppr l <+> ppr c -instance Outputable (GenLocated Anchor AnnotationComment) where +instance Outputable (GenLocated Anchor EpaComment) where ppr (L l c) = text "L" <+> ppr l <+> ppr c instance Outputable EpAnnComments where - ppr (AnnComments cs) = text "AnnComments" <+> ppr cs - ppr (AnnCommentsBalanced cs ts) = text "AnnCommentsBalanced" <+> ppr cs <+> ppr ts + ppr (EpaComments cs) = text "EpaComments" <+> ppr cs + ppr (EpaCommentsBalanced cs ts) = text "EpaCommentsBalanced" <+> ppr cs <+> ppr ts instance (NamedThing (Located a)) => NamedThing (LocatedAn an a) where getName (L l a) = getName (L (locA l) a) diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x index be99757176..eec5171eb8 100644 --- a/compiler/GHC/Parser/Lexer.x +++ b/compiler/GHC/Parser/Lexer.x @@ -2348,8 +2348,8 @@ data PState = PState { -- the GHC API can do source to source conversions. -- 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], + header_comments :: Maybe [LEpaComment], + comment_q :: [LEpaComment], -- Haddock comments accumulated in ascending order of their location -- (BufPos). We use OrdList to get O(1) snoc. @@ -2918,21 +2918,21 @@ instance MonadP P where let (comment_q', newAnns) = allocateComments ss (comment_q s) in POk s { comment_q = comment_q' - } (AnnComments newAnns) + } (EpaComments newAnns) allocatePriorCommentsP ss = P $ \s -> let (header_comments', comment_q', newAnns) = allocatePriorComments ss (comment_q s) (header_comments s) in POk s { header_comments = header_comments', comment_q = comment_q' - } (AnnComments newAnns) + } (EpaComments newAnns) allocateFinalCommentsP ss = P $ \s -> let (header_comments', comment_q', newAnns) = allocateFinalComments ss (comment_q s) (header_comments s) in POk s { header_comments = header_comments', comment_q = comment_q' - } (AnnCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns)) + } (EpaCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns)) getCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments getCommentsFor (RealSrcSpan l _) = allocateCommentsP l @@ -3456,8 +3456,8 @@ queueComment c = P $ \s -> POk s { allocateComments :: RealSrcSpan - -> [LAnnotationComment] - -> ([LAnnotationComment], [LAnnotationComment]) + -> [LEpaComment] + -> ([LEpaComment], [LEpaComment]) allocateComments ss comment_q = let (before,rest) = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q @@ -3469,9 +3469,9 @@ allocateComments ss comment_q = allocatePriorComments :: RealSrcSpan - -> [LAnnotationComment] - -> Maybe [LAnnotationComment] - -> (Maybe [LAnnotationComment], [LAnnotationComment], [LAnnotationComment]) + -> [LEpaComment] + -> Maybe [LEpaComment] + -> (Maybe [LEpaComment], [LEpaComment], [LEpaComment]) allocatePriorComments ss comment_q mheader_comments = let cmp (L l _) = anchor l <= ss @@ -3485,9 +3485,9 @@ allocatePriorComments ss comment_q mheader_comments = allocateFinalComments :: RealSrcSpan - -> [LAnnotationComment] - -> Maybe [LAnnotationComment] - -> (Maybe [LAnnotationComment], [LAnnotationComment], [LAnnotationComment]) + -> [LEpaComment] + -> Maybe [LEpaComment] + -> (Maybe [LEpaComment], [LEpaComment], [LEpaComment]) allocateFinalComments ss comment_q mheader_comments = let cmp (L l _) = anchor l <= ss @@ -3499,19 +3499,19 @@ allocateFinalComments ss comment_q mheader_comments = Nothing -> (Just newAnns, [], comment_q') Just _ -> (mheader_comments, [], comment_q' ++ newAnns) -commentToAnnotation :: RealLocated Token -> LAnnotationComment -commentToAnnotation (L l (ITdocCommentNext s ll)) = mkLAnnotationComment l ll (AnnDocCommentNext s) -commentToAnnotation (L l (ITdocCommentPrev s ll)) = mkLAnnotationComment l ll (AnnDocCommentPrev s) -commentToAnnotation (L l (ITdocCommentNamed s ll)) = mkLAnnotationComment l ll (AnnDocCommentNamed s) -commentToAnnotation (L l (ITdocSection n s ll)) = mkLAnnotationComment l ll (AnnDocSection n s) -commentToAnnotation (L l (ITdocOptions s ll)) = mkLAnnotationComment l ll (AnnDocOptions s) -commentToAnnotation (L l (ITlineComment s ll)) = mkLAnnotationComment l ll (AnnLineComment s) -commentToAnnotation (L l (ITblockComment s ll)) = mkLAnnotationComment l ll (AnnBlockComment s) +commentToAnnotation :: RealLocated Token -> LEpaComment +commentToAnnotation (L l (ITdocCommentNext s ll)) = mkLEpaComment l ll (EpaDocCommentNext s) +commentToAnnotation (L l (ITdocCommentPrev s ll)) = mkLEpaComment l ll (EpaDocCommentPrev s) +commentToAnnotation (L l (ITdocCommentNamed s ll)) = mkLEpaComment l ll (EpaDocCommentNamed s) +commentToAnnotation (L l (ITdocSection n s ll)) = mkLEpaComment l ll (EpaDocSection n s) +commentToAnnotation (L l (ITdocOptions s ll)) = mkLEpaComment l ll (EpaDocOptions s) +commentToAnnotation (L l (ITlineComment s ll)) = mkLEpaComment l ll (EpaLineComment s) +commentToAnnotation (L l (ITblockComment s ll)) = mkLEpaComment l ll (EpaBlockComment s) commentToAnnotation _ = panic "commentToAnnotation" -- see Note [PsSpan in Comments] -mkLAnnotationComment :: RealSrcSpan -> PsSpan -> AnnotationCommentTok -> LAnnotationComment -mkLAnnotationComment l ll tok = L (realSpanAsAnchor l) (AnnComment tok (psRealSpan ll)) +mkLEpaComment :: RealSrcSpan -> PsSpan -> EpaCommentTok -> LEpaComment +mkLEpaComment l ll tok = L (realSpanAsAnchor l) (EpaComment tok (psRealSpan ll)) -- --------------------------------------------------------------------- diff --git a/compiler/GHC/Parser/PostProcess.hs b/compiler/GHC/Parser/PostProcess.hs index 2a70119fcf..2686bc151b 100644 --- a/compiler/GHC/Parser/PostProcess.hs +++ b/compiler/GHC/Parser/PostProcess.hs @@ -2721,8 +2721,8 @@ data PV_Accum = PV_Accum { pv_warnings :: Bag PsWarning , pv_errors :: Bag PsError - , pv_header_comments :: Maybe [LAnnotationComment] - , pv_comment_q :: [LAnnotationComment] + , pv_header_comments :: Maybe [LEpaComment] + , pv_comment_q :: [LEpaComment] } data PV_Result a = PV_Ok PV_Accum a | PV_Failed PV_Accum @@ -2811,21 +2811,21 @@ instance MonadP PV where let (comment_q', newAnns) = allocateComments ss (pv_comment_q s) in PV_Ok s { pv_comment_q = comment_q' - } (AnnComments newAnns) + } (EpaComments newAnns) allocatePriorCommentsP ss = PV $ \_ s -> let (header_comments', comment_q', newAnns) = allocatePriorComments ss (pv_comment_q s) (pv_header_comments s) in PV_Ok s { pv_header_comments = header_comments', pv_comment_q = comment_q' - } (AnnComments newAnns) + } (EpaComments newAnns) allocateFinalCommentsP ss = PV $ \_ s -> let (header_comments', comment_q', newAnns) = allocateFinalComments ss (pv_comment_q s) (pv_header_comments s) in PV_Ok s { pv_header_comments = header_comments', pv_comment_q = comment_q' - } (AnnCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns)) + } (EpaCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns)) {- Note [Parser-Validator Hint] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |