diff options
Diffstat (limited to 'compiler/GHC/Parser')
-rw-r--r-- | compiler/GHC/Parser/Annotation.hs | 66 | ||||
-rw-r--r-- | compiler/GHC/Parser/PostProcess.hs | 18 | ||||
-rw-r--r-- | compiler/GHC/Parser/Types.hs | 4 |
3 files changed, 44 insertions, 44 deletions
diff --git a/compiler/GHC/Parser/Annotation.hs b/compiler/GHC/Parser/Annotation.hs index 23b0864246..6fba7baa94 100644 --- a/compiler/GHC/Parser/Annotation.hs +++ b/compiler/GHC/Parser/Annotation.hs @@ -13,7 +13,7 @@ module GHC.Parser.Annotation ( -- * In-tree Exact Print Annotations AddEpAnn(..), - AnnAnchor(..), annAnchorRealSrcSpan, + EpaAnchor(..), epaAnchorRealSrcSpan, DeltaPos(..), EpAnn, EpAnn'(..), Anchor(..), AnchorOperation(..), @@ -378,15 +378,15 @@ data HasE = HasE | NoE -- --------------------------------------------------------------------- -- | Captures an annotation, storing the @'AnnKeywordId'@ and its --- location. The parser only ever inserts @'AnnAnchor'@ fields with a +-- location. The parser only ever inserts @'EpaAnchor'@ fields with a -- RealSrcSpan being the original location of the annotation in the -- source file. --- The @'AnnAnchor'@ can also store a delta position if the AST has been +-- The @'EpaAnchor'@ can also store a delta position if the AST has been -- modified and needs to be pretty printed again. -- The usual way an 'AddEpAnn' is created is using the 'mj' ("make -- jump") function, and then it can be inserted into the appropriate -- annotation. -data AddEpAnn = AddEpAnn AnnKeywordId AnnAnchor deriving (Data,Show,Eq,Ord) +data AddEpAnn = AddEpAnn AnnKeywordId EpaAnchor deriving (Data,Show,Eq,Ord) -- | The anchor for an @'AnnKeywordId'@. The Parser inserts the @'AR'@ -- variant, giving the exact location of the original item in the @@ -394,7 +394,7 @@ data AddEpAnn = AddEpAnn AnnKeywordId AnnAnchor deriving (Data,Show,Eq,Ord) -- provide a position for the item relative to the end of the previous -- item in the source. This is useful when editing an AST prior to -- exact printing the changed one. -data AnnAnchor = AR RealSrcSpan +data EpaAnchor = AR RealSrcSpan | AD DeltaPos deriving (Data,Show,Eq,Ord) @@ -411,11 +411,11 @@ data DeltaPos = } deriving (Show,Eq,Ord,Data) -annAnchorRealSrcSpan :: AnnAnchor -> RealSrcSpan -annAnchorRealSrcSpan (AR r) = r -annAnchorRealSrcSpan (AD _) = placeholderRealSpan +epaAnchorRealSrcSpan :: EpaAnchor -> RealSrcSpan +epaAnchorRealSrcSpan (AR r) = r +epaAnchorRealSrcSpan (AD _) = placeholderRealSpan -instance Outputable AnnAnchor where +instance Outputable EpaAnchor where ppr (AR r) = text "AR" <+> ppr r ppr (AD d) = text "AD" <+> ppr d @@ -476,8 +476,8 @@ See Note [XRec and Anno in the AST] for details of how this is done. -- type instance XLet GhcPs = EpAnn' AnnsLet -- data AnnsLet -- = AnnsLet { --- alLet :: AnnAnchor, --- alIn :: AnnAnchor +-- alLet :: EpaAnchor, +-- alIn :: EpaAnchor -- } deriving Data -- -- The spacing between the items under the scope of a given EpAnn' is @@ -637,11 +637,11 @@ meaning we can have type LocatedN RdrName -- | Captures the location of punctuation occuring between items, -- normally in a list. It is captured as a trailing annotation. data TrailingAnn - = AddSemiAnn AnnAnchor -- ^ Trailing ';' - | AddCommaAnn AnnAnchor -- ^ Trailing ',' - | AddVbarAnn AnnAnchor -- ^ Trailing '|' - | AddRarrowAnn AnnAnchor -- ^ Trailing '->' - | AddRarrowAnnU AnnAnchor -- ^ Trailing '->', unicode variant + = AddSemiAnn EpaAnchor -- ^ Trailing ';' + | AddCommaAnn EpaAnchor -- ^ Trailing ',' + | AddVbarAnn EpaAnchor -- ^ Trailing '|' + | AddRarrowAnn EpaAnchor -- ^ Trailing '->' + | AddRarrowAnnU EpaAnchor -- ^ Trailing '->', unicode variant deriving (Data,Show,Eq, Ord) instance Outputable TrailingAnn where @@ -686,8 +686,8 @@ data AnnList data AnnParen = AnnParen { ap_adornment :: ParenType, - ap_open :: AnnAnchor, - ap_close :: AnnAnchor + ap_open :: EpaAnchor, + ap_close :: EpaAnchor } deriving (Data) -- | Detail of the "brackets" used in an 'AnnParen' API Annotation. @@ -709,10 +709,10 @@ parenTypeKws AnnParensSquare = (AnnOpenS, AnnCloseS) -- | API Annotation for the 'Context' data type. data AnnContext = AnnContext { - ac_darrow :: Maybe (IsUnicodeSyntax, AnnAnchor), + ac_darrow :: Maybe (IsUnicodeSyntax, EpaAnchor), -- ^ location and encoding of the '=>', if present. - ac_open :: [AnnAnchor], -- ^ zero or more opening parentheses. - ac_close :: [AnnAnchor] -- ^ zero or more closing parentheses. + ac_open :: [EpaAnchor], -- ^ zero or more opening parentheses. + ac_close :: [EpaAnchor] -- ^ zero or more closing parentheses. } deriving (Data) @@ -727,35 +727,35 @@ data NameAnn -- | Used for a name with an adornment, so '`foo`', '(bar)' = NameAnn { nann_adornment :: NameAdornment, - nann_open :: AnnAnchor, - nann_name :: AnnAnchor, - nann_close :: AnnAnchor, + nann_open :: EpaAnchor, + nann_name :: EpaAnchor, + nann_close :: EpaAnchor, nann_trailing :: [TrailingAnn] } -- | Used for @(,,,)@, or @(#,,,#)# | NameAnnCommas { nann_adornment :: NameAdornment, - nann_open :: AnnAnchor, - nann_commas :: [AnnAnchor], - nann_close :: AnnAnchor, + nann_open :: EpaAnchor, + nann_commas :: [EpaAnchor], + nann_close :: EpaAnchor, nann_trailing :: [TrailingAnn] } -- | Used for @()@, @(##)@, @[]@ | NameAnnOnly { nann_adornment :: NameAdornment, - nann_open :: AnnAnchor, - nann_close :: AnnAnchor, + nann_open :: EpaAnchor, + nann_close :: EpaAnchor, nann_trailing :: [TrailingAnn] } -- | Used for @->@, as an identifier | NameAnnRArrow { - nann_name :: AnnAnchor, + nann_name :: EpaAnchor, nann_trailing :: [TrailingAnn] } -- | Used for an item with a leading @'@. The annotation for -- unquoted item is stored in 'nann_quoted'. | NameAnnQuote { - nann_quote :: AnnAnchor, + nann_quote :: EpaAnchor, nann_quoted :: SrcSpanAnnN, nann_trailing :: [TrailingAnn] } @@ -827,12 +827,12 @@ addTrailingAnnToA _ t cs n = n { anns = addTrailing (anns n) -- | Helper function used in the parser to add a comma location to an -- existing annotation. -addTrailingCommaToN :: SrcSpan -> EpAnn' NameAnn -> AnnAnchor -> EpAnn' NameAnn +addTrailingCommaToN :: SrcSpan -> EpAnn' NameAnn -> EpaAnchor -> EpAnn' NameAnn addTrailingCommaToN s EpAnnNotUsed l = EpAnn (spanAsAnchor s) (NameAnnTrailing [AddCommaAnn l]) noCom addTrailingCommaToN _ n l = n { anns = addTrailing (anns n) l } where - addTrailing :: NameAnn -> AnnAnchor -> NameAnn + addTrailing :: NameAnn -> EpaAnchor -> NameAnn addTrailing n l = n { nann_trailing = AddCommaAnn l : nann_trailing n } -- --------------------------------------------------------------------- diff --git a/compiler/GHC/Parser/PostProcess.hs b/compiler/GHC/Parser/PostProcess.hs index 18881dbe4c..2a70119fcf 100644 --- a/compiler/GHC/Parser/PostProcess.hs +++ b/compiler/GHC/Parser/PostProcess.hs @@ -1019,7 +1019,7 @@ checkContext :: LHsType GhcPs -> P (LHsContext GhcPs) checkContext orig_t@(L (SrcSpanAnn _ l) _orig_t) = check ([],[],noCom) orig_t where - check :: ([AnnAnchor],[AnnAnchor],EpAnnComments) + check :: ([EpaAnchor],[EpaAnchor],EpAnnComments) -> LHsType GhcPs -> P (LHsContext GhcPs) check (oparens,cparens,cs) (L _l (HsTupleTy ann' HsBoxedOrConstraintTuple ts)) -- (Eq a, Ord b) shows up as a tuple type. Only boxed tuples can @@ -1044,8 +1044,8 @@ checkContext orig_t@(L (SrcSpanAnn _ l) _orig_t) = check (_opi,_cpi,_csi) _t = return (L (SrcSpanAnn (EpAnn (spanAsAnchor l) (AnnContext Nothing [] []) noCom) l) [orig_t]) -checkImportDecl :: Maybe AnnAnchor - -> Maybe AnnAnchor +checkImportDecl :: Maybe EpaAnchor + -> Maybe EpaAnchor -> P () checkImportDecl mPre mPost = do let whenJust mg f = maybe (pure ()) f mg @@ -1056,18 +1056,18 @@ checkImportDecl mPre mPost = do -- 'ImportQualifiedPost' is not in effect. whenJust mPost $ \post -> when (not importQualifiedPostEnabled) $ - failOpNotEnabledImportQualifiedPost (RealSrcSpan (annAnchorRealSrcSpan post) Nothing) + failOpNotEnabledImportQualifiedPost (RealSrcSpan (epaAnchorRealSrcSpan post) Nothing) -- Error if 'qualified' occurs in both pre and postpositive -- positions. whenJust mPost $ \post -> when (isJust mPre) $ - failOpImportQualifiedTwice (RealSrcSpan (annAnchorRealSrcSpan post) Nothing) + failOpImportQualifiedTwice (RealSrcSpan (epaAnchorRealSrcSpan post) Nothing) -- Warn if 'qualified' found in prepositive position and -- 'Opt_WarnPrepositiveQualifiedModule' is enabled. whenJust mPre $ \pre -> - warnPrepositiveQualifiedModule (RealSrcSpan (annAnchorRealSrcSpan pre) Nothing) + warnPrepositiveQualifiedModule (RealSrcSpan (epaAnchorRealSrcSpan pre) Nothing) -- ------------------------------------------------------------------------- -- Checking Patterns. @@ -2611,7 +2611,7 @@ data ImpExpSubSpec = ImpExpAbs | ImpExpAllWith [LocatedA ImpExpQcSpec] data ImpExpQcSpec = ImpExpQcName (LocatedN RdrName) - | ImpExpQcType AnnAnchor (LocatedN RdrName) + | ImpExpQcType EpaAnchor (LocatedN RdrName) | ImpExpQcWildcard mkModuleImpExp :: [AddEpAnn] -> LocatedA ImpExpQcSpec -> ImpExpSubSpec -> P (IE GhcPs) @@ -2885,7 +2885,7 @@ mkSumOrTupleExpr l boxity (Tuple es) anns = do cs <- getCommentsFor (locA l) return $ L l (ExplicitTuple (EpAnn (spanAsAnchor $ locA l) anns cs) (map toTupArg es) boxity) where - toTupArg :: Either (EpAnn' AnnAnchor) (LHsExpr GhcPs) -> HsTupArg GhcPs + toTupArg :: Either (EpAnn' EpaAnchor) (LHsExpr GhcPs) -> HsTupArg GhcPs toTupArg (Left ann) = missingTupArg ann toTupArg (Right a) = Present noAnn a @@ -2912,7 +2912,7 @@ mkSumOrTuplePat l boxity (Tuple ps) anns = do cs <- getCommentsFor (locA l) return $ L l (PatBuilderPat (TuplePat (EpAnn (spanAsAnchor $ locA l) anns cs) ps' boxity)) where - toTupPat :: Either (EpAnn' AnnAnchor) (LocatedA (PatBuilder GhcPs)) -> PV (LPat GhcPs) + toTupPat :: Either (EpAnn' EpaAnchor) (LocatedA (PatBuilder GhcPs)) -> PV (LPat GhcPs) -- Ignore the element location so that the error message refers to the -- entire tuple. See #19504 (and the discussion) for details. toTupPat p = case p of diff --git a/compiler/GHC/Parser/Types.hs b/compiler/GHC/Parser/Types.hs index 5c3ff72597..2f5f304009 100644 --- a/compiler/GHC/Parser/Types.hs +++ b/compiler/GHC/Parser/Types.hs @@ -26,9 +26,9 @@ import GHC.Parser.Annotation import Language.Haskell.Syntax data SumOrTuple b - = Sum ConTag Arity (LocatedA b) [AnnAnchor] [AnnAnchor] + = Sum ConTag Arity (LocatedA b) [EpaAnchor] [EpaAnchor] -- ^ Last two are the locations of the '|' before and after the payload - | Tuple [Either (EpAnn' AnnAnchor) (LocatedA b)] + | Tuple [Either (EpAnn' EpaAnchor) (LocatedA b)] pprSumOrTuple :: Outputable b => Boxity -> SumOrTuple b -> SDoc pprSumOrTuple boxity = \case |