ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Parser.Annotation

Synopsis

Documentation

getAnnotation :: ApiAnns -> RealSrcSpan -> AnnKeywordId -> [RealSrcSpan] Source #

Retrieve a list of annotation SrcSpans based on the SrcSpan of the annotated AST element, and the known type of the annotation.

getAndRemoveAnnotation :: ApiAnns -> RealSrcSpan -> AnnKeywordId -> ([RealSrcSpan], ApiAnns) Source #

Retrieve a list of annotation SrcSpans based on the SrcSpan of the annotated AST element, and the known type of the annotation. The list is removed from the annotations.

getAnnotationComments :: ApiAnns -> RealSrcSpan -> [RealLocated AnnotationComment] Source #

Retrieve the comments allocated to the current SrcSpan

Note: A given SrcSpan may appear in multiple AST elements, beware of duplicates

getAndRemoveAnnotationComments :: ApiAnns -> RealSrcSpan -> ([RealLocated AnnotationComment], ApiAnns) Source #

Retrieve the comments allocated to the current SrcSpan, and remove them from the annotations

data AnnKeywordId Source #

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.

The annotations, together with original source comments are made available in the pm_annotations field of ParsedModule. Comments are only retained if Opt_KeepRawTokenStream is set in DynFlags before parsing.

The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations

Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [Api annotations] above for details of the usage

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

')'

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 unicode arrow

AnnMdo 
AnnMinus

-

AnnModule 
AnnPercentOne

'%1' -- for HsLinearArrow

AnnNewtype 
AnnName

where a name loses its location in the AST, this carries it

AnnOf 
AnnOpen

'(#' or '{-# LANGUAGE' etc

AnnOpenB

'(|'

AnnOpenBU

'(|', unicode variant

AnnOpenC

'{'

AnnOpenE

'[e|' or '[e||'

AnnOpenEQ

'[|'

AnnOpenEQU

'[|', unicode variant

AnnOpenP

'('

AnnOpenS

'['

AnnDollar

prefix $ -- TemplateHaskell

AnnDollarDollar

prefix $$ -- TemplateHaskell

AnnPackageName 
AnnPattern 
AnnPercent

% -- for HsExplicitMult

AnnProc 
AnnQualified 
AnnRarrow

->

AnnRarrowU

->, unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnSignature 
AnnStatic

static

AnnStock 
AnnThen 
AnnThTyQuote

double '''

AnnTilde

~

AnnType 
AnnUnit

() for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnVia

via

AnnWhere 
Annlarrowtail

-<

AnnlarrowtailU

-<, unicode variant

Annrarrowtail

->

AnnrarrowtailU

->, unicode variant

AnnLarrowtail

-<<

AnnLarrowtailU

-<<, unicode variant

AnnRarrowtail

>>-

AnnRarrowtailU

>>-, unicode variant

Instances

Instances details
Data AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnKeywordId -> c AnnKeywordId Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnKeywordId Source #

toConstr :: AnnKeywordId -> Constr Source #

dataTypeOf :: AnnKeywordId -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnKeywordId) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnKeywordId) Source #

gmapT :: (forall b. Data b => b -> b) -> AnnKeywordId -> AnnKeywordId Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnKeywordId -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnKeywordId -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AnnKeywordId -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnKeywordId -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId Source #

Show AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Eq AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

Ord AnnKeywordId Source # 
Instance details

Defined in GHC.Parser.Annotation

data AddAnn Source #

Encapsulated call to addAnnotation, requiring only the SrcSpan of the AST construct the annotation belongs to; together with the AnnKeywordId, this is the key of the annotation map.

This type is useful for places in the parser where it is not yet known what SrcSpan an annotation should be added to. The most common situation is when we are parsing a list: the annotations need to be associated with the AST element that *contains* the list, not the list itself. AddAnn lets us defer adding the annotations until we finish parsing the list and are now parsing the enclosing element; we then apply the AddAnn to associate the annotations. Another common situation is where a common fragment of the AST has been factored out but there is no separate AST node for this fragment (this occurs in class and data declarations). In this case, the annotation belongs to the parent data declaration.

The usual way an AddAnn is created is using the mj ("make jump") function, and then it can be discharged using the ams function.

mkParensApiAnn :: SrcSpan -> [AddAnn] Source #

Given a SrcSpan that surrounds a HsPar or HsParTy, generate AddAnn values for the opening and closing bordering on the start and end of the span

data AnnotationComment Source #

Constructors

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 {- -}

Instances

Instances details
Data AnnotationComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnotationComment -> c AnnotationComment Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnotationComment Source #

toConstr :: AnnotationComment -> Constr Source #

dataTypeOf :: AnnotationComment -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnotationComment) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnotationComment) Source #

gmapT :: (forall b. Data b => b -> b) -> AnnotationComment -> AnnotationComment Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationComment -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationComment -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AnnotationComment -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnotationComment -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment Source #

Show AnnotationComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Outputable AnnotationComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Eq AnnotationComment Source # 
Instance details

Defined in GHC.Parser.Annotation

Ord AnnotationComment Source # 
Instance details

Defined in GHC.Parser.Annotation

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 ApiAnnotation

Instances

Instances details
Data IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsUnicodeSyntax -> c IsUnicodeSyntax Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsUnicodeSyntax Source #

toConstr :: IsUnicodeSyntax -> Constr Source #

dataTypeOf :: IsUnicodeSyntax -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsUnicodeSyntax) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsUnicodeSyntax) Source #

gmapT :: (forall b. Data b => b -> b) -> IsUnicodeSyntax -> IsUnicodeSyntax Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsUnicodeSyntax -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsUnicodeSyntax -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IsUnicodeSyntax -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IsUnicodeSyntax -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsUnicodeSyntax -> m IsUnicodeSyntax Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsUnicodeSyntax -> m IsUnicodeSyntax Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsUnicodeSyntax -> m IsUnicodeSyntax Source #

Show IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Eq IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

Ord IsUnicodeSyntax Source # 
Instance details

Defined in GHC.Parser.Annotation

unicodeAnn :: AnnKeywordId -> AnnKeywordId Source #

Convert a normal annotation into its unicode equivalent one

data HasE Source #

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.

Constructors

HasE 
NoE 

Instances

Instances details
Data HasE Source # 
Instance details

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 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 Source # 
Instance details

Defined in GHC.Parser.Annotation

Eq HasE Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

(==) :: HasE -> HasE -> Bool #

(/=) :: HasE -> HasE -> Bool #

Ord HasE Source # 
Instance details

Defined in GHC.Parser.Annotation

Methods

compare :: HasE -> HasE -> Ordering #

(<) :: HasE -> HasE -> Bool #

(<=) :: HasE -> HasE -> Bool #

(>) :: HasE -> HasE -> Bool #

(>=) :: HasE -> HasE -> Bool #

max :: HasE -> HasE -> HasE #

min :: HasE -> HasE -> HasE #