Safe Haskell | None |
---|---|
Language | Haskell2010 |
- initialInput :: Text -> Text -> Input
- data Input = Input {}
- inputFile :: Input -> Text
- data Lexeme t = Lexeme {
- lexemeText :: !Text
- lexemeToken :: !t
- lexemeRange :: !SourceRange
- data SourcePos = SourcePos {
- sourceIndex :: !Int
- sourceLine :: !Int
- sourceColumn :: !Int
- sourceFile :: !Text
- startPos :: Text -> SourcePos
- beforeStartPos :: Text -> SourcePos
- data SourceRange = SourceRange {
- sourceFrom :: !SourcePos
- sourceTo :: !SourcePos
- prettySourcePos :: SourcePos -> String
- prettySourceRange :: SourceRange -> String
- prettySourcePosLong :: SourcePos -> String
- prettySourceRangeLong :: SourceRange -> String
- class HasRange t where
- (<->) :: (HasRange a, HasRange b) => a -> b -> SourceRange
- moveSourcePos :: Char -> SourcePos -> SourcePos
- data Action s a
- lexeme :: t -> Action s [Lexeme t]
- matchLength :: Action s Int
- matchRange :: Action s SourceRange
- matchText :: Action s Text
- getLexerState :: Action s s
- setLexerState :: s -> Action s ()
- startInput :: Action s Input
- endInput :: Action s Input
- type AlexInput = Input
- alexInputPrevChar :: AlexInput -> Char
- makeAlexGetByte :: (Char -> Word8) -> AlexInput -> Maybe (Word8, AlexInput)
- makeLexer :: ExpQ
- data LexerConfig s t = LexerConfig {
- lexerInitialState :: s
- lexerStateMode :: s -> Int
- lexerEOF :: s -> [Lexeme t]
- simpleLexer :: LexerConfig () t
- data Word8 :: *
Lexer Basics
Prepare the text for lexing.
Information about the lexer's input.
Lexeme | |
|
SourcePos | |
|
beforeStartPos :: Text -> SourcePos Source #
data SourceRange Source #
A range in the source code.
SourceRange | |
|
prettySourcePos :: SourcePos -> String Source #
Pretty print the source position without the file name.
prettySourceRange :: SourceRange -> String Source #
Pretty print the range, without the file name
prettySourcePosLong :: SourcePos -> String Source #
Pretty print the source position, including the file name.
prettySourceRangeLong :: SourceRange -> String Source #
Pretty print the range, including the file name.
moveSourcePos :: Char -> SourcePos -> SourcePos Source #
Update a SourcePos
for a particular matched character
Writing Lexer Actions
An action to be taken when a regular expression matchers.
Lexemes
lexeme :: t -> Action s [Lexeme t] Source #
Use the token and the current match to construct a lexeme.
matchLength :: Action s Int Source #
The number of characters in the matching input.
matchRange :: Action s SourceRange Source #
Get the range for the matching input.
Manipulating the lexer's state
getLexerState :: Action s s Source #
Acces the curent state of the lexer.
setLexerState :: s -> Action s () Source #
Change the state of the lexer.
Access to the lexer's input
startInput :: Action s Input Source #
Acces the input just before the regular expression started matching.
Interface with Alex
alexInputPrevChar :: AlexInput -> Char Source #
Generate a function to use an Alex lexer.
The expression is of type LexerConfig s t -> Input -> [Lexeme t]
data LexerConfig s t Source #
Lexer configuration.
LexerConfig | |
|
simpleLexer :: LexerConfig () t Source #
A lexer that uses no lexer-modes, and does not emit anything at the end of the file.