Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- keywordToString :: AnnKeywordId -> String
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnClosePH
- | 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
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnOpenPH
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | AnnPercentOne
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- data Comment = Comment {}
Documentation
keywordToString :: AnnKeywordId -> String Source #
Maps AnnKeywordId
to the corresponding String representation.
There is no specific mapping for the following constructors.
AnnOpen
, AnnClose
, AnnVal
, AnnPackageName
, AnnHeader
, AnnFunId
,
AnnInfix
data AnnKeywordId #
Exact print 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 otherwise captured in the AST.
The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/in-tree-api-annotations
Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [exact print annotations] above for details of the usage
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 | ')' |
AnnClosePH | '#)' |
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 |
AnnMdo | |
AnnMinus | |
AnnModule | |
AnnNewtype | |
AnnName | where a name loses its location in the AST, this carries it |
AnnOf | |
AnnOpen | '{-# DEPRECATED' etc. Opening of pragmas where
the capitalisation of the string can be changed by
the user. The actual text used is stored in a
|
AnnOpenB | '(|' |
AnnOpenBU | '(|', unicode variant |
AnnOpenC | '{' |
AnnOpenE | '[e|' or '[e||' |
AnnOpenEQ | '[|' |
AnnOpenEQU | '[|', unicode variant |
AnnOpenP | '(' |
AnnOpenS | '[' |
AnnOpenPH | '(#' |
AnnDollar | prefix |
AnnDollarDollar | prefix |
AnnPackageName | |
AnnPattern | |
AnnPercent |
|
AnnPercentOne | '%1' -- for HsLinearArrow |
AnnProc | |
AnnQualified | |
AnnRarrow |
|
AnnRarrowU |
|
AnnRec | |
AnnRole | |
AnnSafe | |
AnnSemi | ';' |
AnnSimpleQuote | ''' |
AnnSignature | |
AnnStatic |
|
AnnStock | |
AnnThen | |
AnnThTyQuote | double ''' |
AnnTilde |
|
AnnType | |
AnnUnit |
|
AnnUsing | |
AnnVal | e.g. INTEGER |
AnnValStr | String value, will need quotes when output |
AnnVbar | '|' |
AnnVia |
|
AnnWhere | |
Annlarrowtail |
|
AnnlarrowtailU |
|
Annrarrowtail |
|
AnnrarrowtailU |
|
AnnLarrowtail |
|
AnnLarrowtailU |
|
AnnRarrowtail |
|
AnnRarrowtailU |
|
Instances
A Haskell comment. The AnnKeywordId
is present if it has been converted
from an AnnKeywordId
because the annotation must be interleaved into the
stream and does not have a well-defined position
Comment | |
|
Instances
Data Comment Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comment -> c Comment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Comment # toConstr :: Comment -> Constr # dataTypeOf :: Comment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Comment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment) # gmapT :: (forall b. Data b => b -> b) -> Comment -> Comment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQ :: (forall d. Data d => d -> u) -> Comment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # | |
Show Comment Source # | |
Outputable Comment Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Eq Comment Source # | |
Ord Comment Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types |