{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
module Pipes.Attoparsec (
parse
, parsed
, parseL
, parsedL
, isEndOfParserInput
, ParserInput
, ParsingError(..)
) where
import Control.Exception (Exception)
import Control.Monad.Trans.Error (Error)
import qualified Control.Monad.Trans.State.Strict as S
import qualified Data.Attoparsec.ByteString
import qualified Data.Attoparsec.Text
import Data.Attoparsec.Types (IResult (..))
import qualified Data.Attoparsec.Types as Attoparsec
import Data.ByteString (ByteString)
import qualified Data.ByteString
import Data.Data (Data, Typeable)
import Data.Monoid (Monoid (mempty))
import Data.Text (Text)
import qualified Data.Text
import Pipes
import qualified Pipes.Parse as Pipes (Parser)
parse
:: (Monad m, ParserInput a)
=> Attoparsec.Parser a b
-> Pipes.Parser a m (Maybe (Either ParsingError b))
parse parser = S.StateT $ \p0 -> do
x <- nextSkipEmpty p0
case x of
Left r -> return (Nothing, return r)
Right (a,p1) -> step (yield a >>) (_parse parser a) p1
where
step diffP res p0 = case res of
Fail _ c m -> return (Just (Left (ParsingError c m)), diffP p0)
Done a b -> return (Just (Right b), yield a >> p0)
Partial k -> do
x <- nextSkipEmpty p0
case x of
Left e -> step diffP (k mempty) (return e)
Right (a,p1) -> step (diffP . (yield a >>)) (k a) p1
parsed
:: (Monad m, ParserInput a)
=> Attoparsec.Parser a b
-> Producer a m r
-> Producer b m (Either (ParsingError, Producer a m r) r)
parsed parser = go
where
go p0 = do
x <- lift (nextSkipEmpty p0)
case x of
Left r -> return (Right r)
Right (a,p1) -> step (yield a >>) (_parse parser a) p1
step diffP res p0 = case res of
Fail _ c m -> return (Left (ParsingError c m, diffP p0))
Done a b -> yield b >> go (yield a >> p0)
Partial k -> do
x <- lift (nextSkipEmpty p0)
case x of
Left e -> step diffP (k mempty) (return e)
Right (a,p1) -> step (diffP . (yield a >>)) (k a) p1
parseL
:: (Monad m, ParserInput a)
=> Attoparsec.Parser a b
-> Pipes.Parser a m (Maybe (Either ParsingError (Int, b)))
parseL parser = S.StateT $ \p0 -> do
x <- nextSkipEmpty p0
case x of
Left r -> return (Nothing, return r)
Right (a,p1) -> step (yield a >>) (_parse parser a) p1 (_length a)
where
step diffP res p0 !len = case res of
Fail _ c m -> return (Just (Left (ParsingError c m)), diffP p0)
Done a b -> return (Just (Right (len - _length a, b)), yield a >> p0)
Partial k -> do
x <- nextSkipEmpty p0
case x of
Left e -> step diffP (k mempty) (return e) len
Right (a,p1) -> step (diffP . (yield a >>)) (k a) p1 (len + _length a)
parsedL
:: (Monad m, ParserInput a)
=> Attoparsec.Parser a b
-> Producer a m r
-> Producer (Int, b) m (Either (ParsingError, Producer a m r) r)
parsedL parser = go
where
go p0 = do
x <- lift (nextSkipEmpty p0)
case x of
Left r -> return (Right r)
Right (a,p1) -> step (yield a >>) (_parse parser a) p1 (_length a)
step diffP res p0 !len = case res of
Fail _ c m -> return (Left (ParsingError c m, diffP p0))
Done a b -> yield (len - _length a, b) >> go (yield a >> p0)
Partial k -> do
x <- lift (nextSkipEmpty p0)
case x of
Left e -> step diffP (k mempty) (return e) len
Right (a,p1) -> step (diffP . (yield a >>)) (k a) p1 (len + _length a)
isEndOfParserInput :: (Monad m, ParserInput a) => Pipes.Parser a m Bool
isEndOfParserInput = S.StateT $ \p0 -> do
x <- nextSkipEmpty p0
case x of
Left r -> return (True, return r)
Right (a, p1) -> return (False, yield a >> p1)
class (Eq a, Monoid a) => ParserInput a where
_parse :: Attoparsec.Parser a b -> a -> IResult a b
_length :: a -> Int
instance ParserInput ByteString where
_parse = Data.Attoparsec.ByteString.parse
{-# INLINE _parse #-}
_length = Data.ByteString.length
{-# INLINE _length #-}
instance ParserInput Text where
_parse = Data.Attoparsec.Text.parse
{-# INLINE _parse #-}
_length = Data.Text.length
{-# INLINE _length #-}
data ParsingError = ParsingError
{ peContexts :: [String]
, peMessage :: String
} deriving (Show, Read, Eq, Data, Typeable)
instance Exception ParsingError
instance Error ParsingError
instance Error (ParsingError, Producer a m r)
nextSkipEmpty
:: (Monad m, Eq a, Monoid a)
=> Producer a m r
-> m (Either r (a, Producer a m r))
nextSkipEmpty = go where
go p0 = do
x <- next p0
case x of
Left _ -> return x
Right (a,p1)
| a == mempty -> go p1
| otherwise -> return x