[Haskell] ANNOUNCE: incremental-parser library package

Mario Blažević mblazevic at stilo.com
Tue Mar 22 15:14:05 CET 2011


    The first version of incremental-parser has been released on Hackage
[1]. It's yet another parser combinator
library, providing the usual set of Applicative and Monad combinators. Apart
from this, it has three twists that make it
unique.

    First, the parser is incremental. That means it can be fed its input in
chunks, and in proper circumstances it can
also provide the parsed output in chunks. For this to be possible the result
type must be a Monoid. The complete parsing
result is then a concatenation of the partial results.

    In order to make the incremental parsing easier, the combinator set is
optimized for monoidal results. The usual
combinator many1, for example, assumes the result type is a monoid and
concatenates its components instead of
constructing a list.

In Parsec:
> many1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m [a]

In incremental-parser:
> many1 :: (Monoid s, Monoid r) => Parser s r -> Parser s r


    The second weirdness is that the the parser is generic in its input
stream type, but this type is parameterized in a
holistic way. There is no separate token type. Primitive parsers that need
to peek into the input require its type to be
an instance of a monoid subclass.

In Parsec:
> string :: Stream s m Char => String -> ParsecT s u m String
> char :: Stream s m Char => Char -> ParsecT s u m Char
> anyToken :: (Stream s m t, Show t) => ParsecT s u m t

In Attoparsec:
> string :: ByteString -> Parser ByteString
> word8 :: Word8 -> Parser Word8
> anyWord8 :: Parser Word8

In incremental-parser:
> string :: (LeftCancellativeMonoid s, MonoidNull s) => s -> Parser s s
> token :: (Eq s, FactorialMonoid s) => s -> Parser s s
> anyToken :: FactorialMonoid s => Parser s s

    The monoid subclasses referenced above provide methods for analyzing and
subdividing the input stream. The classes
are not particularly demanding, and any reasonable input stream should be
able to accommodate them easily. The library
comes with instances for lists, ByteString, and Text.

> class Monoid m => MonoidNull m where
>    mnull :: m -> Bool

> class Monoid m => LeftCancellativeMonoid m where
>    mstripPrefix :: m -> m -> Maybe m

> class Monoid m => FactorialMonoid m where
>    factors :: m -> [m]
>    primePrefix :: m -> m
>    ...


    Finally, the library being implemented on the basis of Brzozowski
derivatives, it can provide both the symmetric and
the left-biased choice, <|> and <<|>. This is the same design choice made by
Text.ParserCombinators.ReadP and
uu-parsinglib. Parsec and its progeny on the other hand provide only the
faster left-biased choice, at some cost to the
expressiveness of the combinator language.

[1] http://hackage.haskell.org/package/incremental-parser-0.1
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell/attachments/20110322/da9d52c0/attachment-0001.htm>


More information about the Haskell mailing list