ANNOUNCE: incremental-parser library package

Mario Blažević mblazevic at stilo.com
Sat Apr 2 21:56:07 CEST 2011


On Sat, Apr 2, 2011 at 7:45 AM, S. Doaitse Swierstra
<doaitse at swierstra.net>wrote:

> Can you explain what are the advantages of your library over the online
> version of all applicative parsers in the uu-parsinglib, which are not
> restricted to the monoidal results?
>


    To tell you the truth, even though I've read the uu-parsinglib
documentation I wasn't even aware of different parser types it allowed. The
library documentation does not exactly advertise online parsers. I'm reading
the "A Short Tutorial" paper now (
http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-044.pdf). It is
interesting, but very much misnamed: it is neither short nor a tutorial. It
does a good job of explaining the library implementation, but there's very
little in the way of usage. The Demo.Examples module on the other hand does
not provide any example of incremental parsing.

    Would you mind providing a short example of use of an uu-parsinglib
online parser that actually takes advantage of incremental parsing? Here is
such an example of incremental-parser use that you can adapt:

{-# LANGUAGE OverloadedStrings #-}
>
> module Main where
>
> import Prelude hiding (null)
> import Data.ByteString.Char8 (ByteString, hGet, null, unpack)
> import System.Environment (getArgs)
> import System.IO (hIsEOF, IOMode(ReadMode), withFile)
> import Text.ParserCombinators.Incremental
>
> main= getArgs >>= mapM_ incremental
>
> incremental filename = withFile filename ReadMode (flip processHandle
> testParser)
>    where processHandle h p = do chunk <- hGet h 1024
>                                 if null chunk
>                                    then putStrLn "EOF" >> extract (feedEof
> p)
>                                    else extract (feed chunk p) >>=
> processHandle h
>          extract p = let (r, p') = resultPrefix p
>                      in print r >> return p'
>
> testParser :: Parser ByteString [Int]
> testParser = many0 (fmap (\digits-> [read $ unpack digits]) (takeWhile1
> (\c-> c >= "0" && c <= "9"))
>                     <<|> skip anyToken)
>


    This simple example will read a text file containing integers, in
kilobyte chunks, and print out the list of integers. The parser is
simplistic, but it serves to illustrate the main points of the interface:
  - the parser is fed input in chunks,
  - the parsed results are read in chunks, and
  - the input chunks may overlap with result components.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110402/2496d886/attachment.htm>


More information about the Libraries mailing list