| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
ApiAnnotation
Synopsis
- 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
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | 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
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenPE
- | AnnOpenPTE
- | AnnOpenS
- | AnnPackageName
- | AnnPattern
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThIdSplice
- | AnnThIdTySplice
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- | AnnEofPos
- data AnnotationComment
- data IsUnicodeSyntax
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- data HasE
- type LRdrName = Located RdrName
Documentation
getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] Source #
getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns) Source #
getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment] 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://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
!
'`'
case or lambda case
'#)' or '#-}' etc
'|)'
'|)', unicode variant
'}'
'|]'
'|]', unicode variant
')'
']'
as a list separator
in a RdrName for a tuple
'=>'
'=>', unicode variant
'::'
'::', unicode variant
'..'
Unicode variant
for function name in matches where there are multiple equations for the function.
for CType
'infix' or 'infixl' or 'infixr'
'<-'
'<-', unicode variant
where a name loses its location in the AST, this carries it
'(#' or '{-# LANGUAGE' etc
'(|'
'(|', unicode variant
'{'
'[e|' or '[e||'
'[|'
'[|', unicode variant
'('
'$('
'$$('
'['
'->'
'->', unicode variant
';'
'''
static
double '''
'~'
'()' for types
e.g. INTEGER
String value, will need quotes when output
'|'
via
-<, unicode variant
'->'
'->', unicode variant
-<<
-<<, unicode variant
>>-
>>-, unicode variant
Instances
Instance details
Defined in ApiAnnotation
Methods
(==) :: AnnKeywordId -> AnnKeywordId -> Bool #
(/=) :: AnnKeywordId -> AnnKeywordId -> Bool #
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 #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnKeywordId #
toConstr :: AnnKeywordId -> Constr #
dataTypeOf :: AnnKeywordId -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnKeywordId) #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnKeywordId) #
gmapT :: (forall b. Data b => b -> b) -> AnnKeywordId -> AnnKeywordId #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnKeywordId -> r #
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnKeywordId -> r #
gmapQ :: (forall d. Data d => d -> u) -> AnnKeywordId -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnKeywordId -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKeywordId -> m AnnKeywordId #
Instance details
Defined in ApiAnnotation
Methods
compare :: AnnKeywordId -> AnnKeywordId -> Ordering #
(<) :: AnnKeywordId -> AnnKeywordId -> Bool #
(<=) :: AnnKeywordId -> AnnKeywordId -> Bool #
(>) :: AnnKeywordId -> AnnKeywordId -> Bool #
(>=) :: AnnKeywordId -> AnnKeywordId -> Bool #
max :: AnnKeywordId -> AnnKeywordId -> AnnKeywordId #
min :: AnnKeywordId -> AnnKeywordId -> AnnKeywordId #
Instance details
Defined in ApiAnnotation
Methods
showsPrec :: Int -> AnnKeywordId -> ShowS #
show :: AnnKeywordId -> String #
showList :: [AnnKeywordId] -> ShowS #
Instance details
Defined in ApiAnnotation
data AnnotationComment Source #
Constructors
Instances
Instance details
Defined in ApiAnnotation
Methods
(==) :: AnnotationComment -> AnnotationComment -> Bool #
(/=) :: AnnotationComment -> AnnotationComment -> Bool #
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 #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnotationComment #
toConstr :: AnnotationComment -> Constr #
dataTypeOf :: AnnotationComment -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnotationComment) #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnotationComment) #
gmapT :: (forall b. Data b => b -> b) -> AnnotationComment -> AnnotationComment #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationComment -> r #
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationComment -> r #
gmapQ :: (forall d. Data d => d -> u) -> AnnotationComment -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnotationComment -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationComment -> m AnnotationComment #
Instance details
Defined in ApiAnnotation
Methods
compare :: AnnotationComment -> AnnotationComment -> Ordering #
(<) :: AnnotationComment -> AnnotationComment -> Bool #
(<=) :: AnnotationComment -> AnnotationComment -> Bool #
(>) :: AnnotationComment -> AnnotationComment -> Bool #
(>=) :: AnnotationComment -> AnnotationComment -> Bool #
max :: AnnotationComment -> AnnotationComment -> AnnotationComment #
min :: AnnotationComment -> AnnotationComment -> AnnotationComment #
Instance details
Defined in ApiAnnotation
Methods
showsPrec :: Int -> AnnotationComment -> ShowS #
show :: AnnotationComment -> String #
showList :: [AnnotationComment] -> ShowS #
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
Instance details
Defined in ApiAnnotation
Methods
(==) :: IsUnicodeSyntax -> IsUnicodeSyntax -> Bool #
(/=) :: IsUnicodeSyntax -> IsUnicodeSyntax -> Bool #
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 #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsUnicodeSyntax #
toConstr :: IsUnicodeSyntax -> Constr #
dataTypeOf :: IsUnicodeSyntax -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsUnicodeSyntax) #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsUnicodeSyntax) #
gmapT :: (forall b. Data b => b -> b) -> IsUnicodeSyntax -> IsUnicodeSyntax #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsUnicodeSyntax -> r #
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsUnicodeSyntax -> r #
gmapQ :: (forall d. Data d => d -> u) -> IsUnicodeSyntax -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> IsUnicodeSyntax -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsUnicodeSyntax -> m IsUnicodeSyntax #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsUnicodeSyntax -> m IsUnicodeSyntax #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsUnicodeSyntax -> m IsUnicodeSyntax #
Instance details
Defined in ApiAnnotation
Methods
compare :: IsUnicodeSyntax -> IsUnicodeSyntax -> Ordering #
(<) :: IsUnicodeSyntax -> IsUnicodeSyntax -> Bool #
(<=) :: IsUnicodeSyntax -> IsUnicodeSyntax -> Bool #
(>) :: IsUnicodeSyntax -> IsUnicodeSyntax -> Bool #
(>=) :: IsUnicodeSyntax -> IsUnicodeSyntax -> Bool #
max :: IsUnicodeSyntax -> IsUnicodeSyntax -> IsUnicodeSyntax #
min :: IsUnicodeSyntax -> IsUnicodeSyntax -> IsUnicodeSyntax #
Instance details
Defined in ApiAnnotation
Methods
showsPrec :: Int -> IsUnicodeSyntax -> ShowS #
show :: IsUnicodeSyntax -> String #
showList :: [IsUnicodeSyntax] -> ShowS #
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
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 #
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 :: (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 #