-----------------------------------------------------------------------------
-- |
-- Module: Data.Attoparsec.Enumerator
-- Copyright: 2010 John Millikin
-- License: MIT
--
-- Maintainer: jmillikin@gmail.com
-- Portability: portable
--
-----------------------------------------------------------------------------
module Data.Attoparsec.Enumerator
	( ParseError (..)
	, iterParser
	) where
import qualified Data.Attoparsec as A
import qualified Data.ByteString as B
import qualified Data.Enumerator as E

-- | The context and message from a 'A.Fail' value.
data ParseError = ParseError
	{ errorContexts :: [String]
	, errorMessage :: String
	}
	deriving (Show)

-- | Convert an Attoparsec 'A.Parser' into an 'E.Iteratee'. The parser will
-- be streamed bytes until it returns 'A.Done' or 'A.Fail'.
iterParser :: Monad m => A.Parser a -> E.Iteratee ParseError B.ByteString m a
iterParser p = E.continue (step (A.parse p)) where
	step parse (E.Chunks xs) = parseLoop parse xs
	step parse E.EOF = case parse B.empty of
		A.Done extra a -> E.yield a (E.Chunks [extra])
		A.Partial _ -> error "iterParser: divergent parser"
		A.Fail _ ctx msg -> err ctx msg
	
	parseLoop parse [] = E.continue (step parse)
	parseLoop parse (x:xs) = case parse x of
		A.Done extra a -> E.yield a (E.Chunks (extra:xs))
		A.Partial parse' -> parseLoop parse' xs
		A.Fail _ ctx msg -> err ctx msg
	
	err ctx msg = E.throwError (ParseError ctx msg)