ghc-8.10.7: The GHC API
Safe HaskellNone
LanguageHaskell2010

ApiAnnotation

Synopsis

Documentation

getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] 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 -> SrcSpan -> AnnKeywordId -> ([SrcSpan], 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 -> SrcSpan -> [Located 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 -> SrcSpan -> ([Located 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 
AnnMdo 
AnnMinus

-

AnnModule 
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

'('

AnnOpenPE

'$('

AnnOpenPTE

'$$('

AnnOpenS

'['

AnnPackageName 
AnnPattern 
AnnProc 
AnnQualified 
AnnRarrow

->

AnnRarrowU

->, unicode variant

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnSimpleQuote

'''

AnnSignature 
AnnStatic

static

AnnStock 
AnnThen 
AnnThIdSplice

$

AnnThIdTySplice

$$

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

AnnEofPos 

Instances

Instances details
Eq AnnKeywordId # 
Instance details

Defined in ApiAnnotation

Data AnnKeywordId # 
Instance details

Defined in ApiAnnotation

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 #

Ord AnnKeywordId # 
Instance details

Defined in ApiAnnotation

Show AnnKeywordId # 
Instance details

Defined in ApiAnnotation

Outputable AnnKeywordId # 
Instance details

Defined in ApiAnnotation

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
Eq AnnotationComment # 
Instance details

Defined in ApiAnnotation

Data AnnotationComment # 
Instance details

Defined in ApiAnnotation

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 #

Ord AnnotationComment # 
Instance details

Defined in ApiAnnotation

Show AnnotationComment # 
Instance details

Defined in ApiAnnotation

Outputable AnnotationComment # 
Instance details

Defined in ApiAnnotation

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
Eq IsUnicodeSyntax # 
Instance details

Defined in ApiAnnotation

Data IsUnicodeSyntax # 
Instance details

Defined in ApiAnnotation

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 #

Ord IsUnicodeSyntax # 
Instance details

Defined in ApiAnnotation

Show IsUnicodeSyntax # 
Instance details

Defined in ApiAnnotation

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
Eq HasE # 
Instance details

Defined in ApiAnnotation

Methods

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

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

Data HasE # 
Instance details

Defined in ApiAnnotation

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 #

Ord HasE # 
Instance details

Defined in ApiAnnotation

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 #

Show HasE # 
Instance details

Defined in ApiAnnotation