{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Machine.Attoparsec.Text
( parse
, many
) where
import qualified Data.Attoparsec.Text as P
import qualified Data.Attoparsec.Internal.Types as PI
import qualified Data.Text as T
import Data.Machine
import Data.Machine.Stack
parse :: forall m a . Monad m => P.Parser a -> MachineT m (Stack T.Text) (Either String a)
parse p = encased $ Await (\b -> if PI.nullChunk b
then parse p
else feed (P.parse p b)) Pop stopped
where
feed :: P.Result a -> MachineT m (Stack T.Text) (Either String a)
feed (P.Partial c) = encased $
Await (\b -> if PI.nullChunk b
then feed (P.Partial c)
else feed (c b)) Pop (feed $ c mempty)
feed (P.Done i r) = encased $
Await (\() -> encased $ Yield (Right r) stopped) (Push i) stopped
feed (P.Fail i _ e) = encased $
Await (\() -> encased $ Yield (Left e) stopped) (Push i) stopped
{-# INLINE feed #-}
{-# INLINE parse #-}
many :: forall m a. Monad m => P.Parser a -> MachineT m (Stack T.Text) (Either String a)
many p = pp
where
pp = encased $ Await (\b -> if PI.nullChunk b
then pp
else (feed . P.parse p $ b)) Pop stopped
{-# INLINE pp #-}
feed :: P.Result a -> MachineT m (Stack T.Text) (Either String a)
feed (P.Partial c) = encased $
Await (\b -> if PI.nullChunk b
then feed (P.Partial c)
else feed (c b)) Pop (finish $ c mempty)
feed (P.Done i r) = encased $
Await (\() -> encased $ Yield (Right r) pp) (Push i) stopped
feed (P.Fail i _ e) = encased $
Await (\() -> encased $ Yield (Left e) pp) (Push i) stopped
{-# INLINE feed #-}
finish (P.Partial _) = stopped
finish (P.Done i r) = encased $
Await (\() -> encased $ Yield (Right r) stopped) (Push i) stopped
finish (P.Fail i _ e) = encased $
Await (\() -> encased $ Yield (Left e) stopped) (Push i) stopped
{-# INLINE finish #-}
{-# INLINE many #-}