| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Parser.Annotation
Contents
- 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 GenLocatedwhen
- we do not care about the annotations.
- Building up annotations
- Querying annotations
- Working with locations of annotations
- Constructing GenLocatedannotation types when we do not care
- 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 EpaLocation
- data EpaLocation- = EpaSpan !RealSrcSpan
- | EpaDelta !DeltaPos ![LEpaComment]
 
- epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
- epaLocationFromSrcAnn :: SrcAnn ann -> EpaLocation
- data DeltaPos- = SameLine { - deltaColumn :: !Int
 
- | DifferentLine { - deltaLine :: !Int
- deltaColumn :: !Int
 
 
- = SameLine { 
- deltaPos :: Int -> Int -> DeltaPos
- getDeltaLine :: DeltaPos -> Int
- 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
- emptyComments :: 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 {}
- type SrcAnn ann = SrcSpanAnn' (EpAnn ann)
- data AnnListItem = AnnListItem {- lann_trailing :: [TrailingAnn]
 
- data AnnList = AnnList {}
- data AnnParen = AnnParen {}
- data ParenType
- parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId)
- data AnnPragma = AnnPragma {}
- data AnnContext = AnnContext {- ac_darrow :: Maybe (IsUnicodeSyntax, EpaLocation)
- ac_open :: [EpaLocation]
- ac_close :: [EpaLocation]
 
- 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 -> EpaLocation -> 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] -> [AddEpAnn] -> EpAnnComments -> EpAnn [AddEpAnn]
- 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] -> [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 (SrcAnn a) e1 -> GenLocated (SrcAnn a) e2 -> SrcAnn a
- combineSrcSpansA :: Semigroup a => SrcAnn a -> SrcAnn a -> SrcAnn 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
- transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA)
- commentsOnlyA :: Monoid ann => SrcAnn ann -> SrcAnn ann
- removeCommentsA :: 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 otherwise captured in the AST.
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
Constructors
| 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 #
Constructors
| EpaComment | |
| Fields 
 | |
Instances
data EpaCommentTok Source #
Constructors
| 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
Constructors
| UnicodeSyntax | |
| NormalSyntax | 
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
| Eq HasE Source # | |
| Data HasE Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HasE -> c HasE # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HasE # dataTypeOf :: HasE -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HasE) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HasE) # gmapT :: (forall b. Data b => b -> b) -> HasE -> HasE # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HasE -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HasE -> r # gmapQ :: (forall d. Data d => d -> u) -> HasE -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HasE -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HasE -> m HasE # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HasE -> m HasE # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HasE -> m HasE # | |
| Ord HasE Source # | |
| Show HasE Source # | |
In-tree Exact Print Annotations
Captures an annotation, storing the AnnKeywordIdEpaLocationEpaLocationAddEpAnn is created is using the mj ("make
 jump") function, and then it can be inserted into the appropriate
 annotation.
Constructors
| AddEpAnn AnnKeywordId EpaLocation | 
Instances
| Eq AddEpAnn Source # | |
| Data AddEpAnn Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddEpAnn -> c AddEpAnn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddEpAnn # toConstr :: AddEpAnn -> Constr # dataTypeOf :: AddEpAnn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AddEpAnn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddEpAnn) # gmapT :: (forall b. Data b => b -> b) -> AddEpAnn -> AddEpAnn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddEpAnn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddEpAnn -> r # gmapQ :: (forall d. Data d => d -> u) -> AddEpAnn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AddEpAnn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddEpAnn -> m AddEpAnn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddEpAnn -> m AddEpAnn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddEpAnn -> m AddEpAnn # | |
| Ord AddEpAnn Source # | |
| Defined in GHC.Parser.Annotation | |
| Outputable AddEpAnn Source # | |
data EpaLocation Source #
The anchor for an AnnKeywordIdEpaSpanEpaDeltaEpaDelta
Constructors
| EpaSpan !RealSrcSpan | |
| EpaDelta !DeltaPos ![LEpaComment] | 
Instances
epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan Source #
Used in the parser only, extract the RealSrcSpan from an
 EpaLocation. The parser will never insert a DeltaPos, so the
 partial function is safe.
epaLocationFromSrcAnn :: SrcAnn ann -> EpaLocation Source #
Spacing between output items when exact printing.  It captures
 the spacing from the current print position on the page to the
 position required for the thing about to be printed.  This is
 either on the same line in which case is is simply the number of
 spaces to emit, or it is some number of lines down, with a given
 column offset.  The exact printing algorithm keeps track of the
 column offset pertaining to the current anchor position, so the
 deltaColumn is the additional spaces to add in this case.  See
 https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations for
 details.
Constructors
| SameLine | |
| Fields 
 | |
| DifferentLine | |
| Fields 
 | |
Instances
| Eq DeltaPos Source # | |
| Data DeltaPos Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeltaPos -> c DeltaPos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeltaPos # toConstr :: DeltaPos -> Constr # dataTypeOf :: DeltaPos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeltaPos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeltaPos) # gmapT :: (forall b. Data b => b -> b) -> DeltaPos -> DeltaPos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r # gmapQ :: (forall d. Data d => d -> u) -> DeltaPos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeltaPos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # | |
| Ord DeltaPos Source # | |
| Defined in GHC.Parser.Annotation | |
| Show DeltaPos Source # | |
| Outputable DeltaPos Source # | |
deltaPos :: Int -> Int -> DeltaPos Source #
Smart constructor for a DeltaPos. It preserves the invariant
 that for the DifferentLine constructor deltaLine is always > 0.
getDeltaLine :: DeltaPos -> Int Source #
The exact print annotations (EPAs) are kept in the HsSyn AST for the GhcPs phase. We do not always have EPAs though, only for code that has been parsed as they do not exist for generated code. This type captures that they may be missing.
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 exact
 print annotation elements.  So for HsLet we have
type instance XLet GhcPs = EpAnn AnnsLet data AnnsLet = AnnsLet { alLet :: EpaLocation, alIn :: EpaLocation } deriving Data
The spacing between the items under the scope of a given EpAnn is
 normally derived from the original Anchor.  But if a sub-element
 is not in its original position, the required spacing can be
 directly captured in the anchor_op field of the entry Anchor.
 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 precise way.
Constructors
| 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.
 It is also normally used as the reference point for the spacing of
 the element relative to its container. If it is moved, that
 relationship is tracked in the anchor_op instead.
Constructors
| Anchor | |
| Fields 
 | |
Instances
| Eq Anchor Source # | |
| Data Anchor Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Anchor -> c Anchor # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Anchor # toConstr :: Anchor -> Constr # dataTypeOf :: Anchor -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Anchor) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Anchor) # gmapT :: (forall b. Data b => b -> b) -> Anchor -> Anchor # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Anchor -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Anchor -> r # gmapQ :: (forall d. Data d => d -> u) -> Anchor -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Anchor -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Anchor -> m Anchor # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Anchor -> m Anchor # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Anchor -> m Anchor # | |
| Ord Anchor Source # | |
| Show Anchor Source # | |
| Semigroup Anchor Source # | |
| Outputable Anchor Source # | |
| Outputable (GenLocated Anchor EpaComment) Source # | |
| Defined in GHC.Parser.Annotation Methods 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.
Constructors
| UnchangedAnchor | |
| MovedAnchor DeltaPos | 
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 editing 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.
Constructors
| EpaComments | |
| Fields 
 | |
| EpaCommentsBalanced | |
| Fields 
 | |
Instances
type LEpaComment = GenLocated Anchor EpaComment 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.
Constructors
| SrcSpanAnn | |
Instances
type SrcAnn ann = SrcSpanAnn' (EpAnn ann) Source #
We mostly use 'SrcSpanAnn'' with an 'EpAnn''
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.
Constructors
| AnnListItem | |
| Fields 
 | |
Instances
Annotation for the "container" of a list. This captures surrounding items such as braces if present, and introductory keywords such as 'where'.
Constructors
| AnnList | |
Instances
| Eq AnnList Source # | |
| Data AnnList Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnList -> c AnnList # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnList # toConstr :: AnnList -> Constr # dataTypeOf :: AnnList -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnList) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnList) # gmapT :: (forall b. Data b => b -> b) -> AnnList -> AnnList # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnList -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnList -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnList -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnList -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnList -> m AnnList # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnList -> m AnnList # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnList -> m AnnList # | |
| Semigroup AnnList Source # | |
| Monoid AnnList Source # | |
| Outputable AnnList Source # | |
| Binary a => Binary (LocatedL a) Source # | |
exact print annotation for an item having surrounding "brackets", such as tuples or lists
Constructors
| AnnParen | |
| Fields | |
Instances
| Data AnnParen Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnParen -> c AnnParen # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnParen # toConstr :: AnnParen -> Constr # dataTypeOf :: AnnParen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnParen) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnParen) # gmapT :: (forall b. Data b => b -> b) -> AnnParen -> AnnParen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnParen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnParen -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnParen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnParen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnParen -> m AnnParen # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnParen -> m AnnParen # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnParen -> m AnnParen # | |
Detail of the "brackets" used in an AnnParen exact print annotation.
Constructors
| AnnParens | '(', ')' | 
| AnnParensHash | |
| AnnParensSquare | '[', ']' | 
Instances
| Eq ParenType Source # | |
| Data ParenType Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParenType -> c ParenType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParenType # toConstr :: ParenType -> Constr # dataTypeOf :: ParenType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParenType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParenType) # gmapT :: (forall b. Data b => b -> b) -> ParenType -> ParenType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParenType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParenType -> r # gmapQ :: (forall d. Data d => d -> u) -> ParenType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParenType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParenType -> m ParenType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParenType -> m ParenType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParenType -> m ParenType # | |
| Ord ParenType Source # | |
parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId) Source #
Maps the ParenType to the related opening and closing
 AnnKeywordId. Used when actually printing the item.
exact print annotation used for capturing the locations of annotations in pragmas.
Instances
| Eq AnnPragma Source # | |
| Data AnnPragma Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnPragma -> c AnnPragma # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnPragma # toConstr :: AnnPragma -> Constr # dataTypeOf :: AnnPragma -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnPragma) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnPragma) # gmapT :: (forall b. Data b => b -> b) -> AnnPragma -> AnnPragma # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnPragma -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnPragma -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnPragma -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnPragma -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnPragma -> m AnnPragma # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnPragma -> m AnnPragma # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnPragma -> m AnnPragma # | |
| Outputable AnnPragma Source # | |
data AnnContext Source #
Exact print annotation for the Context data type.
Constructors
| AnnContext | |
| Fields 
 | |
Instances
| Data AnnContext Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnContext -> c AnnContext # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnContext # toConstr :: AnnContext -> Constr # dataTypeOf :: AnnContext -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnContext) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnContext) # gmapT :: (forall b. Data b => b -> b) -> AnnContext -> AnnContext # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnContext -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnContext -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnContext -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnContext -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnContext -> m AnnContext # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnContext -> m AnnContext # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnContext -> m AnnContext # | |
| Outputable AnnContext Source # | |
| Defined in GHC.Parser.Annotation Methods ppr :: AnnContext -> SDoc Source # | |
exact print 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.
Constructors
| NameAnn | Used for a name with an adornment, so  | 
| Fields | |
| NameAnnCommas | |
| Fields | |
| NameAnnOnly | Used for  | 
| Fields | |
| NameAnnRArrow | Used for  | 
| Fields 
 | |
| NameAnnQuote | Used for an item with a leading  | 
| Fields | |
| NameAnnTrailing | Used when adding a  | 
| Fields 
 | |
Instances
| Eq NameAnn Source # | |
| Data NameAnn Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameAnn -> c NameAnn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameAnn # toConstr :: NameAnn -> Constr # dataTypeOf :: NameAnn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameAnn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameAnn) # gmapT :: (forall b. Data b => b -> b) -> NameAnn -> NameAnn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameAnn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameAnn -> r # gmapQ :: (forall d. Data d => d -> u) -> NameAnn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NameAnn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameAnn -> m NameAnn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameAnn -> m NameAnn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameAnn -> m NameAnn # | |
| Semigroup NameAnn Source # | |
| Monoid NameAnn Source # | |
| Outputable NameAnn Source # | |
| type Anno [LocatedN Name] Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno [LocatedN Id] Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno [LocatedN RdrName] Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno (LocatedN Name) Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno (LocatedN Id) Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno (LocatedN RdrName) Source # | |
| 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.
Constructors
| NameParens | '(' ')' | 
| NameParensHash | |
| NameBackquotes | '`' | 
| NameSquare | '[' ']' | 
Instances
Constructors
| NoEpAnns | 
Instances
| Eq NoEpAnns Source # | |
| Data NoEpAnns Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoEpAnns -> c NoEpAnns # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoEpAnns # toConstr :: NoEpAnns -> Constr # dataTypeOf :: NoEpAnns -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoEpAnns) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoEpAnns) # gmapT :: (forall b. Data b => b -> b) -> NoEpAnns -> NoEpAnns # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoEpAnns -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoEpAnns -> r # gmapQ :: (forall d. Data d => d -> u) -> NoEpAnns -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoEpAnns -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoEpAnns -> m NoEpAnns # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoEpAnns -> m NoEpAnns # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoEpAnns -> m NoEpAnns # | |
| Ord NoEpAnns Source # | |
| 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.
Constructors
| NoAnnSortKey | |
| AnnSortKey [RealSrcSpan] | 
Instances
| Eq AnnSortKey Source # | |
| Defined in GHC.Parser.Annotation | |
| Data AnnSortKey Source # | |
| Defined in GHC.Parser.Annotation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnSortKey -> c AnnSortKey # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnSortKey # toConstr :: AnnSortKey -> Constr # dataTypeOf :: AnnSortKey -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnSortKey) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnSortKey) # gmapT :: (forall b. Data b => b -> b) -> AnnSortKey -> AnnSortKey # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnSortKey -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnSortKey -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnSortKey -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnSortKey -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnSortKey -> m AnnSortKey # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnSortKey -> m AnnSortKey # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnSortKey -> m AnnSortKey # | |
| Semigroup AnnSortKey Source # | |
| Defined in GHC.Parser.Annotation Methods (<>) :: AnnSortKey -> AnnSortKey -> AnnSortKey # sconcat :: NonEmpty AnnSortKey -> AnnSortKey # stimes :: Integral b => b -> AnnSortKey -> AnnSortKey # | |
| Monoid AnnSortKey Source # | |
| Defined in GHC.Parser.Annotation Methods mempty :: AnnSortKey # mappend :: AnnSortKey -> AnnSortKey -> AnnSortKey # mconcat :: [AnnSortKey] -> AnnSortKey # | |
| Outputable AnnSortKey Source # | |
| Defined in GHC.Parser.Annotation Methods ppr :: AnnSortKey -> SDoc Source # | |
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.
Constructors
| AddSemiAnn EpaLocation | Trailing ';' | 
| AddCommaAnn EpaLocation | Trailing ',' | 
| AddVbarAnn EpaLocation | Trailing '|' | 
| AddRarrowAnn EpaLocation | Trailing  | 
| AddRarrowAnnU EpaLocation | Trailing  | 
| AddLollyAnnU EpaLocation | 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 -> EpaLocation -> 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 (SrcAnn a) e1 -> GenLocated (SrcAnn a) e2 -> SrcAnn 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
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.
transferAnnsA :: SrcSpanAnnA -> SrcSpanAnnA -> (SrcSpanAnnA, SrcSpanAnnA) Source #
Transfer comments and trailing items from the annotations in the
 first SrcSpanAnnA argument to those in the second.
commentsOnlyA :: Monoid ann => SrcAnn ann -> SrcAnn ann Source #
Remove the exact print annotations payload, leaving only the anchor and comments.
removeCommentsA :: SrcAnn ann -> SrcAnn ann Source #
Remove the comments, leaving the exact print annotations payload