Portability | unknown |
---|---|
Stability | experimental |
Maintainer | uzytkownik2@gmail.com |
Simple, efficient combinator parsing for LL.ListLike
lists based on
Attoparsec library.
- data Parser δ a
- data Result δ r
- parse :: Monoid δ => Parser δ a -> δ -> Result δ a
- feed :: Monoid δ => Result δ r -> δ -> Result δ r
- parseWith :: (Monad m, Monoid δ) => m δ -> Parser δ a -> δ -> m (Result δ a)
- parseTest :: (Show a, Show δ, Monoid δ) => Parser δ a -> δ -> IO ()
- maybeResult :: Result δ r -> Maybe r
- eitherResult :: Result δ r -> Either String r
- (<?>) :: Parser δ a -> String -> Parser δ a
- try :: Monoid δ => Parser δ a -> Parser δ a
- module Data.Nanoparsec.Combinator
- elem :: (Eq ε, Show ε, ListLike δ ε) => ε -> Parser δ ε
- anyElem :: ListLike δ ε => Parser δ ε
- satisfy :: ListLike δ ε => (ε -> Bool) -> Parser δ ε
- satisfyWith :: ListLike δ ε => (ε -> a) -> (a -> Bool) -> Parser δ a
- skip :: ListLike δ ε => (ε -> Bool) -> Parser δ ()
- string :: (Eq δ, ListLike δ ε) => δ -> Parser δ δ
- skipWhile :: ListLike δ ε => (ε -> Bool) -> Parser δ ()
- take :: ListLike δ ε => Int -> Parser δ δ
- takeWhile :: ListLike δ ε => (ε -> Bool) -> Parser δ δ
- takeWhile1 :: ListLike δ ε => (ε -> Bool) -> Parser δ δ
- takeTill :: ListLike δ ε => (ε -> Bool) -> Parser δ δ
- endOfInput :: ListLike δ ε => Parser δ ()
- ensure :: ListLike δ ε => Int -> Parser δ ()
- (<*.) :: Monoid δ => Parser δ a -> Parser δ δ -> Parser δ a
- (.*>) :: Monoid δ => Parser δ δ -> Parser δ a -> Parser δ a
Differences from Attoparsec
Compared to Attoparsec and Attoparsec-text Nanoparsec is a little (around 6%) slower. However it allows more abstract parsers on similar level as Parsec 3 (except the monad transformation).
Differences from Parsec
Compared to Parsec 3, Nanoparsec makes several tradeoffs. It is not intended for, or ideal for, all possible uses.
- While Nanoparsec 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 Nanoparsec is gained via
high-performance parsers such as
takeWhile
andstring
. If you use complicated combinators that return lists of elements or characters, there really isn't much performance difference the two libraries. - Unlike Parsec 3, Nanoparsec does not support being used as a monad transformer. This is mostly a matter of the implementor not having needed that functionality.
- Parsec parsers can produce more helpful error messages than Nanoparsec parsers. This is a matter of focus: Nanoparsec avoids the extra book-keeping in favour of higher performance.
Performance considerations
If you write an Nanoparsec-based parser carefully, it can be realistic to expect it to perform within a factor of 2.4 of a hand-rolled C parser (measuring megabytes parsed per second).
To actually achieve high performance, there are a few guidelines that it is useful to follow.
Use the list-oriented parsers whenever possible,
e.g. takeWhile1
instead of many1
I.anyWord8
. There is
about a factor of 100 difference in performance between the two
kinds of parser.
Make active use of benchmarking and profiling tools to measure, find the problems with, and improve the performance of your parser.
Parser types
Typeclass instances
The Parser
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. -
Monoid
, wheremempty
fails (with no error message) andmappend
executes the right-hand parser if the left-hand one fails. -
MonadPlus
andAlternative
, which followsMonadPlus
.
The Result
type is an instance of Functor
, where fmap
transforms the value in a Done
result.
Running parsers
:: (Monad m, Monoid δ) | |
=> m δ | An action that will be executed to provide the parser
with more input, if necessary. The action must return an
|
-> Parser δ a | |
-> δ | Initial input for the parser. |
-> m (Result δ a) |
Run a parser with an initial input string, and a monadic action that can supply more input if needed.
parseTest :: (Show a, Show δ, Monoid δ) => Parser δ a -> δ -> IO ()Source
Run a parser and print its result to standard output.
Result conversion
maybeResult :: Result δ r -> Maybe rSource
eitherResult :: Result δ r -> Either String rSource
Combinators
(<?>) :: Parser δ a -> String -> Parser δ aSource
Match either a single newline character '\n'
, or a carriage
return followed by a newline character "\r\n"
.
try :: Monoid δ => Parser δ a -> Parser δ aSource
Attempt a parse, and if it fails, rewind the input so that no input appears to have been consumed.
This combinator is useful in cases where a parser might consume some input before failing, i.e. the parser needs arbitrary lookahead. The downside to using this combinator is that it can retain input for longer than is desirable.
module Data.Nanoparsec.Combinator
Parsing infividual elements
satisfy :: ListLike δ ε => (ε -> Bool) -> Parser δ εSource
The parser satisfy p
succeeds for any element for which the
predicate p
returns True
. Returns the element that is actually
parsed.
digit = satisfy isDigit where isDigit w = w >= 48 && w <= 57
satisfyWith :: ListLike δ ε => (ε -> a) -> (a -> Bool) -> Parser δ aSource
The parser satisfyWith f p
transforms an element, and succeeds if
the predicate p
returns True
on the transformed value. The
parser returns the transformed element that was parsed.
skip :: ListLike δ ε => (ε -> Bool) -> Parser δ ()Source
The parser skip p
succeeds for any element for which the predicate
p
returns True
.
space = skip isSpace where isDigit w = w == 9 || w == 10 || w == 13 || w == 32
Efficient sublist handling
string :: (Eq δ, ListLike δ ε) => δ -> Parser δ δSource
string s
parses a sequence of elements that identically match
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 that the first branch is a
partial match, and will consume the letters 'f'
and 'o'
before failing. In Nnaoparsec, the above parser will succeed on
that input, because the failed first branch will consume nothing.
takeWhile :: ListLike δ ε => (ε -> Bool) -> Parser δ δ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 element of 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.
takeWhile1 :: ListLike δ ε => (ε -> Bool) -> Parser δ δSource
takeTill :: ListLike δ ε => (ε -> Bool) -> Parser δ δ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 element of 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.
State observation and manipulation functions
endOfInput :: ListLike δ ε => Parser δ ()Source
Match only if all input has been consumed.
ensure :: ListLike δ ε => Int -> Parser δ ()Source
Succeed only if at least n
elements of input are available.
Applicative specializations
We provide specializations of <*
and *>
as <*.
and
.*>
, respectively. Together with IsString
instance of
Parser
, you may write parsers applicatively more easily.
For example:
paren p = "(" .*> p <*. ")"
instead of the more verbose
paren p = string "(" *> p <* string ")"