Copyright | (c) Edward Kmett 2011-2019 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- 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 -> Step a
- stepResult :: Rope -> Result a -> Step a
- stepIt :: It Rope a -> Step a
- runParser :: Reducer t Rope => Parser a -> Delta -> t -> Result 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).
Instances
MonadFail Parser Source # | |
Defined in Text.Trifecta.Parser | |
Alternative Parser Source # | |
Applicative Parser Source # | |
Functor Parser Source # | |
Monad Parser Source # | |
MonadPlus Parser Source # | |
CharParsing Parser Source # | |
Parsing Parser Source # | |
LookAheadParsing Parser Source # | |
Defined in Text.Trifecta.Parser | |
TokenParsing Parser Source # | |
DeltaParsing Parser Source # | |
Defined in Text.Trifecta.Parser | |
Errable Parser Source # | |
MarkParsing Delta Parser Source # | |
(Semigroup a, Monoid a) => Monoid (Parser a) Source # | |
Semigroup a => Semigroup (Parser a) Source # | |
Feeding a parser more more input
A Step
allows for incremental parsing, since the parser
- can be done with a final result
- have errored
- can have yielded a partial result with possibly more to come
StepDone !Rope a | Parsing is done and has converted the |
StepFail !Rope ErrInfo | Parsing the |
StepCont !Rope (Result a) (Rope -> Step a) | The One common scenario for this is to parse log files: after parsing a single line, that data can already be worked with, but there may be more lines to come. |
feed :: Reducer t Rope => t -> Step r -> Step r Source #
Feed some additional input to a Step
to continue parsing a bit further.
starve :: Step a -> Result a Source #
Assume all possible input has been given to the parser, execute it to yield a final result.
Parsing
:: Reducer t Rope | |
=> Parser a | |
-> Delta | Starting cursor position. Usually |
-> t | |
-> Result a |
Run a Parser
on input that can be reduced to a Rope
, e.g. String
, or
ByteString
. See also the monomorphic versions parseString
and
parseByteString
.
parseFromFile :: MonadIO m => Parser a -> String -> m (Maybe a) Source #
(
runs a parser parseFromFile
p filePath)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 #
(
runs a parser parseFromFileEx
p filePath)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)
:: Parser a | |
-> Delta | Starting cursor position. Usually |
-> ByteString | |
-> Result a |
Fully parse a ByteString
to a Result
.
parseByteString p delta i
runs a parser p
on i
.