| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Agda.Syntax.Parser.LexActions
Description
This module contains the building blocks used to construct the lexer.
- lexToken :: Parser Token
- token :: (String -> Parser tok) -> LexAction tok
- withInterval :: ((Interval, String) -> tok) -> LexAction tok
- withInterval' :: (String -> a) -> ((Interval, a) -> tok) -> LexAction tok
- withInterval_ :: (Interval -> r) -> LexAction r
- withLayout :: LexAction r -> LexAction r
- begin :: LexState -> LexAction Token
- end :: LexAction Token
- endWith :: LexAction a -> LexAction a
- begin_ :: LexState -> LexAction Token
- end_ :: LexAction Token
- lexError :: String -> Parser a
- keyword :: Keyword -> LexAction Token
- symbol :: Symbol -> LexAction Token
- identifier :: LexAction Token
- literal :: Read a => (Range -> a -> Literal) -> LexAction Token
- followedBy :: Char -> LexPredicate
- eof :: LexPredicate
- inState :: LexState -> LexPredicate
Main function
lexToken :: Parser Token Source
Scan the input to find the next token. Calls
alexScanUser. This is the main lexing function
where all the work happens. The function lexer,
used by the parser is the continuation version of this function.
Lex actions
General actions
withInterval :: ((Interval, String) -> tok) -> LexAction tok Source
Parse a token from an Interval and the lexed string.
withInterval' :: (String -> a) -> ((Interval, a) -> tok) -> LexAction tok Source
Like withInterval, but applies a function to the string.
withInterval_ :: (Interval -> r) -> LexAction r Source
Return a token without looking at the lexed string.
withLayout :: LexAction r -> LexAction r Source
Executed for layout keywords. Enters the layout
   state and performs the given action.
lexError :: String -> Parser a Source
For lexical errors we want to report the current position as the site of
   the error, whereas for parse errors the previous position is the one
   we're interested in (since this will be the position of the token we just
   lexed). This function does parseErrorAt the current position.
Specialized actions
keyword :: Keyword -> LexAction Token Source
Parse a Keyword token, triggers layout for layoutKeywords.
identifier :: LexAction Token Source
Parse an identifier. Identifiers can be qualified (see Name).
   Example: Foo.Bar.f
Lex predicates
followedBy :: Char -> LexPredicate Source
True when the given character is the next character of the input string.
True if we are at the end of the file.
inState :: LexState -> LexPredicate Source
True if the given state appears somewhere on the state stack