[Haskell-cafe] Strange error when using Attoparsec and Enumerator

Crutcher Dunnavant crutcher at gmail.com
Sun Dec 5 18:14:20 CET 2010


I have spent a good chunk of the past week tracing code, trying to
solve this problem. I'm seeing an error when using Enumerator and
Attoparsec that I can't explain. This is a reduced form of the
problem.

In general, I've observed that debugging broken iterators and
enumerators is very hard. We probably want some tooling around that;
I'm looking at an identity enumeratee with debug.trace shoved in, or
something like that, not sure yet what would help.

{-
Haskell 2010, ghc 6.12.3
array-0.3.0.2
attoparsec-0.8.2.0
attoparsec-enumerator-0.2.0.2
bytestring-0.9.1.7
containers-0.4.0.0
deepseq-1.1.0.2
enumerator-0.4.2
text-0.10.0.0
transformers-0.2.2.0
-}
import Control.Applicative ((<|>))
import qualified Data.Attoparsec.Char8 as AP
import qualified Data.Attoparsec.Combinator as APC
import qualified Data.Attoparsec.Enumerator as APE
import qualified Data.ByteString.Char8 as B
import qualified Data.Enumerator as E
import Data.Enumerator (($$))
import System.IO as IO

parseLine :: AP.Parser B.ByteString
parseLine = do
  AP.char '+'
  return . B.pack =<< APC.manyTill AP.anyChar endOfLineOrInput

endOfLineOrInput :: AP.Parser ()
endOfLineOrInput = AP.endOfInput <|> AP.endOfLine

pp :: Show a => AP.Parser a -> String -> IO ()
pp p s = do
  result <- E.run $
    E.enumList 1 [ B.pack s ]
    $$ E.sequence (APE.iterParser p)
    $$ E.printChunks False
  case result of
    (Right _) -> return ()
    (Left e)  -> IO.hPutStrLn stderr $ show e

main = pp parseLine "+OK"
{-
Observed output:
["OK"]
*** Exception: enumEOF: divergent iteratee

Problems with this:
1) I didn't write an iteratee, enumerator, or enumeratee in this code.
Something's wrong.

2) If the parser is divergent, I _should_ be getting the error message:
  "iterParser: divergent parser"
-}

--
Crutcher Dunnavant <crutcher at gmail.com>



More information about the Haskell-Cafe mailing list