----------------------------------------------------------------------------- -- | -- Module: Data.Attoparsec.Text.Enumerator -- Copyright: Felipe Lessa 2010, John Millikin 2010 -- License: MIT -- -- Maintainer: felipe.lessa@gmail.com -- Portability: portable -- -- Convert an attoparsec-text parser into an iteratee. This -- package is heavily based on attoparsec-enumerator for the -- original attoparsec on @ByteString@. -- ----------------------------------------------------------------------------- {-# LANGUAGE DeriveDataTypeable #-} module Data.Attoparsec.Text.Enumerator ( ParseError (..) , iterParser ) where import Control.Exception (Exception) import Data.Typeable (Typeable) import qualified Data.Attoparsec.Text as A import qualified Data.Text as T import qualified Data.Enumerator as E -- | The context and message from a 'A.Fail' value. data ParseError = ParseError { errorContexts :: [String] , errorMessage :: String } deriving (Show, Typeable) instance Exception ParseError -- | Convert an Attoparsec 'A.Parser' into an 'E.Iteratee'. The parser will -- be streamed characters until it returns 'A.Done' or 'A.Fail'. -- -- If parsing fails, the iteratee's error value will contain a 'ParseError'. iterParser :: Monad m => A.Parser a -> E.Iteratee T.Text m a iterParser p = E.continue (step (A.parse p)) where step parse (E.Chunks xs) = parseLoop parse (notEmpty xs) step parse E.EOF = case A.feed (parse T.empty) T.empty of A.Done _ a -> E.yield a E.EOF A.Partial _ -> err [] "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 $ if T.null extra then E.Chunks xs else 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) notEmpty = filter (not . T.null)