Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Token
- = ITas
- | ITcase
- | ITclass
- | ITdata
- | ITdefault
- | ITderiving
- | ITdo
- | ITelse
- | IThiding
- | ITforeign
- | ITif
- | ITimport
- | ITin
- | ITinfix
- | ITinfixl
- | ITinfixr
- | ITinstance
- | ITlet
- | ITmodule
- | ITnewtype
- | ITof
- | ITqualified
- | ITthen
- | ITtype
- | ITwhere
- | ITforall IsUnicodeSyntax
- | ITexport
- | ITlabel
- | ITdynamic
- | ITsafe
- | ITinterruptible
- | ITunsafe
- | ITstdcallconv
- | ITccallconv
- | ITcapiconv
- | ITprimcallconv
- | ITjavascriptcallconv
- | ITmdo
- | ITfamily
- | ITrole
- | ITgroup
- | ITby
- | ITusing
- | ITpattern
- | ITstatic
- | ITinline_prag SourceText InlineSpec RuleMatchInfo
- | ITspec_prag SourceText
- | ITspec_inline_prag SourceText Bool
- | ITsource_prag SourceText
- | ITrules_prag SourceText
- | ITwarning_prag SourceText
- | ITdeprecated_prag SourceText
- | ITline_prag
- | ITscc_prag SourceText
- | ITgenerated_prag SourceText
- | ITcore_prag SourceText
- | ITunpack_prag SourceText
- | ITnounpack_prag SourceText
- | ITann_prag SourceText
- | ITclose_prag
- | IToptions_prag String
- | ITinclude_prag String
- | ITlanguage_prag
- | ITvect_prag SourceText
- | ITvect_scalar_prag SourceText
- | ITnovect_prag SourceText
- | ITminimal_prag SourceText
- | IToverlappable_prag SourceText
- | IToverlapping_prag SourceText
- | IToverlaps_prag SourceText
- | ITincoherent_prag SourceText
- | ITctype SourceText
- | ITdotdot
- | ITcolon
- | ITdcolon IsUnicodeSyntax
- | ITequal
- | ITlam
- | ITlcase
- | ITvbar
- | ITlarrow IsUnicodeSyntax
- | ITrarrow IsUnicodeSyntax
- | ITat
- | ITtilde
- | ITtildehsh
- | ITdarrow IsUnicodeSyntax
- | ITminus
- | ITbang
- | ITdot
- | ITbiglam
- | ITocurly
- | ITccurly
- | ITvocurly
- | ITvccurly
- | ITobrack
- | ITopabrack
- | ITcpabrack
- | ITcbrack
- | IToparen
- | ITcparen
- | IToubxparen
- | ITcubxparen
- | ITsemi
- | ITcomma
- | ITunderscore
- | ITbackquote
- | ITsimpleQuote
- | ITvarid FastString
- | ITconid FastString
- | ITvarsym FastString
- | ITconsym FastString
- | ITqvarid (FastString, FastString)
- | ITqconid (FastString, FastString)
- | ITqvarsym (FastString, FastString)
- | ITqconsym (FastString, FastString)
- | ITdupipvarid FastString
- | ITlabelvarid FastString
- | ITchar SourceText Char
- | ITstring SourceText FastString
- | ITinteger SourceText Integer
- | ITrational FractionalLit
- | ITprimchar SourceText Char
- | ITprimstring SourceText ByteString
- | ITprimint SourceText Integer
- | ITprimword SourceText Integer
- | ITprimfloat FractionalLit
- | ITprimdouble FractionalLit
- | ITopenExpQuote HasE
- | ITopenPatQuote
- | ITopenDecQuote
- | ITopenTypQuote
- | ITcloseQuote
- | ITopenTExpQuote HasE
- | ITcloseTExpQuote
- | ITidEscape FastString
- | ITparenEscape
- | ITidTyEscape FastString
- | ITparenTyEscape
- | ITtyQuote
- | ITquasiQuote (FastString, FastString, RealSrcSpan)
- | ITqQuasiQuote (FastString, FastString, FastString, RealSrcSpan)
- | ITproc
- | ITrec
- | IToparenbar
- | ITcparenbar
- | ITlarrowtail IsUnicodeSyntax
- | ITrarrowtail IsUnicodeSyntax
- | ITLarrowtail IsUnicodeSyntax
- | ITRarrowtail IsUnicodeSyntax
- | ITtypeApp
- | ITunknown String
- | ITeof
- | ITdocCommentNext String
- | ITdocCommentPrev String
- | ITdocCommentNamed String
- | ITdocSection Int String
- | ITdocOptions String
- | ITdocOptionsOld String
- | ITlineComment String
- | ITblockComment String
- lexer :: Bool -> (Located Token -> P a) -> P a
- pragState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState
- mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState
- data PState = PState {
- buffer :: StringBuffer
- dflags :: DynFlags
- messages :: Messages
- tab_first :: Maybe RealSrcSpan
- tab_count :: !Int
- last_tk :: Maybe Token
- last_loc :: RealSrcSpan
- last_len :: !Int
- loc :: RealSrcLoc
- extsBitmap :: !ExtsBitmap
- context :: [LayoutContext]
- lex_state :: [Int]
- srcfiles :: [FastString]
- alr_pending_implicit_tokens :: [RealLocated Token]
- alr_next_token :: Maybe (RealLocated Token)
- alr_last_loc :: RealSrcSpan
- alr_context :: [ALRContext]
- alr_expecting_ocurly :: Maybe ALRLayout
- alr_justClosedExplicitLetBlock :: Bool
- annotations :: [(ApiAnnKey, [SrcSpan])]
- comment_q :: [Located AnnotationComment]
- annotations_comments :: [(SrcSpan, [Located AnnotationComment])]
- newtype P a = P {
- unP :: PState -> ParseResult a
- data ParseResult a
- getSrcLoc :: P RealSrcLoc
- getPState :: P PState
- getDynFlags :: HasDynFlags m => m DynFlags
- withThisPackage :: (UnitId -> a) -> P a
- failLocMsgP :: RealSrcLoc -> RealSrcLoc -> String -> P a
- failSpanMsgP :: SrcSpan -> SDoc -> P a
- srcParseFail :: P a
- getMessages :: PState -> Messages
- popContext :: P ()
- pushCurrentContext :: P ()
- setLastToken :: RealSrcSpan -> Int -> P ()
- setSrcLoc :: RealSrcLoc -> P ()
- activeContext :: P Bool
- nextIsEOF :: P Bool
- getLexState :: P Int
- popLexState :: P Int
- pushLexState :: Int -> P ()
- extension :: (ExtsBitmap -> Bool) -> P Bool
- bangPatEnabled :: ExtsBitmap -> Bool
- datatypeContextsEnabled :: ExtsBitmap -> Bool
- traditionalRecordSyntaxEnabled :: ExtsBitmap -> Bool
- explicitForallEnabled :: ExtsBitmap -> Bool
- inRulePrag :: ExtsBitmap -> Bool
- explicitNamespacesEnabled :: ExtsBitmap -> Bool
- patternSynonymsEnabled :: ExtsBitmap -> Bool
- sccProfilingOn :: ExtsBitmap -> Bool
- hpcEnabled :: ExtsBitmap -> Bool
- addWarning :: WarningFlag -> SrcSpan -> SDoc -> P ()
- lexTokenStream :: StringBuffer -> RealSrcLoc -> DynFlags -> ParseResult [Located Token]
- addAnnotation :: SrcSpan -> AnnKeywordId -> SrcSpan -> P ()
- type AddAnn = SrcSpan -> P ()
- addAnnsAt :: SrcSpan -> [AddAnn] -> P ()
- mkParensApiAnn :: SrcSpan -> [AddAnn]
- moveAnnotations :: SrcSpan -> SrcSpan -> P ()
Documentation
pragState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState Source #
mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState Source #
PState | |
|
P | |
|
getSrcLoc :: P RealSrcLoc Source #
getDynFlags :: HasDynFlags m => m DynFlags Source #
withThisPackage :: (UnitId -> a) -> P a Source #
failLocMsgP :: RealSrcLoc -> RealSrcLoc -> String -> P a Source #
srcParseFail :: P a Source #
getMessages :: PState -> Messages Source #
popContext :: P () Source #
pushCurrentContext :: P () Source #
setLastToken :: RealSrcSpan -> Int -> P () Source #
setSrcLoc :: RealSrcLoc -> P () Source #
activeContext :: P Bool Source #
getLexState :: P Int Source #
popLexState :: P Int Source #
pushLexState :: Int -> P () Source #
bangPatEnabled :: ExtsBitmap -> Bool Source #
datatypeContextsEnabled :: ExtsBitmap -> Bool Source #
traditionalRecordSyntaxEnabled :: ExtsBitmap -> Bool Source #
explicitForallEnabled :: ExtsBitmap -> Bool Source #
inRulePrag :: ExtsBitmap -> Bool Source #
explicitNamespacesEnabled :: ExtsBitmap -> Bool Source #
patternSynonymsEnabled :: ExtsBitmap -> Bool Source #
sccProfilingOn :: ExtsBitmap -> Bool Source #
hpcEnabled :: ExtsBitmap -> Bool Source #
addWarning :: WarningFlag -> SrcSpan -> SDoc -> P () Source #
lexTokenStream :: StringBuffer -> RealSrcLoc -> DynFlags -> ParseResult [Located Token] Source #
addAnnotation :: SrcSpan -> AnnKeywordId -> SrcSpan -> P () Source #
type AddAnn = SrcSpan -> P () Source #
Encapsulated call to addAnnotation, requiring only the SrcSpan of the AST construct the annotation belongs to; together with the AnnKeywordId, this is is the key of the annotation map
addAnnsAt :: SrcSpan -> [AddAnn] -> P () Source #
Given a location and a list of AddAnn, apply them all to the location.
mkParensApiAnn :: SrcSpan -> [AddAnn] Source #