Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Parser a
- data ParseResult a
- data ParseState = PState {}
- data ParseError
- = ParseError {
- errSrcFile :: !SrcFile
- errPos :: !PositionWithoutFile
- errInput :: String
- errPrevToken :: String
- errMsg :: String
- | OverlappingTokensError { }
- | InvalidExtensionError {
- errPath :: !AbsolutePath
- errValidExts :: [String]
- | ReadFileError {
- errPath :: !AbsolutePath
- errIOError :: IOError
- = ParseError {
- data ParseWarning = OverlappingTokensWarning {}
- type LexState = Int
- data LayoutContext
- data ParseFlags = ParseFlags {}
- initState :: Maybe AbsolutePath -> ParseFlags -> String -> [LexState] -> ParseState
- defaultParseFlags :: ParseFlags
- parse :: ParseFlags -> [LexState] -> Parser a -> String -> ParseResult a
- parsePosString :: Position -> ParseFlags -> [LexState] -> Parser a -> String -> ParseResult a
- parseFromSrc :: ParseFlags -> [LexState] -> Parser a -> SrcFile -> String -> ParseResult a
- setParsePos :: PositionWithoutFile -> Parser ()
- setLastPos :: PositionWithoutFile -> Parser ()
- getParseInterval :: Parser Interval
- setPrevToken :: String -> Parser ()
- getParseFlags :: Parser ParseFlags
- getLexState :: Parser [LexState]
- pushLexState :: LexState -> Parser ()
- popLexState :: Parser ()
- topContext :: Parser LayoutContext
- popContext :: Parser ()
- pushContext :: LayoutContext -> Parser ()
- pushCurrentContext :: Parser ()
- parseWarningName :: ParseWarning -> WarningName
- parseError :: String -> Parser a
- parseErrorAt :: PositionWithoutFile -> String -> Parser a
- parseError' :: Maybe PositionWithoutFile -> String -> Parser a
- parseErrorRange :: HasRange r => r -> String -> Parser a
- lexError :: String -> Parser a
The parser monad
The parse monad.
Instances
Monad Parser Source # | |
Functor Parser Source # | |
Applicative Parser Source # | |
MonadState ParseState Parser Source # | |
Defined in Agda.Syntax.Parser.Monad get :: Parser ParseState # put :: ParseState -> Parser () # state :: (ParseState -> (a, ParseState)) -> Parser a # | |
MonadError ParseError Parser Source # | |
Defined in Agda.Syntax.Parser.Monad throwError :: ParseError -> Parser a # catchError :: Parser a -> (ParseError -> Parser a) -> Parser a # |
data ParseResult a Source #
The result of parsing something.
Instances
Show a => Show (ParseResult a) Source # | |
Defined in Agda.Syntax.Parser.Monad showsPrec :: Int -> ParseResult a -> ShowS # show :: ParseResult a -> String # showList :: [ParseResult a] -> ShowS # |
data ParseState Source #
The parser state. Contains everything the parser and the lexer could ever need.
PState | |
|
Instances
Show ParseState Source # | |
Defined in Agda.Syntax.Parser.Monad showsPrec :: Int -> ParseState -> ShowS # show :: ParseState -> String # showList :: [ParseState] -> ShowS # | |
MonadState ParseState Parser Source # | |
Defined in Agda.Syntax.Parser.Monad get :: Parser ParseState # put :: ParseState -> Parser () # state :: (ParseState -> (a, ParseState)) -> Parser a # |
data ParseError Source #
Parse errors: what you get if parsing fails.
ParseError | Errors that arise at a specific position in the file |
| |
OverlappingTokensError | Parse errors that concern a range in a file. |
InvalidExtensionError | Parse errors that concern a whole file. |
| |
ReadFileError | |
|
Instances
Show ParseError Source # | |
Defined in Agda.Syntax.Parser.Monad showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Pretty ParseError Source # | |
Defined in Agda.Syntax.Parser.Monad pretty :: ParseError -> Doc Source # prettyPrec :: Int -> ParseError -> Doc Source # prettyList :: [ParseError] -> Doc Source # | |
HasRange ParseError Source # | |
Defined in Agda.Syntax.Parser.Monad getRange :: ParseError -> Range Source # | |
MonadError ParseError Parser Source # | |
Defined in Agda.Syntax.Parser.Monad throwError :: ParseError -> Parser a # catchError :: Parser a -> (ParseError -> Parser a) -> Parser a # | |
MonadError ParseError PM Source # | |
Defined in Agda.Syntax.Parser throwError :: ParseError -> PM a # catchError :: PM a -> (ParseError -> PM a) -> PM a # |
data ParseWarning Source #
Warnings for parsing.
OverlappingTokensWarning | Parse errors that concern a range in a file. |
Instances
For context sensitive lexing alex provides what is called start codes
in the Alex documentation. It is really an integer representing the state
of the lexer, so we call it LexState
instead.
data LayoutContext Source #
We need to keep track of the context to do layout. The context specifies the indentation (if any) of a layout block. See Agda.Syntax.Parser.Layout for more informaton.
Instances
Show LayoutContext Source # | |
Defined in Agda.Syntax.Parser.Monad showsPrec :: Int -> LayoutContext -> ShowS # show :: LayoutContext -> String # showList :: [LayoutContext] -> ShowS # |
data ParseFlags Source #
Parser flags.
ParseFlags | |
|
Instances
Show ParseFlags Source # | |
Defined in Agda.Syntax.Parser.Monad showsPrec :: Int -> ParseFlags -> ShowS # show :: ParseFlags -> String # showList :: [ParseFlags] -> ShowS # |
Running the parser
initState :: Maybe AbsolutePath -> ParseFlags -> String -> [LexState] -> ParseState Source #
Constructs the initial state of the parser. The string argument is the input string, the file path is only there because it's part of a position.
defaultParseFlags :: ParseFlags Source #
The default flags.
parse :: ParseFlags -> [LexState] -> Parser a -> String -> ParseResult a Source #
The most general way of parsing a string. The Agda.Syntax.Parser will define
more specialised functions that supply the ParseFlags
and the
LexState
.
parsePosString :: Position -> ParseFlags -> [LexState] -> Parser a -> String -> ParseResult a Source #
The even more general way of parsing a string.
parseFromSrc :: ParseFlags -> [LexState] -> Parser a -> SrcFile -> String -> ParseResult a Source #
Parses a string as if it were the contents of the given file Useful for integrating preprocessors.
Manipulating the state
setParsePos :: PositionWithoutFile -> Parser () Source #
setLastPos :: PositionWithoutFile -> Parser () Source #
getParseInterval :: Parser Interval Source #
The parse interval is between the last position and the current position.
setPrevToken :: String -> Parser () Source #
getLexState :: Parser [LexState] Source #
pushLexState :: LexState -> Parser () Source #
popLexState :: Parser () Source #
Layout
topContext :: Parser LayoutContext Source #
Return the current layout context.
popContext :: Parser () Source #
pushContext :: LayoutContext -> Parser () Source #
pushCurrentContext :: Parser () Source #
Should only be used at the beginning of a file. When we start parsing we should be in layout mode. Instead of forcing zero indentation we use the indentation of the first token.
Errors
parseError :: String -> Parser a Source #
Throw a parse error at the current position.
parseErrorAt :: PositionWithoutFile -> String -> Parser a Source #
Fake a parse error at the specified position. Used, for instance, when lexing nested comments, which when failing will always fail at the end of the file. A more informative position is the beginning of the failing comment.
parseError' :: Maybe PositionWithoutFile -> String -> Parser a Source #
Use parseErrorAt
or parseError
as appropriate.
parseErrorRange :: HasRange r => r -> String -> Parser a Source #
Report a parse error at the beginning of the given Range
.
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.