ghc-7.10.0.20150123: 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://ghc.haskell.org/trac/ghc/wiki/ApiAnnotations

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

AnnAs 
AnnAt 
AnnBang

!

AnnBackquote

'`'

AnnBy 
AnnCase

case or lambda case

AnnClass 
AnnClose

'#)' or '#-}' etc

AnnCloseC

'}'

AnnCloseP

')'

AnnCloseS

']'

AnnColon 
AnnComma

as a list separator

AnnCommaTuple

in a RdrName for a tuple

AnnDarrow

'=>'

AnnData 
AnnDcolon

'::'

AnnDefault 
AnnDeriving 
AnnDo 
AnnDot

.

AnnDotdot

'..'

AnnElse 
AnnEqual 
AnnExport 
AnnFamily 
AnnForall 
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

'<-'

AnnLet 
AnnMdo 
AnnMinus

-

AnnModule 
AnnNewtype 
AnnOf 
AnnOpen

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

AnnOpenC

'{'

AnnOpenP

'('

AnnOpenS

'['

AnnPackageName 
AnnPattern 
AnnProc 
AnnQualified 
AnnRarrow

'->'

AnnRec 
AnnRole 
AnnSafe 
AnnSemi

';'

AnnStatic

static

AnnThen 
AnnTilde

'~'

AnnTildehsh

~#

AnnType 
AnnUnit

'()' for types

AnnUsing 
AnnVal

e.g. INTEGER

AnnValStr

String value, will need quotes when output

AnnVbar

'|'

AnnWhere 
Annlarrowtail

-<

Annrarrowtail

'->'

AnnLarrowtail

-<<

AnnRarrowtail

>>-

AnnEofPos 

Instances

Eq AnnKeywordId 
Data AnnKeywordId 
Ord AnnKeywordId 
Show AnnKeywordId 
Outputable AnnKeywordId 
Typeable * AnnKeywordId 
Typeable AnnKeywordId AnnAs 
Typeable AnnKeywordId AnnAt 
Typeable AnnKeywordId AnnBang 
Typeable AnnKeywordId AnnBackquote 
Typeable AnnKeywordId AnnBy 
Typeable AnnKeywordId AnnCase 
Typeable AnnKeywordId AnnClass 
Typeable AnnKeywordId AnnClose 
Typeable AnnKeywordId AnnCloseC 
Typeable AnnKeywordId AnnCloseP 
Typeable AnnKeywordId AnnCloseS 
Typeable AnnKeywordId AnnColon 
Typeable AnnKeywordId AnnComma 
Typeable AnnKeywordId AnnCommaTuple 
Typeable AnnKeywordId AnnDarrow 
Typeable AnnKeywordId AnnData 
Typeable AnnKeywordId AnnDcolon 
Typeable AnnKeywordId AnnDefault 
Typeable AnnKeywordId AnnDeriving 
Typeable AnnKeywordId AnnDo 
Typeable AnnKeywordId AnnDot 
Typeable AnnKeywordId AnnDotdot 
Typeable AnnKeywordId AnnElse 
Typeable AnnKeywordId AnnEqual 
Typeable AnnKeywordId AnnExport 
Typeable AnnKeywordId AnnFamily 
Typeable AnnKeywordId AnnForall 
Typeable AnnKeywordId AnnForeign 
Typeable AnnKeywordId AnnFunId 
Typeable AnnKeywordId AnnGroup 
Typeable AnnKeywordId AnnHeader 
Typeable AnnKeywordId AnnHiding 
Typeable AnnKeywordId AnnIf 
Typeable AnnKeywordId AnnImport 
Typeable AnnKeywordId AnnIn 
Typeable AnnKeywordId AnnInfix 
Typeable AnnKeywordId AnnInstance 
Typeable AnnKeywordId AnnLam 
Typeable AnnKeywordId AnnLarrow 
Typeable AnnKeywordId AnnLet 
Typeable AnnKeywordId AnnMdo 
Typeable AnnKeywordId AnnMinus 
Typeable AnnKeywordId AnnModule 
Typeable AnnKeywordId AnnNewtype 
Typeable AnnKeywordId AnnOf 
Typeable AnnKeywordId AnnOpen 
Typeable AnnKeywordId AnnOpenC 
Typeable AnnKeywordId AnnOpenP 
Typeable AnnKeywordId AnnOpenS 
Typeable AnnKeywordId AnnPackageName 
Typeable AnnKeywordId AnnPattern 
Typeable AnnKeywordId AnnProc 
Typeable AnnKeywordId AnnQualified 
Typeable AnnKeywordId AnnRarrow 
Typeable AnnKeywordId AnnRec 
Typeable AnnKeywordId AnnRole 
Typeable AnnKeywordId AnnSafe 
Typeable AnnKeywordId AnnSemi 
Typeable AnnKeywordId AnnStatic 
Typeable AnnKeywordId AnnThen 
Typeable AnnKeywordId AnnTilde 
Typeable AnnKeywordId AnnTildehsh 
Typeable AnnKeywordId AnnType 
Typeable AnnKeywordId AnnUnit 
Typeable AnnKeywordId AnnUsing 
Typeable AnnKeywordId AnnVal 
Typeable AnnKeywordId AnnValStr 
Typeable AnnKeywordId AnnVbar 
Typeable AnnKeywordId AnnWhere 
Typeable AnnKeywordId Annlarrowtail 
Typeable AnnKeywordId Annrarrowtail 
Typeable AnnKeywordId AnnLarrowtail 
Typeable AnnKeywordId AnnRarrowtail 
Typeable AnnKeywordId AnnEofPos 

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)

AnnDocOptionsOld String

doc options declared "-- # ..."-style

AnnLineComment String

comment starting by "--"

AnnBlockComment String

comment in {- -}