nanoparsec-0.1.1: An implementation of attoparsec-like parser around list-like

Portabilityunknown
Stabilityexperimental
Maintaineruzytkownik2@gmail.com

Data.Nanoparsec

Contents

Description

Simple, efficient combinator parsing for LL.ListLike lists based on Attoparsec library.

Synopsis

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 and string. 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

data Parser δ a Source

Instances

Monoid δ => Monad (Parser δ) 
Functor (Parser δ) 
Monoid δ => MonadPlus (Parser δ) 
Monoid δ => Applicative (Parser δ) 
Monoid δ => Alternative (Parser δ) 
(Eq δ, ListLike δ ε, IsString δ) => IsString (Parser δ δ) 
Monoid δ => Monoid (Parser δ a) 

data Result δ r Source

Constructors

Fail !δ [String] String 
Partial (δ -> Result δ r) 
Done !δ r 

Instances

Functor (Result δ) 
(Show δ, Show r) => Show (Result δ r) 

Typeclass instances

The Parser type is an instance of the following classes:

  • Monad, where fail throws an exception (i.e. fails) with an error message.
  • Functor and Applicative, which follow the usual definitions.
  • Monoid, where mempty fails (with no error message) and mappend executes the right-hand parser if the left-hand one fails.
  • MonadPlus and Alternative, which follows MonadPlus.

The Result type is an instance of Functor, where fmap transforms the value in a Done result.

Running parsers

parse :: Monoid δ => Parser δ a -> δ -> Result δ aSource

Run a parser and return its result.

feed :: Monoid δ => Result δ r -> δ -> Result δ rSource

parseWithSource

Arguments

:: (Monad m, Monoid δ) 
=> m δ

An action that will be executed to provide the parser with more input, if necessary. The action must return an empty string when there is no more input available.

-> 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

Convert a Result value to a Maybe value. A Partial result is treated as failure.

eitherResult :: Result δ r -> Either String rSource

Convert a Result value to an Either value. A Partial result is treated as failure.

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.

Parsing infividual elements

elem :: (Eq ε, Show ε, ListLike δ ε) => ε -> Parser δ εSource

anyElem :: ListLike δ ε => Parser δ εSource

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.

skipWhile :: ListLike δ ε => (ε -> Bool) -> Parser δ ()Source

take :: ListLike δ ε => Int -> Parser δ δSource

Consume exactly n elements of input.

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

Consume input as long as the predicate returns True, and return the consumed input.

This parser requires the predicate to succeed on at least one element of input: it will fail if the predicate never returns True or if there is no input left.

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 ")"

(<*.) :: Monoid δ => Parser δ a -> Parser δ δ -> Parser δ aSource

Same as Applicative's <* but specialized.

(.*>) :: Monoid δ => Parser δ δ -> Parser δ a -> Parser δ aSource

Same as Applicative's *> but specialized.