Copyright | (c) Edward Kmett 2011-2015 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- newtype Parser a = Parser {}
- manyAccum :: (a -> [a] -> [a]) -> Parser a -> Parser [a]
- data Step a
- feed :: Reducer t Rope => t -> Step r -> Step r
- starve :: Step a -> Result a
- stepParser :: Parser a -> Delta -> ByteString -> Step a
- stepResult :: Rope -> Result a -> Step a
- stepIt :: It Rope a -> Step a
- parseFromFile :: MonadIO m => Parser a -> String -> m (Maybe a)
- parseFromFileEx :: MonadIO m => Parser a -> String -> m (Result a)
- parseString :: Parser a -> Delta -> String -> Result a
- parseByteString :: Parser a -> Delta -> ByteString -> Result a
- parseTest :: (MonadIO m, Show a) => Parser a -> String -> m ()
Documentation
The type of a trifecta parser
The first four arguments are behavior continuations:
- epsilon success: the parser has consumed no input and has a result
as well as a possible Err; the position and chunk are unchanged
(see
pure
) - epsilon failure: the parser has consumed no input and is failing
with the given Err; the position and chunk are unchanged (see
empty
) - committed success: the parser has consumed input and is yielding the result, set of expected strings that would have permitted this parse to continue, new position, and residual chunk to the continuation.
- committed failure: the parser has consumed input and is failing with a given ErrInfo (user-facing error message)
The remaining two arguments are
- the current position
- the chunk of input currently under analysis
Parser
is an Alternative
; trifecta's backtracking behavior encoded as
<|>
is to behave as the leftmost parser which yields a value
(regardless of any input being consumed) or which consumes input and
fails. That is, a choice of parsers will only yield an epsilon failure
if *all* parsers in the choice do. If that is not the desired behavior,
see try
, which turns a committed parser failure into an epsilon failure
(at the cost of error information).
Feeding a parser more more input
stepParser :: Parser a -> Delta -> ByteString -> Step a Source #
Parsing
parseFromFile :: MonadIO m => Parser a -> String -> m (Maybe a) Source #
parseFromFile p filePath
runs a parser p
on the
input read from filePath
using readFile
. All diagnostic messages
emitted over the course of the parse attempt are shown to the user on the console.
main = do result <- parseFromFile numbers "digits.txt" case result of Nothing -> return () Just a -> print $ sum a
parseFromFileEx :: MonadIO m => Parser a -> String -> m (Result a) Source #
parseFromFileEx p filePath
runs a parser p
on the
input read from filePath
using readFile
. Returns all diagnostic messages
emitted over the course of the parse and the answer if the parse was successful.
main = do result <- parseFromFileEx (many number) "digits.txt" case result of Failure xs -> displayLn xs Success a -> print (sum a)
parseByteString :: Parser a -> Delta -> ByteString -> Result a Source #
parseByteString p delta i
runs a parser p
on i
.