Copyright | (c) 2009 Bernie Pope |
---|---|
License | BSD-style |
Maintainer | bjpop@csse.unimelb.edu.au |
Stability | experimental |
Portability | ghc |
Safe Haskell | Safe |
Language | Haskell98 |
Monad support for Python parser and lexer.
Documentation
type P a = StateT ParseState (Either ParseError) a Source #
execParser :: P a -> ParseState -> Either ParseError a Source #
execParserKeepComments :: P a -> ParseState -> Either ParseError (a, [Token]) Source #
runParser :: P a -> ParseState -> Either ParseError (a, ParseState) Source #
setLocation :: SrcLocation -> P () Source #
getLastToken :: P Token Source #
setLastToken :: Token -> P () Source #
setLastEOL :: SrcSpan -> P () Source #
getLastEOL :: P SrcSpan Source #
data ParseError Source #
UnexpectedToken Token | An error from the parser. Token found where it should not be. Note: tokens contain their own source span. |
UnexpectedChar Char SrcLocation | An error from the lexer. Character found where it should not be. |
StrError String | A generic error containing a string message. No source location. |
Instances
Eq ParseError Source # | |
Defined in Language.Python.Common.ParseError (==) :: ParseError -> ParseError -> Bool # (/=) :: ParseError -> ParseError -> Bool # | |
Ord ParseError Source # | |
Defined in Language.Python.Common.ParseError compare :: ParseError -> ParseError -> Ordering # (<) :: ParseError -> ParseError -> Bool # (<=) :: ParseError -> ParseError -> Bool # (>) :: ParseError -> ParseError -> Bool # (>=) :: ParseError -> ParseError -> Bool # max :: ParseError -> ParseError -> ParseError # min :: ParseError -> ParseError -> ParseError # | |
Show ParseError Source # | |
Defined in Language.Python.Common.ParseError showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Error ParseError Source # | |
Defined in Language.Python.Common.ParseError noMsg :: ParseError # strMsg :: String -> ParseError # | |
Pretty ParseError Source # | |
Defined in Language.Python.Common.PrettyParseError pretty :: ParseError -> Doc Source # |
data ParseState Source #
ParseState | |
|
Instances
Show ParseState Source # | |
Defined in Language.Python.Common.ParserMonad showsPrec :: Int -> ParseState -> ShowS # show :: ParseState -> String # showList :: [ParseState] -> ShowS # |
initialState :: SrcLocation -> String -> [Int] -> ParseState Source #
pushStartCode :: Int -> P () Source #
popStartCode :: P () Source #
getStartCode :: P Int Source #
pushIndent :: Int -> P () Source #
addComment :: Token -> P () Source #
getComments :: P [Token] Source #