Agda-2.5.3: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell2010

Agda.Syntax.Parser.Monad

Contents

Synopsis

The parser monad

data Parser a Source #

The parse monad. Equivalent to StateT ParseState (Either ParseError) except for the definition of fail, which builds a suitable ParseError object.

Instances

Monad Parser Source # 

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

MonadState ParseState Parser Source # 
MonadError ParseError Parser Source # 

data ParseResult a Source #

The result of parsing something.

data ParseState Source #

The parser state. Contains everything the parser and the lexer could ever need.

Constructors

PState 

Fields

data ParseError Source #

What you get if parsing fails.

Constructors

ParseError

Errors that arise at a specific position in the file

Fields

OverlappingTokensError

Parse errors that concern a range in a file.

Fields

InvalidExtensionError

Parse errors that concern a whole file.

Fields

ReadFileError 

Fields

data ParseWarning Source #

Warnings for parsing

Constructors

OverlappingTokensWarning

Parse errors that concern a range in a file.

Fields

Instances

Data ParseWarning Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseWarning -> c ParseWarning #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParseWarning #

toConstr :: ParseWarning -> Constr #

dataTypeOf :: ParseWarning -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParseWarning) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseWarning) #

gmapT :: (forall b. Data b => b -> b) -> ParseWarning -> ParseWarning #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseWarning -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseWarning -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseWarning -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseWarning -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseWarning -> m ParseWarning #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseWarning -> m ParseWarning #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseWarning -> m ParseWarning #

Show ParseWarning Source # 
Pretty ParseWarning Source # 
HasRange ParseWarning Source # 

type LexState = Int Source #

To do 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.

Constructors

NoLayout

no layout

Layout Int32

layout at specified column

data ParseFlags Source #

There aren't any parser flags at the moment.

Constructors

ParseFlags 

Fields

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.

parseFile :: ParseFlags -> [LexState] -> Parser a -> AbsolutePath -> IO (ParseResult a) Source #

The most general way of parsing a file. The Agda.Syntax.Parser will define more specialised functions that supply the ParseFlags and the LexState.

Note that Agda source files always use the UTF-8 character encoding.

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

getParseInterval :: Parser Interval Source #

The parse interval is between the last position and the current position.

Layout

topContext :: Parser LayoutContext Source #

Return the current layout context.

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 #

parseError = fail

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.

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.