Safe Haskell | None |
---|
Text.Roundtrip.Parser
- module Text.Parsec
- newPos :: SourceName -> Line -> Column -> SourcePos
- initialPos :: SourceName -> SourcePos
- type PParser s u m = ParsecT s u m
- parsecApply :: Iso a b -> PParser s u m a -> PParser s u m b
- parsecConcat :: PParser s u m a -> PParser s u m b -> PParser s u m (a, b)
- parsecAlternative1Lookahead :: PParser s u m a -> PParser s u m a -> PParser s u m a
- parsecAlternativeInfLookahead :: PParser s u m a -> PParser s u m a -> PParser s u m a
- parsecEmpty :: PParser s u m a
- parsecPure :: a -> PParser s u m a
- runStringParser :: Stream s Identity Char => PParser s () Identity a -> SourceName -> s -> Either ParseError a
- runParser :: Stream s Identity t => Parsec s u a -> u -> SourceName -> s -> Either ParseError a
- mkParseError :: SourcePos -> String -> ParseError
Documentation
module Text.Parsec
newPos :: SourceName -> Line -> Column -> SourcePos
Create a new SourcePos
with the given source name,
line number and column number.
initialPos :: SourceName -> SourcePos
Create a new SourcePos
with the given source name,
and line number and column number set to 1, the upper left.
parsecApply :: Iso a b -> PParser s u m a -> PParser s u m bSource
parsecConcat :: PParser s u m a -> PParser s u m b -> PParser s u m (a, b)Source
parsecAlternative1Lookahead :: PParser s u m a -> PParser s u m a -> PParser s u m aSource
parsecAlternativeInfLookahead :: PParser s u m a -> PParser s u m a -> PParser s u m aSource
parsecEmpty :: PParser s u m aSource
parsecPure :: a -> PParser s u m aSource
runStringParser :: Stream s Identity Char => PParser s () Identity a -> SourceName -> s -> Either ParseError aSource
runParser :: Stream s Identity t => Parsec s u a -> u -> SourceName -> s -> Either ParseError a
The most general way to run a parser over the Identity monad. runParser p state filePath
input
runs parser p
on the input list of tokens input
,
obtained from source filePath
with the initial user state st
.
The filePath
is only used in error messages and may be the empty
string. Returns either a ParseError
(Left
) or a
value of type a
(Right
).
parseFromFile p fname = do{ input <- readFile fname ; return (runParser p () fname input) }
mkParseError :: SourcePos -> String -> ParseErrorSource