Copyright | Bryan O'Sullivan 2007-2011, Mario Blažević 2014 |
---|---|
License | BSD3 |
Maintainer | Mario Blažević |
Stability | experimental |
Portability | unknown |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Simple, efficient combinator parsing for
LeftGCDMonoid
and
FactorialMonoid
inputs, loosely based on
Parsec and derived from Attoparsec.
- data Parser t a
- type Result = IResult
- data IResult i r
- compareResults :: (Eq i, Eq r) => IResult i r -> IResult i r -> Maybe Bool
- parse :: Monoid t => Parser t a -> t -> IResult t a
- feed :: Monoid i => IResult i r -> i -> IResult i r
- parseOnly :: Monoid t => Parser t a -> t -> Either String a
- parseWith :: (Monoid t, Monad m) => m t -> Parser t a -> t -> m (Result t a)
- parseTest :: (Monoid t, Show t, Show a) => Parser t a -> t -> IO ()
- maybeResult :: Result t r -> Maybe r
- eitherResult :: Result t r -> Either String r
- anyToken :: FactorialMonoid t => Parser t t
- notToken :: (Eq t, FactorialMonoid t) => t -> Parser t t
- peekToken :: FactorialMonoid t => Parser t t
- satisfy :: FactorialMonoid t => (t -> Bool) -> Parser t t
- satisfyWith :: FactorialMonoid t => (t -> a) -> (a -> Bool) -> Parser t a
- skip :: FactorialMonoid t => (t -> Bool) -> Parser t ()
- anyChar :: TextualMonoid t => Parser t Char
- char :: TextualMonoid t => Char -> Parser t Char
- notChar :: TextualMonoid t => Char -> Parser t Char
- peekChar :: TextualMonoid t => Parser t (Maybe Char)
- peekChar' :: TextualMonoid t => Parser t Char
- satisfyChar :: TextualMonoid t => (Char -> Bool) -> Parser t Char
- scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser t t
- string :: (LeftGCDMonoid t, MonoidNull t) => t -> Parser t t
- skipWhile :: FactorialMonoid t => (t -> Bool) -> Parser t ()
- take :: FactorialMonoid t => Int -> Parser t t
- takeWhile :: FactorialMonoid t => (t -> Bool) -> Parser t t
- takeWhile1 :: FactorialMonoid t => (t -> Bool) -> Parser t t
- takeTill :: FactorialMonoid t => (t -> Bool) -> Parser t t
- scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser t t
- skipCharsWhile :: TextualMonoid t => (Char -> Bool) -> Parser t ()
- takeCharsWhile :: TextualMonoid t => (Char -> Bool) -> Parser t t
- takeCharsWhile1 :: TextualMonoid t => (Char -> Bool) -> Parser t t
- takeCharsTill :: TextualMonoid t => (Char -> Bool) -> Parser t t
- takeTillChar :: TextualMonoid t => (Char -> Bool) -> Parser t t
- takeTillChar1 :: TextualMonoid t => (Char -> Bool) -> Parser t t
- takeRest :: MonoidNull t => Parser t t
- endOfLine :: (Eq t, TextualMonoid t) => Parser t ()
- try :: Parser i a -> Parser i a
- (<?>) :: Parser i a -> String -> Parser i a
- choice :: Alternative f => [f a] -> f a
- count :: Monad m => Int -> m a -> m [a]
- option :: Alternative f => a -> f a -> f a
- many' :: MonadPlus m => m a -> m [a]
- many1 :: Alternative f => f a -> f [a]
- many1' :: MonadPlus m => m a -> m [a]
- manyTill :: Alternative f => f a -> f b -> f [a]
- manyTill' :: MonadPlus m => m a -> m b -> m [a]
- sepBy :: Alternative f => f a -> f s -> f [a]
- sepBy' :: MonadPlus m => m a -> m s -> m [a]
- sepBy1 :: Alternative f => f a -> f s -> f [a]
- sepBy1' :: MonadPlus m => m a -> m s -> m [a]
- skipMany :: Alternative f => f a -> f ()
- skipMany1 :: Alternative f => f a -> f ()
- eitherP :: Alternative f => f a -> f b -> f (Either a b)
- endOfInput :: MonoidNull t => Parser t ()
- atEnd :: MonoidNull t => Parser t Bool
Differences from Parsec
Compared to Parsec 3, Picoparsec makes several tradeoffs. It is not intended for, or ideal for, all possible uses.
- While Picoparsec can consume input incrementally, Parsec cannot. Incremental input is a huge deal for efficient and secure network and system programming, since it gives much more control to users of the library over matters such as resource usage and the I/O model to use.
- Much of the performance advantage of Picoparsec is gained via high-performance parsers such as
takeWhile
andstring
. If you use complicated combinators that return lists of bytes or characters, there is less performance difference between the two libraries. - Unlike Parsec 3, Picoparsec does not support being used as a monad transformer.
- Parsec parsers can produce more helpful error messages than Picoparsec parsers. This is a matter of focus: Picoparsec avoids the extra book-keeping in favour of higher performance.
- Parsec comes with built-in support for user state. Picoparsec does not maintain any state by default, in order to
maximize performance. If your parsing logic needs depends on it, you can track the state by wrapping your input in a
Stateful
monoid.
Differences from Attoparsec
Compared to Attoparsec, Picoparsec trades away some performance for generality. Attoparsec works only with
ByteString
and Text
inputs. If your input type is one of these two, Attoparsec is the better choice. Use
Picoparsec if you want your parser to be applicable to a different input type, especially if you wish to leave the
choice of that input type to the end user.
Some Attoparsec primitives like word8
are missing because they are specific to ByteString inputs. Picoparsec is
otherwise largely compatible with Attoparsec, having copied from it both the core logic and the full set of parsing
combinators.
Incremental input
Picoparsec supports incremental input, meaning that you can feed it a chunk of input that represents only part of the
expected total amount of data to parse. If your parser reaches the end of a fragment of input and could consume more
input, it will suspend parsing and return a Partial
continuation.
Supplying the Partial
continuation with another string will resume parsing at the point where it was
suspended. You must be prepared for the result of the resumed parse to be another Partial
continuation.
To indicate that you have no more input, supply the Partial
continuation with an empty string.
Remember that some parsing combinators will not return a result until they reach the end of input. They may thus
cause Partial
results to be returned.
If you do not need support for incremental input, consider using the parseOnly
function to run your parser. It
will never prompt for more input.
Performance considerations
A Picoparsec-based parser applied to a strict ByteString or Text input will generally be somewhat slower than Attoparsec, but if properly optimized and specialized the difference should be less than 50%.
To actually achieve high performance, there are a few guidelines that it is useful to follow.
- Use the input-returning parsers whenever possible, e.g.
takeWhile1
instead ofmany1
anyToken
. There is a large difference in performance between the two kinds of parsers. - If you are parsing textual inputs, use the specialized character parsers; e.g.
takeCharsWhile1
instead oftakeWhile1
. - If the
mappend
operation is slow for the input monoid type, it may drastically slow down the parsing of large inputs. Try wrapping the input with theConcat
newtype to make themappend
time constant. - Use the INLINE, INLINABLE, and SPECIALIZE pragmas to optimize the more important parts of your parser for the likely input types.
- Make active use of benchmarking and profiling tools to measure, find the problems with, and improve the performance of your parser.
Parser types
The core parser type. This is parameterised over the type t
of
string being processed.
This type is an instance of the following classes:
Monad
, wherefail
throws an exception (i.e. fails) with an error message.Functor
andApplicative
, which follow the usual definitions.MonadPlus
, wheremzero
fails (with no error message) andmplus
executes the right-hand parser if the left-hand one fails. When the parser on the right executes, the input is reset to the same state as the parser on the left started with. (In other words, Picoparsec is a backtracking parser that supports arbitrary lookahead.)Alternative
, which followsMonadPlus
.
Monoid i => Alternative (Parser i) | |
Monad (Parser t) | |
Functor (Parser t) | |
Monoid t => MonadPlus (Parser t) | |
Applicative (Parser i) | |
(IsString a, LeftGCDMonoid a, MonoidNull a, (~) * a b) => IsString (Parser a b) |
The result of a parse. This is parameterised over the type t
of string that was processed.
This type is an instance of Functor
, where fmap
transforms the
value in a Done
result.
Fail i [String] String | The parse failed. The |
Partial (i -> IResult i r) | Supply this continuation with more input so that the parser can resume. To indicate that no more input is available, pass an empty string to the continuation. Note: if you get a |
Done i r | The parse succeeded. The |
Running parsers
feed :: Monoid i => IResult i r -> i -> IResult i r Source
If a parser has returned a Partial
result, supply it with more
input.
parseOnly :: Monoid t => Parser t a -> t -> Either String a Source
Run a parser that cannot be resupplied via a Partial
result.
:: (Monoid t, Monad m) | |
=> m t | An action that will be executed to provide the parser
with more input, if necessary. The action must return an
|
-> Parser t a | |
-> t | Initial input for the parser. |
-> m (Result t a) |
Run a parser with an initial input string, and a monadic action that can supply more input if needed.
parseTest :: (Monoid t, Show t, Show a) => Parser t a -> t -> IO () Source
Run a parser and print its result to standard output.
Result conversion
maybeResult :: Result t r -> Maybe r Source
eitherResult :: Result t r -> Either String r Source
Parsing individual tokens
anyToken :: FactorialMonoid t => Parser t t Source
Match any prime input token.
notToken :: (Eq t, FactorialMonoid t) => t -> Parser t t Source
Match any prime input token except the given one.
peekToken :: FactorialMonoid t => Parser t t Source
Match any prime input token. Returns mempty
if end of input
has been reached. Does not consume any input.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
satisfy :: FactorialMonoid t => (t -> Bool) -> Parser t t Source
The parser satisfy p
succeeds for any prime input token for
which the predicate p
returns True
. Returns the token that is
actually parsed.
digit = satisfy isDigit where isDigit w = w >= "0" && w <= "9"
satisfyWith :: FactorialMonoid t => (t -> a) -> (a -> Bool) -> Parser t a Source
The parser satisfyWith f p
transforms an input token, and
succeeds if the predicate p
returns True
on the transformed
value. The parser returns the transformed token that was parsed.
skip :: FactorialMonoid t => (t -> Bool) -> Parser t () Source
The parser skip p
succeeds for any prime input token for which
the predicate p
returns True
.
skipDigit = skip isDigit where isDigit w = w >= "0" && w <= "9"
Parsing individual characters
anyChar :: TextualMonoid t => Parser t Char Source
Match any character.
peekChar :: TextualMonoid t => Parser t (Maybe Char) Source
Match any input character, if available. Does not consume any input.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
peekChar' :: TextualMonoid t => Parser t Char Source
Match any input character, failing if the input doesn't start with any. Does not consume any input.
satisfyChar :: TextualMonoid t => (Char -> Bool) -> Parser t Char Source
The parser satisfy p
succeeds for any input character for
which the predicate p
returns True
. Returns the character that
is actually parsed.
digit = satisfy isDigit where isDigit w = w >= "0" && w <= "9"
Efficient string handling
scan :: FactorialMonoid t => s -> (s -> t -> Maybe s) -> Parser t t Source
A stateful scanner. The predicate consumes and transforms a
state argument, and each transformed state is passed to successive
invocations of the predicate on each token of the input until one
returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the
predicate returns Nothing
on the first prime input factor.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
string :: (LeftGCDMonoid t, MonoidNull t) => t -> Parser t t Source
string s
parses a prefix of input that identically matches
s
. Returns the parsed string (i.e. s
). This parser consumes no
input if it fails (even if a partial match).
Note: The behaviour of this parser is different to that of the
similarly-named parser in Parsec, as this one is all-or-nothing.
To illustrate the difference, the following parser will fail under
Parsec given an input of "for"
:
string "foo" <|> string "for"
The reason for its failure is that the first branch is a
partial match, and will consume the letters 'f'
and 'o'
before failing. In Attoparsec, the above parser will succeed on
that input, because the failed first branch will consume nothing.
skipWhile :: FactorialMonoid t => (t -> Bool) -> Parser t () Source
Skip past input for as long as the predicate returns True
.
take :: FactorialMonoid t => Int -> Parser t t Source
Consume exactly n
prime input tokens.
takeWhile :: FactorialMonoid t => (t -> Bool) -> Parser t t Source
Consume input as long as the predicate returns True
, and return
the consumed input.
This parser does not fail. It will return an empty string if the
predicate returns False
on the first input token.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
takeWhile1 :: FactorialMonoid t => (t -> Bool) -> Parser t t Source
takeTill :: FactorialMonoid t => (t -> Bool) -> Parser t t Source
Consume input as long as the predicate returns False
(i.e. until it returns True
), and return the consumed input.
This parser does not fail. It will return an empty string if the
predicate returns True
on the first input token.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
Efficient character string handling
scanChars :: TextualMonoid t => s -> (s -> Char -> Maybe s) -> Parser t t Source
A stateful scanner. The predicate consumes and transforms a
state argument, and each transformed state is passed to successive
invocations of the predicate on each token of the input until one
returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the
predicate returns Nothing
on the first prime input factor.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
skipCharsWhile :: TextualMonoid t => (Char -> Bool) -> Parser t () Source
Skip past input characters for as long as the predicate returns True
.
takeCharsWhile :: TextualMonoid t => (Char -> Bool) -> Parser t t Source
Consume input characters as long as the predicate returns True
,
and return the consumed input.
This parser does not fail. It will return an empty string if the
predicate returns False
on the first input token.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
takeCharsWhile1 :: TextualMonoid t => (Char -> Bool) -> Parser t t Source
takeCharsTill :: TextualMonoid t => (Char -> Bool) -> Parser t t Source
Consume input characters as long as the predicate returns False
(i.e. until it returns True
), and return the consumed input.
This parser does not fail. It will return an empty string if the
predicate returns True
on the first input token.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
takeTillChar :: TextualMonoid t => (Char -> Bool) -> Parser t t Source
Consume all input until the character for which the predicate
returns True
and return the consumed input.
The only difference between takeCharsTill
and takeTillChar
is
in their handling of non-character data: The former never consumes
it, the latter always does.
This parser does not fail. It will return an empty string if the
predicate returns True
on the first input token.
Note: Because this parser does not fail, do not use it with
combinators such as many
, because such parsers loop until a
failure occurs. Careless use will thus result in an infinite loop.
takeTillChar1 :: TextualMonoid t => (Char -> Bool) -> Parser t t Source
Consume all remaining input
takeRest :: MonoidNull t => Parser t t Source
Consume all remaining input and return it as a single string.
Text parsing
endOfLine :: (Eq t, TextualMonoid t) => Parser t () Source
Match either a single newline character '\n'
, or a carriage
return followed by a newline character "\r\n"
.
Combinators
try :: Parser i a -> Parser i a Source
Attempt a parse, and if it fails, rewind the input so that no input appears to have been consumed.
This combinator is provided for compatibility with Parsec. Picoparsec parsers always backtrack on failure.
Name the parser, in case failure occurs.
choice :: Alternative f => [f a] -> f a Source
choice ps
tries to apply the actions in the list ps
in order,
until one of them succeeds. Returns the value of the succeeding
action.
count :: Monad m => Int -> m a -> m [a] Source
Apply the given action repeatedly, returning every result.
option :: Alternative f => a -> f a -> f a Source
option x p
tries to apply action p
. If p
fails without
consuming input, it returns the value x
, otherwise the value
returned by p
.
priority = option 0 (digitToInt <$> digit)
many' :: MonadPlus m => m a -> m [a] Source
many' p
applies the action p
zero or more times. Returns a
list of the returned values of p
. The value returned by p
is
forced to WHNF.
word = many' letter
many1 :: Alternative f => f a -> f [a] Source
many1 p
applies the action p
one or more times. Returns a
list of the returned values of p
.
word = many1 letter
many1' :: MonadPlus m => m a -> m [a] Source
many1' p
applies the action p
one or more times. Returns a
list of the returned values of p
. The value returned by p
is
forced to WHNF.
word = many1' letter
manyTill :: Alternative f => f a -> f b -> f [a] Source
manyTill p end
applies action p
zero or more times until
action end
succeeds, and returns the list of values returned by
p
. This can be used to scan comments:
simpleComment = string "<!--" *> manyTill anyChar (string "-->")
(Note the overlapping parsers anyChar
and string "-->"
.
While this will work, it is not very efficient, as it will cause a
lot of backtracking.)
manyTill' :: MonadPlus m => m a -> m b -> m [a] Source
manyTill' p end
applies action p
zero or more times until
action end
succeeds, and returns the list of values returned by
p
. This can be used to scan comments:
simpleComment = string "<!--" *> manyTill' anyChar (string "-->")
(Note the overlapping parsers anyChar
and string "-->"
.
While this will work, it is not very efficient, as it will cause a
lot of backtracking.)
The value returned by p
is forced to WHNF.
sepBy :: Alternative f => f a -> f s -> f [a] Source
sepBy p sep
applies zero or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
.
commaSep p = p `sepBy` (char ',')
sepBy' :: MonadPlus m => m a -> m s -> m [a] Source
sepBy' p sep
applies zero or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
. The value
returned by p
is forced to WHNF.
commaSep p = p `sepBy'` (char ',')
sepBy1 :: Alternative f => f a -> f s -> f [a] Source
sepBy1 p sep
applies one or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
.
commaSep p = p `sepBy1` (char ',')
sepBy1' :: MonadPlus m => m a -> m s -> m [a] Source
sepBy1' p sep
applies one or more occurrences of p
, separated
by sep
. Returns a list of the values returned by p
. The value
returned by p
is forced to WHNF.
commaSep p = p `sepBy1'` (char ',')
skipMany :: Alternative f => f a -> f () Source
Skip zero or more instances of an action.
skipMany1 :: Alternative f => f a -> f () Source
Skip one or more instances of an action.
eitherP :: Alternative f => f a -> f b -> f (Either a b) Source
Combine two alternatives.
State observation and manipulation functions
endOfInput :: MonoidNull t => Parser t () Source
Match only if all input has been consumed.
atEnd :: MonoidNull t => Parser t Bool Source
Return an indication of whether the end of input has been reached.