Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- | ITstock
- | ITanyclass
- | ITvia
- | ITunit
- | ITsignature
- | ITdependency
- | ITrequires
- | 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 SourceText
- | ITcolumn_prag SourceText
- | ITscc_prag SourceText
- | ITgenerated_prag SourceText
- | ITcore_prag SourceText
- | ITunpack_prag SourceText
- | ITnounpack_prag SourceText
- | ITann_prag SourceText
- | ITcomplete_prag SourceText
- | ITclose_prag
- | IToptions_prag String
- | ITinclude_prag String
- | ITlanguage_prag
- | ITminimal_prag SourceText
- | IToverlappable_prag SourceText
- | IToverlapping_prag SourceText
- | IToverlaps_prag SourceText
- | ITincoherent_prag SourceText
- | ITctype SourceText
- | ITcomment_line_prag
- | ITdotdot
- | ITcolon
- | ITdcolon IsUnicodeSyntax
- | ITequal
- | ITlam
- | ITlcase
- | ITvbar
- | ITlarrow IsUnicodeSyntax
- | ITrarrow IsUnicodeSyntax
- | ITat
- | ITtilde
- | ITdarrow IsUnicodeSyntax
- | ITminus
- | ITbang
- | ITstar IsUnicodeSyntax
- | 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 IntegralLit
- | ITrational FractionalLit
- | ITprimchar SourceText Char
- | ITprimstring SourceText ByteString
- | ITprimint SourceText Integer
- | ITprimword SourceText Integer
- | ITprimfloat FractionalLit
- | ITprimdouble FractionalLit
- | ITopenExpQuote HasE IsUnicodeSyntax
- | ITopenPatQuote
- | ITopenDecQuote
- | ITopenTypQuote
- | ITcloseQuote IsUnicodeSyntax
- | ITopenTExpQuote HasE
- | ITcloseTExpQuote
- | ITidEscape FastString
- | ITparenEscape
- | ITidTyEscape FastString
- | ITparenTyEscape
- | ITtyQuote
- | ITquasiQuote (FastString, FastString, RealSrcSpan)
- | ITqQuasiQuote (FastString, FastString, FastString, RealSrcSpan)
- | ITproc
- | ITrec
- | IToparenbar IsUnicodeSyntax
- | ITcparenbar IsUnicodeSyntax
- | ITlarrowtail IsUnicodeSyntax
- | ITrarrowtail IsUnicodeSyntax
- | ITLarrowtail IsUnicodeSyntax
- | ITRarrowtail IsUnicodeSyntax
- | ITtypeApp
- | ITunknown String
- | ITeof
- | ITdocCommentNext String
- | ITdocCommentPrev String
- | ITdocCommentNamed String
- | ITdocSection Int String
- | ITdocOptions String
- | ITlineComment String
- | ITblockComment String
- lexer :: Bool -> (Located Token -> P a) -> P a
- pragState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState
- mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState
- mkPStatePure :: ParserFlags -> StringBuffer -> RealSrcLoc -> PState
- data PState = PState {
- buffer :: StringBuffer
- options :: ParserFlags
- messages :: DynFlags -> Messages
- tab_first :: Maybe RealSrcSpan
- tab_count :: !Int
- last_tk :: Maybe Token
- last_loc :: RealSrcSpan
- last_len :: !Int
- loc :: RealSrcLoc
- 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
- mkParserFlags :: DynFlags -> ParserFlags
- mkParserFlags' :: EnumSet WarningFlag -> EnumSet Extension -> UnitId -> Bool -> Bool -> Bool -> Bool -> ParserFlags
- data ParserFlags = ParserFlags {
- pWarningFlags :: EnumSet WarningFlag
- pThisPackage :: UnitId
- pExtsBitmap :: !ExtsBitmap
- appendWarning :: ParserFlags -> WarningFlag -> SrcSpan -> SDoc -> (DynFlags -> Messages) -> DynFlags -> Messages
- appendError :: SrcSpan -> SDoc -> (DynFlags -> Messages) -> DynFlags -> Messages
- allocateComments :: SrcSpan -> [Located AnnotationComment] -> ([Located AnnotationComment], [(SrcSpan, [Located AnnotationComment])])
- class Monad m => MonadP m where
- addError :: SrcSpan -> SDoc -> m ()
- addWarning :: WarningFlag -> SrcSpan -> SDoc -> m ()
- addFatalError :: SrcSpan -> SDoc -> m a
- getBit :: ExtBits -> m Bool
- addAnnotation :: SrcSpan -> AnnKeywordId -> SrcSpan -> m ()
- getRealSrcLoc :: P RealSrcLoc
- getPState :: P PState
- withThisPackage :: (UnitId -> a) -> P a
- failLocMsgP :: RealSrcLoc -> RealSrcLoc -> String -> P a
- srcParseFail :: P a
- getErrorMessages :: PState -> DynFlags -> ErrorMessages
- getMessages :: PState -> DynFlags -> Messages
- popContext :: P ()
- pushModuleContext :: P ()
- setLastToken :: RealSrcSpan -> Int -> P ()
- setSrcLoc :: RealSrcLoc -> P ()
- activeContext :: P Bool
- nextIsEOF :: P Bool
- getLexState :: P Int
- popLexState :: P Int
- pushLexState :: Int -> P ()
- data ExtBits
- = FfiBit
- | InterruptibleFfiBit
- | CApiFfiBit
- | ArrowsBit
- | ThBit
- | ThQuotesBit
- | IpBit
- | OverloadedLabelsBit
- | ExplicitForallBit
- | BangPatBit
- | PatternSynonymsBit
- | HaddockBit
- | MagicHashBit
- | RecursiveDoBit
- | UnicodeSyntaxBit
- | UnboxedTuplesBit
- | UnboxedSumsBit
- | DatatypeContextsBit
- | MonadComprehensionsBit
- | TransformComprehensionsBit
- | QqBit
- | RawTokenStreamBit
- | AlternativeLayoutRuleBit
- | ALRTransitionalBit
- | RelaxedLayoutBit
- | NondecreasingIndentationBit
- | SafeHaskellBit
- | TraditionalRecordSyntaxBit
- | ExplicitNamespacesBit
- | LambdaCaseBit
- | BinaryLiteralsBit
- | NegativeLiteralsBit
- | HexFloatLiteralsBit
- | TypeApplicationsBit
- | StaticPointersBit
- | NumericUnderscoresBit
- | StarIsTypeBit
- | BlockArgumentsBit
- | NPlusKPatternsBit
- | DoAndIfThenElseBit
- | MultiWayIfBit
- | GadtSyntaxBit
- | ImportQualifiedPostBit
- | InRulePragBit
- | InNestedCommentBit
- | UsePosPragsBit
- xtest :: ExtBits -> ExtsBitmap -> Bool
- lexTokenStream :: StringBuffer -> RealSrcLoc -> DynFlags -> ParseResult [Located Token]
- data AddAnn = AddAnn AnnKeywordId SrcSpan
- mkParensApiAnn :: SrcSpan -> [AddAnn]
- addAnnsAt :: MonadP m => SrcSpan -> [AddAnn] -> m ()
- commentToAnnotation :: Located Token -> Located AnnotationComment
Documentation
pragState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState Source #
mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState Source #
Creates a parse state from a DynFlags
value
mkPStatePure :: ParserFlags -> StringBuffer -> RealSrcLoc -> PState Source #
Creates a parse state from a ParserFlags
value
PState | |
|
The parsing monad, isomorphic to StateT PState Maybe
.
P | |
|
data ParseResult a Source #
The result of running a parser.
POk | The parser has consumed a (possibly empty) prefix
of the input and produced a result. Use |
| |
PFailed | The parser has consumed a (possibly empty) prefix of the input and failed. |
|
mkParserFlags :: DynFlags -> ParserFlags Source #
Extracts the flag information needed for parsing
:: EnumSet WarningFlag | warnings flags enabled |
-> EnumSet Extension | permitted language extensions enabled |
-> UnitId | key of package currently being compiled |
-> Bool | are safe imports on? |
-> Bool | keeping Haddock comment tokens |
-> Bool | keep regular comment tokens |
-> Bool | If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update
the internal position kept by the parser. Otherwise, those pragmas are
lexed as |
-> ParserFlags |
Given exactly the information needed, set up the ParserFlags
data ParserFlags Source #
The subset of the DynFlags
used by the parser.
See mkParserFlags
or mkParserFlags'
for ways to construct this.
ParserFlags | |
|
appendWarning :: ParserFlags -> WarningFlag -> SrcSpan -> SDoc -> (DynFlags -> Messages) -> DynFlags -> Messages Source #
allocateComments :: SrcSpan -> [Located AnnotationComment] -> ([Located AnnotationComment], [(SrcSpan, [Located AnnotationComment])]) Source #
class Monad m => MonadP m where Source #
An mtl-style class for monads that support parsing-related operations. For example, sometimes we make a second pass over the parsing results to validate, disambiguate, or rearrange them, and we do so in the PV monad which cannot consume input but can report parsing errors, check for extension bits, and accumulate parsing annotations. Both P and PV are instances of MonadP.
MonadP grants us convenient overloading. The other option is to have separate operations for each monad: addErrorP vs addErrorPV, getBitP vs getBitPV, and so on.
addError :: SrcSpan -> SDoc -> m () Source #
Add a non-fatal error. Use this when the parser can produce a result despite the error.
For example, when GHC encounters a forall
in a type,
but -XExplicitForAll
is disabled, the parser constructs ForAllTy
as if -XExplicitForAll
was enabled, adding a non-fatal error to
the accumulator.
Control flow wise, non-fatal errors act like warnings: they are added to the accumulator and parsing continues. This allows GHC to report more than one parse error per file.
addWarning :: WarningFlag -> SrcSpan -> SDoc -> m () Source #
Add a warning to the accumulator.
Use getMessages
to get the accumulated warnings.
addFatalError :: SrcSpan -> SDoc -> m a Source #
Add a fatal error. This will be the last error reported by the parser, and
the parser will not produce any result, ending in a PFailed
state.
getBit :: ExtBits -> m Bool Source #
Check if a given flag is currently set in the bitmap.
addAnnotation :: SrcSpan -> AnnKeywordId -> SrcSpan -> m () Source #
Given a location and a list of AddAnn, apply them all to the location.
withThisPackage :: (UnitId -> a) -> P a Source #
failLocMsgP :: RealSrcLoc -> RealSrcLoc -> String -> P a Source #
srcParseFail :: P a Source #
getErrorMessages :: PState -> DynFlags -> ErrorMessages Source #
Get a bag of the errors that have been accumulated so far. Does not take -Werror into account.
getMessages :: PState -> DynFlags -> Messages Source #
Get the warnings and errors accumulated so far. Does not take -Werror into account.
popContext :: P () Source #
pushModuleContext :: 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 #
Various boolean flags, mostly language extensions, that impact lexing and parsing. Note that a handful of these can change during lexing/parsing.
FfiBit | |
InterruptibleFfiBit | |
CApiFfiBit | |
ArrowsBit | |
ThBit | |
ThQuotesBit | |
IpBit | |
OverloadedLabelsBit | |
ExplicitForallBit | |
BangPatBit | |
PatternSynonymsBit | |
HaddockBit | |
MagicHashBit | |
RecursiveDoBit | |
UnicodeSyntaxBit | |
UnboxedTuplesBit | |
UnboxedSumsBit | |
DatatypeContextsBit | |
MonadComprehensionsBit | |
TransformComprehensionsBit | |
QqBit | |
RawTokenStreamBit | |
AlternativeLayoutRuleBit | |
ALRTransitionalBit | |
RelaxedLayoutBit | |
NondecreasingIndentationBit | |
SafeHaskellBit | |
TraditionalRecordSyntaxBit | |
ExplicitNamespacesBit | |
LambdaCaseBit | |
BinaryLiteralsBit | |
NegativeLiteralsBit | |
HexFloatLiteralsBit | |
TypeApplicationsBit | |
StaticPointersBit | |
NumericUnderscoresBit | |
StarIsTypeBit | |
BlockArgumentsBit | |
NPlusKPatternsBit | |
DoAndIfThenElseBit | |
MultiWayIfBit | |
GadtSyntaxBit | |
ImportQualifiedPostBit | |
InRulePragBit | |
InNestedCommentBit | |
UsePosPragsBit | If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update the internal position. Otherwise, those pragmas are lexed as tokens of their own. |
Instances
Enum ExtBits # | |
Defined in Lexer succ :: ExtBits -> ExtBits Source # pred :: ExtBits -> ExtBits Source # toEnum :: Int -> ExtBits Source # fromEnum :: ExtBits -> Int Source # enumFrom :: ExtBits -> [ExtBits] Source # enumFromThen :: ExtBits -> ExtBits -> [ExtBits] Source # enumFromTo :: ExtBits -> ExtBits -> [ExtBits] Source # enumFromThenTo :: ExtBits -> ExtBits -> ExtBits -> [ExtBits] Source # |
lexTokenStream :: StringBuffer -> RealSrcLoc -> DynFlags -> ParseResult [Located Token] Source #
Encapsulated call to addAnnotation, requiring only the SrcSpan of the AST construct the annotation belongs to; together with the AnnKeywordId, this is the key of the annotation map.
This type is useful for places in the parser where it is not yet
known what SrcSpan an annotation should be added to. The most
common situation is when we are parsing a list: the annotations
need to be associated with the AST element that *contains* the
list, not the list itself. AddAnn
lets us defer adding the
annotations until we finish parsing the list and are now parsing
the enclosing element; we then apply the AddAnn
to associate
the annotations. Another common situation is where a common fragment of
the AST has been factored out but there is no separate AST node for
this fragment (this occurs in class and data declarations). In this
case, the annotation belongs to the parent data declaration.
The usual way an AddAnn
is created is using the mj
("make jump")
function, and then it can be discharged using the ams
function.
mkParensApiAnn :: SrcSpan -> [AddAnn] Source #