Safe Haskell | None |
---|---|
Language | Haskell2010 |
- getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan]
- getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns)
- getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment]
- getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns)
- type ApiAnns = (Map ApiAnnKey [SrcSpan], Map SrcSpan [Located AnnotationComment])
- type ApiAnnKey = (SrcSpan, AnnKeywordId)
- data AnnKeywordId
- = AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseC
- | AnnCloseP
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnData
- | AnnDcolon
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLet
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenC
- | AnnOpenP
- | AnnOpenPE
- | AnnOpenPTE
- | AnnOpenS
- | AnnPackageName
- | AnnPattern
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnStatic
- | AnnThen
- | AnnThIdSplice
- | AnnThIdTySplice
- | AnnThTyQuote
- | AnnTilde
- | AnnTildehsh
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnWhere
- | Annlarrowtail
- | Annrarrowtail
- | AnnLarrowtail
- | AnnRarrowtail
- | AnnEofPos
- data AnnotationComment
- type LRdrName = Located RdrName
Documentation
getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] Source
getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns) Source
getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns) Source
Retrieve the comments allocated to the current SrcSpan
, and
remove them from the annotations
type ApiAnnKey = (SrcSpan, AnnKeywordId) Source
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
field of pm_annotations
.
Comments are only retained if ParsedModule
is set in
Opt_KeepRawTokenStream
before parsing.DynFlags
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
data AnnotationComment Source
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 {- -} |