Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Core Exact Print Annotation types
- In-tree Exact Print Annotations
- Comments in Annotations
- Annotations in
GenLocated
- Annotation data types used in
GenLocated
- Trailing annotations in lists
- Utilities for converting between different
GenLocated
when - we do not care about the annotations.
- Building up annotations
- Querying annotations
- Working with locations of annotations
- Constructing
GenLocated
annotation types when we do not care about annotations. - Working with comments in annotations
Synopsis
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnClosePH
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnOpenPH
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | AnnPercentOne
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- data EpaComment = EpaComment {}
- data EpaCommentTok
- data IsUnicodeSyntax
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- data HasE
- data AddEpAnn = AddEpAnn AnnKeywordId EpaAnchor
- data EpaAnchor
- = AR RealSrcSpan
- | AD DeltaPos
- epaAnchorRealSrcSpan :: EpaAnchor -> RealSrcSpan
- data DeltaPos = DP {
- deltaLine :: !Int
- deltaColumn :: !Int
- type EpAnn = EpAnn' [AddEpAnn]
- data EpAnn' ann
- = EpAnn {
- entry :: Anchor
- anns :: ann
- comments :: EpAnnComments
- | EpAnnNotUsed
- = EpAnn {
- data Anchor = Anchor {}
- data AnchorOperation
- spanAsAnchor :: SrcSpan -> Anchor
- realSpanAsAnchor :: RealSrcSpan -> Anchor
- noAnn :: EpAnn' a
- data EpAnnComments
- = EpaComments {
- priorComments :: ![LEpaComment]
- | EpaCommentsBalanced {
- priorComments :: ![LEpaComment]
- followingComments :: ![LEpaComment]
- = EpaComments {
- type LEpaComment = GenLocated Anchor EpaComment
- com :: [LEpaComment] -> EpAnnComments
- noCom :: EpAnnComments
- getFollowingComments :: EpAnnComments -> [LEpaComment]
- setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments
- type EpAnnCO = EpAnn' NoEpAnns
- type LocatedA = GenLocated SrcSpanAnnA
- type LocatedL = GenLocated SrcSpanAnnL
- type LocatedC = GenLocated SrcSpanAnnC
- type LocatedN = GenLocated SrcSpanAnnN
- type LocatedAn an = GenLocated (SrcAnn an)
- type LocatedP = GenLocated SrcSpanAnnP
- type SrcSpanAnnA = SrcAnn AnnListItem
- type SrcSpanAnnL = SrcAnn AnnList
- type SrcSpanAnnP = SrcAnn AnnPragma
- type SrcSpanAnnC = SrcAnn AnnContext
- type SrcSpanAnnN = SrcAnn NameAnn
- data SrcSpanAnn' a = SrcSpanAnn {}
- data AnnListItem = AnnListItem {
- lann_trailing :: [TrailingAnn]
- data AnnList = AnnList {}
- data AnnParen = AnnParen {}
- data ParenType
- parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId)
- data AnnPragma = AnnPragma {}
- data AnnContext = AnnContext {}
- data NameAnn
- = NameAnn { }
- | NameAnnCommas { }
- | NameAnnOnly { }
- | NameAnnRArrow { }
- | NameAnnQuote { }
- | NameAnnTrailing {
- nann_trailing :: [TrailingAnn]
- data NameAdornment
- data NoEpAnns = NoEpAnns
- data AnnSortKey
- data TrailingAnn
- addTrailingAnnToA :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn' AnnListItem -> EpAnn' AnnListItem
- addTrailingAnnToL :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn' AnnList -> EpAnn' AnnList
- addTrailingCommaToN :: SrcSpan -> EpAnn' NameAnn -> EpaAnchor -> EpAnn' NameAnn
- la2na :: SrcSpanAnn' a -> SrcSpanAnnN
- na2la :: SrcSpanAnn' a -> SrcAnn ann
- n2l :: LocatedN a -> LocatedA a
- l2n :: LocatedAn a1 a2 -> LocatedN a2
- l2l :: SrcSpanAnn' a -> SrcAnn ann
- la2la :: LocatedAn ann1 a2 -> LocatedAn ann2 a2
- reLoc :: LocatedAn a e -> Located e
- reLocA :: Located e -> LocatedAn ann e
- reLocL :: LocatedN e -> LocatedA e
- reLocC :: LocatedN e -> LocatedC e
- reLocN :: LocatedN a -> Located a
- la2r :: SrcSpanAnn' a -> RealSrcSpan
- realSrcSpan :: SrcSpan -> RealSrcSpan
- extraToAnnList :: AnnList -> [AddEpAnn] -> AnnList
- reAnn :: [TrailingAnn] -> EpAnnComments -> Located a -> LocatedA a
- reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e
- reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a
- addAnns :: EpAnn -> [AddEpAnn] -> EpAnnComments -> EpAnn
- addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA
- widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan
- widenAnchor :: Anchor -> [AddEpAnn] -> Anchor
- widenAnchorR :: Anchor -> RealSrcSpan -> Anchor
- widenLocatedAn :: SrcSpanAnn' an -> [AddEpAnn] -> SrcSpanAnn' an
- getLocAnn :: Located a -> SrcSpanAnnA
- epAnnAnns :: EpAnn -> [AddEpAnn]
- epAnnAnnsL :: EpAnn' a -> [a]
- annParen2AddEpAnn :: EpAnn' AnnParen -> [AddEpAnn]
- epAnnComments :: EpAnn' an -> EpAnnComments
- sortLocatedA :: [GenLocated (SrcSpanAnn' a) e] -> [GenLocated (SrcSpanAnn' a) e]
- mapLocA :: (a -> b) -> GenLocated SrcSpan a -> GenLocated (SrcAnn ann) b
- combineLocsA :: Semigroup a => GenLocated (SrcSpanAnn' a) e1 -> GenLocated (SrcSpanAnn' a) e2 -> SrcSpanAnn' a
- combineSrcSpansA :: Semigroup a => SrcSpanAnn' a -> SrcSpanAnn' a -> SrcSpanAnn' a
- addCLocA :: GenLocated (SrcSpanAnn' a) e1 -> GenLocated SrcSpan e2 -> e3 -> GenLocated (SrcAnn ann) e3
- addCLocAA :: GenLocated (SrcSpanAnn' a1) e1 -> GenLocated (SrcSpanAnn' a2) e2 -> e3 -> GenLocated (SrcAnn ann) e3
- noLocA :: a -> LocatedAn an a
- getLocA :: GenLocated (SrcSpanAnn' a) e -> SrcSpan
- noSrcSpanA :: SrcAnn ann
- noAnnSrcSpan :: SrcSpan -> SrcAnn ann
- noComments :: EpAnnCO
- comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO
- addCommentsToSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann
- setCommentsSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann
- addCommentsToEpAnn :: Monoid a => SrcSpan -> EpAnn' a -> EpAnnComments -> EpAnn' a
- setCommentsEpAnn :: Monoid a => SrcSpan -> EpAnn' a -> EpAnnComments -> EpAnn' a
- transferComments :: Monoid ann => SrcAnn ann -> SrcAnn ann -> (SrcAnn ann, SrcAnn ann)
- placeholderRealSpan :: RealSrcSpan
Core Exact Print Annotation types
data AnnKeywordId Source #
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
.HsParsedModule
The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/in-tree-api-annotations
Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [exact print annotations] above for details of the usage
AnnAnyclass | |
AnnAs | |
AnnAt | |
AnnBang |
|
AnnBackquote | '`' |
AnnBy | |
AnnCase | case or lambda case |
AnnClass | |
AnnClose | '#)' or '#-}' etc |
AnnCloseB | '|)' |
AnnCloseBU | '|)', unicode variant |
AnnCloseC | '}' |
AnnCloseQ | '|]' |
AnnCloseQU | '|]', unicode variant |
AnnCloseP | ')' |
AnnClosePH | '#)' |
AnnCloseS | ']' |
AnnColon | |
AnnComma | as a list separator |
AnnCommaTuple | in a RdrName for a tuple |
AnnDarrow | '=>' |
AnnDarrowU | '=>', unicode variant |
AnnData | |
AnnDcolon | '::' |
AnnDcolonU | '::', unicode variant |
AnnDefault | |
AnnDeriving | |
AnnDo | |
AnnDot | |
AnnDotdot | '..' |
AnnElse | |
AnnEqual | |
AnnExport | |
AnnFamily | |
AnnForall | |
AnnForallU | Unicode variant |
AnnForeign | |
AnnFunId | for function name in matches where there are multiple equations for the function. |
AnnGroup | |
AnnHeader | for CType |
AnnHiding | |
AnnIf | |
AnnImport | |
AnnIn | |
AnnInfix | 'infix' or 'infixl' or 'infixr' |
AnnInstance | |
AnnLam | |
AnnLarrow | '<-' |
AnnLarrowU | '<-', unicode variant |
AnnLet | |
AnnLollyU | The |
AnnMdo | |
AnnMinus | |
AnnModule | |
AnnNewtype | |
AnnName | where a name loses its location in the AST, this carries it |
AnnOf | |
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
|
AnnOpenB | '(|' |
AnnOpenBU | '(|', unicode variant |
AnnOpenC | '{' |
AnnOpenE | '[e|' or '[e||' |
AnnOpenEQ | '[|' |
AnnOpenEQU | '[|', unicode variant |
AnnOpenP | '(' |
AnnOpenS | '[' |
AnnOpenPH | '(#' |
AnnDollar | prefix |
AnnDollarDollar | prefix |
AnnPackageName | |
AnnPattern | |
AnnPercent |
|
AnnPercentOne | '%1' -- for HsLinearArrow |
AnnProc | |
AnnQualified | |
AnnRarrow |
|
AnnRarrowU |
|
AnnRec | |
AnnRole | |
AnnSafe | |
AnnSemi | ';' |
AnnSimpleQuote | ''' |
AnnSignature | |
AnnStatic |
|
AnnStock | |
AnnThen | |
AnnThTyQuote | double ''' |
AnnTilde |
|
AnnType | |
AnnUnit |
|
AnnUsing | |
AnnVal | e.g. INTEGER |
AnnValStr | String value, will need quotes when output |
AnnVbar | '|' |
AnnVia |
|
AnnWhere | |
Annlarrowtail |
|
AnnlarrowtailU |
|
Annrarrowtail |
|
AnnrarrowtailU |
|
AnnLarrowtail |
|
AnnLarrowtailU |
|
AnnRarrowtail |
|
AnnRarrowtailU |
|
Instances
data EpaComment Source #
EpaComment | |
|
Instances
data EpaCommentTok Source #
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 |
Instances
data IsUnicodeSyntax Source #
Certain tokens can have alternate representations when unicode syntax is
enabled. This flag is attached to those tokens in the lexer so that the
original source representation can be reproduced in the corresponding
EpAnnotation
Instances
unicodeAnn :: AnnKeywordId -> AnnKeywordId Source #
Convert a normal annotation into its unicode equivalent one
Some template haskell tokens have two variants, one with an e
the other
not:
[| or [e| [|| or [e||
This type indicates whether the e
is present or not.
Instances
Data HasE # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HasE -> c HasE Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HasE Source # toConstr :: HasE -> Constr Source # dataTypeOf :: HasE -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HasE) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HasE) Source # gmapT :: (forall b. Data b => b -> b) -> HasE -> HasE Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HasE -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HasE -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HasE -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HasE -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HasE -> m HasE Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HasE -> m HasE Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HasE -> m HasE Source # | |
Show HasE # | |
Eq HasE # | |
Ord HasE # | |
In-tree Exact Print Annotations
Captures an annotation, storing the
and its
location. The parser only ever inserts AnnKeywordId
fields with a
RealSrcSpan being the original location of the annotation in the
source file.
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 EpaAnchor
AddEpAnn
is created is using the mj
("make
jump") function, and then it can be inserted into the appropriate
annotation.
Instances
Data AddEpAnn # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddEpAnn -> c AddEpAnn Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddEpAnn Source # toConstr :: AddEpAnn -> Constr Source # dataTypeOf :: AddEpAnn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AddEpAnn) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddEpAnn) Source # gmapT :: (forall b. Data b => b -> b) -> AddEpAnn -> AddEpAnn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddEpAnn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddEpAnn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AddEpAnn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AddEpAnn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddEpAnn -> m AddEpAnn Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddEpAnn -> m AddEpAnn Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddEpAnn -> m AddEpAnn Source # | |
Show AddEpAnn # | |
Outputable AddEpAnn # | |
Eq AddEpAnn # | |
Ord AddEpAnn # | |
Defined in GHC.Parser.Annotation |
The anchor for an
. The Parser inserts the AnnKeywordId
variant, giving the exact location of the original item in the
parsed source. This can be replace by the AR
version, to
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.AD
Instances
Data EpaAnchor # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpaAnchor -> c EpaAnchor Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpaAnchor Source # toConstr :: EpaAnchor -> Constr Source # dataTypeOf :: EpaAnchor -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpaAnchor) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpaAnchor) Source # gmapT :: (forall b. Data b => b -> b) -> EpaAnchor -> EpaAnchor Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpaAnchor -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpaAnchor -> r Source # gmapQ :: (forall d. Data d => d -> u) -> EpaAnchor -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpaAnchor -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpaAnchor -> m EpaAnchor Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpaAnchor -> m EpaAnchor Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpaAnchor -> m EpaAnchor Source # | |
Show EpaAnchor # | |
Outputable EpaAnchor # | |
Eq EpaAnchor # | |
Ord EpaAnchor # | |
Defined in GHC.Parser.Annotation |
Relative position, line then column. If deltaLine
is zero then
deltaColumn
gives the number of spaces between the end of the
preceding output element and the start of the one this is attached
to, on the same line. If deltaLine
is > 0, then it is the number
of lines to advance, and deltaColumn
is the start column on the
new line.
DP | |
|
Instances
Data DeltaPos # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeltaPos -> c DeltaPos Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeltaPos Source # toConstr :: DeltaPos -> Constr Source # dataTypeOf :: DeltaPos -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeltaPos) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeltaPos) Source # gmapT :: (forall b. Data b => b -> b) -> DeltaPos -> DeltaPos Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DeltaPos -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeltaPos -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos Source # | |
Show DeltaPos # | |
Outputable DeltaPos # | |
Eq DeltaPos # | |
Ord DeltaPos # | |
Defined in GHC.Parser.Annotation |
The API Annotations are now kept in the HsSyn AST for the GhcPs phase. We do not always have API Annotations though, only for parsed code. This type captures that, and allows the representation decision to be easily revisited as it evolves.
A goal of the annotations is that an AST can be edited, including moving subtrees from one place to another, duplicating them, and so on. This means that each fragment must be self-contained. To this end, each annotated fragment keeps track of the anchor position it was originally captured at, being simply the start span of the topmost element of the ast fragment. This gives us a way to later re-calculate all Located items in this layer of the AST, as well as any annotations captured. The comments associated with the AST fragment are also captured here.
The ann
type parameter allows this general structure to be
specialised to the specific set of locations of original API
Annotation elements. So for HsLet
we have
type instance XLet GhcPs = EpAnn' AnnsLet data AnnsLet = AnnsLet { alLet :: EpaAnchor, alIn :: EpaAnchor } deriving Data
The spacing between the items under the scope of a given EpAnn' is
derived from the original Anchor
. But there is no requirement
that the items included in the sub-element have a "matching"
location in their relative anchors. This allows us to freely move
elements around, and stitch together new AST fragments out of old
ones, and have them still printed out in a reasonable way.
EpAnn | |
EpAnnNotUsed | No Annotation for generated code, e.g. from TH, deriving, etc. |
Instances
An Anchor
records the base location for the start of the
syntactic element holding the annotations, and is used as the point
of reference for calculating delta positions for contained
annotations. If an AST element is moved or deleted, the original
location is also tracked, for printing the source without gaps.
Anchor | |
|
Instances
Data Anchor # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Anchor -> c Anchor Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Anchor Source # toConstr :: Anchor -> Constr Source # dataTypeOf :: Anchor -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Anchor) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Anchor) Source # gmapT :: (forall b. Data b => b -> b) -> Anchor -> Anchor Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Anchor -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Anchor -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Anchor -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Anchor -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Anchor -> m Anchor Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Anchor -> m Anchor Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Anchor -> m Anchor Source # | |
Semigroup Anchor # | |
Show Anchor # | |
Outputable Anchor # | |
Eq Anchor # | |
Ord Anchor # | |
Outputable (GenLocated Anchor EpaComment) # | |
Defined in GHC.Parser.Annotation ppr :: GenLocated Anchor EpaComment -> SDoc Source # |
data AnchorOperation Source #
If tools modify the parsed source, the MovedAnchor
variant can
directly provide the spacing for this item relative to the previous
one when printing. This allows AST fragments with a particular
anchor to be freely moved, without worrying about recalculating the
appropriate anchor span.
Instances
spanAsAnchor :: SrcSpan -> Anchor Source #
realSpanAsAnchor :: RealSrcSpan -> Anchor Source #
Short form for EpAnnNotUsed
Comments in Annotations
data EpAnnComments Source #
When we are parsing we add comments that belong a particular AST
element, and print them together with the element, interleaving
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 EpaCommentsBalanced
constructor is used to do
this. The GHC parser will only insert the EpaComments
form.
EpaComments | |
| |
EpaCommentsBalanced | |
|
Instances
type LEpaComment = GenLocated Anchor EpaComment Source #
com :: [LEpaComment] -> EpAnnComments Source #
setFollowingComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments Source #
setPriorComments :: EpAnnComments -> [LEpaComment] -> EpAnnComments Source #
Annotations in GenLocated
type LocatedA = GenLocated SrcSpanAnnA Source #
type LocatedL = GenLocated SrcSpanAnnL Source #
type LocatedC = GenLocated SrcSpanAnnC Source #
type LocatedN = GenLocated SrcSpanAnnN Source #
type LocatedAn an = GenLocated (SrcAnn an) Source #
General representation of a GenLocated
type carrying a
parameterised annotation type.
type LocatedP = GenLocated SrcSpanAnnP Source #
type SrcSpanAnnA = SrcAnn AnnListItem Source #
type SrcSpanAnnL = SrcAnn AnnList Source #
type SrcSpanAnnP = SrcAnn AnnPragma Source #
type SrcSpanAnnC = SrcAnn AnnContext Source #
type SrcSpanAnnN = SrcAnn NameAnn Source #
data SrcSpanAnn' a Source #
The 'SrcSpanAnn'' type wraps a normal SrcSpan
, together with
an extra annotation type. This is mapped to a specific GenLocated
usage in the AST through the XRec
and Anno
type families.
Instances
Annotation data types used in GenLocated
data AnnListItem Source #
Annotation for items appearing in a list. They can have one or more trailing punctuations items, such as commas or semicolons.
Instances
Annotation for the "container" of a list. This captures surrounding items such as braces if present, and introductory keywords such as 'where'.
Instances
Data AnnList # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnList -> c AnnList Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnList Source # toConstr :: AnnList -> Constr Source # dataTypeOf :: AnnList -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnList) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnList) Source # gmapT :: (forall b. Data b => b -> b) -> AnnList -> AnnList Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnList -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnList -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnList -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnList -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnList -> m AnnList Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnList -> m AnnList Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnList -> m AnnList Source # | |
Monoid AnnList # | |
Semigroup AnnList # | |
Outputable AnnList # | |
Eq AnnList # | |
Binary a => Binary (LocatedL a) # | |
API Annotation for an item having surrounding "brackets", such as tuples or lists
Instances
Data AnnParen # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnParen -> c AnnParen Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnParen Source # toConstr :: AnnParen -> Constr Source # dataTypeOf :: AnnParen -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnParen) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnParen) Source # gmapT :: (forall b. Data b => b -> b) -> AnnParen -> AnnParen Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnParen -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnParen -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnParen -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnParen -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnParen -> m AnnParen Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnParen -> m AnnParen Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnParen -> m AnnParen Source # |
Detail of the "brackets" used in an AnnParen
API Annotation.
AnnParens | '(', ')' |
AnnParensHash | '(#', '#)' |
AnnParensSquare | '[', ']' |
Instances
Data ParenType # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParenType -> c ParenType Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParenType Source # toConstr :: ParenType -> Constr Source # dataTypeOf :: ParenType -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParenType) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParenType) Source # gmapT :: (forall b. Data b => b -> b) -> ParenType -> ParenType Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParenType -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParenType -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ParenType -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParenType -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParenType -> m ParenType Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParenType -> m ParenType Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParenType -> m ParenType Source # | |
Eq ParenType # | |
Ord ParenType # | |
Defined in GHC.Parser.Annotation |
parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId) Source #
Maps the ParenType
to the related opening and closing
AnnKeywordId. Used when actually printing the item.
API Annotation used for capturing the locations of annotations in pragmas.
Instances
Data AnnPragma # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnPragma -> c AnnPragma Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnPragma Source # toConstr :: AnnPragma -> Constr Source # dataTypeOf :: AnnPragma -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnPragma) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnPragma) Source # gmapT :: (forall b. Data b => b -> b) -> AnnPragma -> AnnPragma Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnPragma -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnPragma -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnPragma -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnPragma -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnPragma -> m AnnPragma Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnPragma -> m AnnPragma Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnPragma -> m AnnPragma Source # | |
Outputable AnnPragma # | |
Eq AnnPragma # | |
data AnnContext Source #
API Annotation for the Context
data type.
Instances
Data AnnContext # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnContext -> c AnnContext Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnContext Source # toConstr :: AnnContext -> Constr Source # dataTypeOf :: AnnContext -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnContext) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnContext) Source # gmapT :: (forall b. Data b => b -> b) -> AnnContext -> AnnContext Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnContext -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnContext -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnContext -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnContext -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnContext -> m AnnContext Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnContext -> m AnnContext Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnContext -> m AnnContext Source # | |
Outputable AnnContext # | |
Defined in GHC.Parser.Annotation ppr :: AnnContext -> SDoc Source # |
API Annotations for a RdrName
. There are many kinds of
adornment that can be attached to a given RdrName
. This type
captures them, as detailed on the individual constructors.
NameAnn | Used for a name with an adornment, so |
NameAnnCommas | |
| |
NameAnnOnly | Used for |
NameAnnRArrow | Used for |
| |
NameAnnQuote | Used for an item with a leading |
NameAnnTrailing | Used when adding a |
|
Instances
Data NameAnn # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameAnn -> c NameAnn Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameAnn Source # toConstr :: NameAnn -> Constr Source # dataTypeOf :: NameAnn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameAnn) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameAnn) Source # gmapT :: (forall b. Data b => b -> b) -> NameAnn -> NameAnn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameAnn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameAnn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NameAnn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NameAnn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameAnn -> m NameAnn Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameAnn -> m NameAnn Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameAnn -> m NameAnn Source # | |
Monoid NameAnn # | |
Semigroup NameAnn # | |
Outputable NameAnn # | |
Eq NameAnn # | |
type Anno (LocatedN Name) # | |
Defined in GHC.Hs.Binds | |
type Anno (LocatedN RdrName) # | |
Defined in GHC.Hs.Binds | |
type Anno (LocatedN Id) # | |
Defined in GHC.Hs.Binds | |
type Anno [LocatedN Name] # | |
Defined in GHC.Hs.Binds | |
type Anno [LocatedN RdrName] # | |
Defined in GHC.Hs.Binds | |
type Anno [LocatedN Id] # | |
Defined in GHC.Hs.Binds |
data NameAdornment Source #
A NameAnn
can capture the locations of surrounding adornments,
such as parens or backquotes. This data type identifies what
particular pair are being used.
NameParens | '(' ')' |
NameParensHash | '(#' '#)' |
NameBackquotes | '`' |
NameSquare | '[' ']' |
Instances
Instances
Data NoEpAnns # | |
Defined in GHC.Parser.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoEpAnns -> c NoEpAnns Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoEpAnns Source # toConstr :: NoEpAnns -> Constr Source # dataTypeOf :: NoEpAnns -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoEpAnns) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoEpAnns) Source # gmapT :: (forall b. Data b => b -> b) -> NoEpAnns -> NoEpAnns Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoEpAnns -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoEpAnns -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NoEpAnns -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoEpAnns -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoEpAnns -> m NoEpAnns Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoEpAnns -> m NoEpAnns Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoEpAnns -> m NoEpAnns Source # | |
Eq NoEpAnns # | |
Ord NoEpAnns # | |
Defined in GHC.Parser.Annotation |
data AnnSortKey Source #
Captures the sort order of sub elements. This is needed when the sub-elements have been split (as in a HsLocalBind which holds separate binds and sigs) or for infix patterns where the order has been re-arranged. It is captured explicitly so that after the Delta phase a SrcSpan is used purely as an index into the annotations, allowing transformations of the AST including the introduction of new Located items or re-arranging existing ones.
Instances
Trailing annotations in lists
data TrailingAnn Source #
Captures the location of punctuation occuring between items, normally in a list. It is captured as a trailing annotation.
AddSemiAnn EpaAnchor | Trailing ';' |
AddCommaAnn EpaAnchor | Trailing ',' |
AddVbarAnn EpaAnchor | Trailing '|' |
AddRarrowAnn EpaAnchor | Trailing |
AddRarrowAnnU EpaAnchor | Trailing |
Instances
addTrailingAnnToA :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn' AnnListItem -> EpAnn' AnnListItem Source #
Helper function used in the parser to add a TrailingAnn
items
to an existing annotation.
addTrailingAnnToL :: SrcSpan -> TrailingAnn -> EpAnnComments -> EpAnn' AnnList -> EpAnn' AnnList Source #
Helper function used in the parser to add a TrailingAnn
items
to an existing annotation.
addTrailingCommaToN :: SrcSpan -> EpAnn' NameAnn -> EpaAnchor -> EpAnn' NameAnn Source #
Helper function used in the parser to add a comma location to an existing annotation.
Utilities for converting between different GenLocated
when
we do not care about the annotations.
la2na :: SrcSpanAnn' a -> SrcSpanAnnN Source #
Helper function (temporary) during transition of names Discards any annotations
na2la :: SrcSpanAnn' a -> SrcAnn ann Source #
Helper function (temporary) during transition of names Discards any annotations
l2n :: LocatedAn a1 a2 -> LocatedN a2 Source #
Helper function (temporary) during transition of names Discards any annotations
l2l :: SrcSpanAnn' a -> SrcAnn ann Source #
la2la :: LocatedAn ann1 a2 -> LocatedAn ann2 a2 Source #
Helper function (temporary) during transition of names Discards any annotations
la2r :: SrcSpanAnn' a -> RealSrcSpan Source #
realSrcSpan :: SrcSpan -> RealSrcSpan Source #
Building up annotations
reAnn :: [TrailingAnn] -> EpAnnComments -> Located a -> LocatedA a Source #
reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e Source #
reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a Source #
addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA Source #
widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan Source #
The annotations need to all come after the anchor. Make sure this is the case.
widenAnchorR :: Anchor -> RealSrcSpan -> Anchor Source #
widenLocatedAn :: SrcSpanAnn' an -> [AddEpAnn] -> SrcSpanAnn' an Source #
Querying annotations
getLocAnn :: Located a -> SrcSpanAnnA Source #
epAnnAnnsL :: EpAnn' a -> [a] Source #
epAnnComments :: EpAnn' an -> EpAnnComments Source #
Working with locations of annotations
sortLocatedA :: [GenLocated (SrcSpanAnn' a) e] -> [GenLocated (SrcSpanAnn' a) e] Source #
mapLocA :: (a -> b) -> GenLocated SrcSpan a -> GenLocated (SrcAnn ann) b Source #
combineLocsA :: Semigroup a => GenLocated (SrcSpanAnn' a) e1 -> GenLocated (SrcSpanAnn' a) e2 -> SrcSpanAnn' a Source #
combineSrcSpansA :: Semigroup a => SrcSpanAnn' a -> SrcSpanAnn' a -> SrcSpanAnn' a Source #
addCLocA :: GenLocated (SrcSpanAnn' a) e1 -> GenLocated SrcSpan e2 -> e3 -> GenLocated (SrcAnn ann) e3 Source #
Combine locations from two Located
things and add them to a third thing
addCLocAA :: GenLocated (SrcSpanAnn' a1) e1 -> GenLocated (SrcSpanAnn' a2) e2 -> e3 -> GenLocated (SrcAnn ann) e3 Source #
Constructing GenLocated
annotation types when we do not care about annotations.
getLocA :: GenLocated (SrcSpanAnn' a) e -> SrcSpan Source #
noSrcSpanA :: SrcAnn ann Source #
noAnnSrcSpan :: SrcSpan -> SrcAnn ann Source #
Working with comments in annotations
noComments :: EpAnnCO Source #
comment :: RealSrcSpan -> EpAnnComments -> EpAnnCO Source #
addCommentsToSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann Source #
Add additional comments to a SrcAnn
, used for manipulating the
AST prior to exact printing the changed one.
setCommentsSrcAnn :: Monoid ann => SrcAnn ann -> EpAnnComments -> SrcAnn ann Source #
Replace any existing comments on a SrcAnn
, used for manipulating the
AST prior to exact printing the changed one.
addCommentsToEpAnn :: Monoid a => SrcSpan -> EpAnn' a -> EpAnnComments -> EpAnn' a Source #
Add additional comments, used for manipulating the AST prior to exact printing the changed one.
setCommentsEpAnn :: Monoid a => SrcSpan -> EpAnn' a -> EpAnnComments -> EpAnn' a Source #
Replace any existing comments, used for manipulating the AST prior to exact printing the changed one.
transferComments :: Monoid ann => SrcAnn ann -> SrcAnn ann -> (SrcAnn ann, SrcAnn ann) Source #
Transfer comments from the annotations in one SrcAnn
to those
in another. The originals are not changed. This is used when
manipulating an AST prior to exact printing,