module Waargonaut.Attoparsec
  ( 
    decodeAttoparsecText
  , decodeAttoparsecByteString
  , pureDecodeAttoparsecText
  , pureDecodeAttoparsecByteString
  ) where
import           Data.Functor.Identity      (Identity)
import           Data.ByteString            (ByteString)
import           Data.Text                  (Text)
import qualified Data.Attoparsec.ByteString as AB
import qualified Data.Attoparsec.Text       as AT
import           Waargonaut.Decode          (CursorHistory, Decoder)
import           Waargonaut.Decode.Error    (DecodeError)
import qualified Waargonaut.Decode          as D
decodeAttoparsecText
  :: Monad f
  => Decoder f a
  -> Text
  -> f (Either (DecodeError, CursorHistory) a)
decodeAttoparsecText :: Decoder f a -> Text -> f (Either (DecodeError, CursorHistory) a)
decodeAttoparsecText Decoder f a
decoder =
  (forall a. Parser Text a -> Text -> Either String a)
-> Decoder f a -> Text -> f (Either (DecodeError, CursorHistory) a)
forall (f :: * -> *) (g :: * -> *) e x.
(CharParsing f, Monad f, Monad g, Show e) =>
(forall a. f a -> Text -> Either e a)
-> Decoder g x -> Text -> g (Either (DecodeError, CursorHistory) x)
D.decodeFromText forall a. Parser Text a -> Text -> Either String a
AT.parseOnly Decoder f a
decoder
decodeAttoparsecByteString
  :: Monad f
  => Decoder f a
  -> ByteString
  -> f (Either (DecodeError, CursorHistory) a)
decodeAttoparsecByteString :: Decoder f a
-> ByteString -> f (Either (DecodeError, CursorHistory) a)
decodeAttoparsecByteString Decoder f a
decoder =
  (forall a. Parser ByteString a -> ByteString -> Either String a)
-> Decoder f a
-> ByteString
-> f (Either (DecodeError, CursorHistory) a)
forall (f :: * -> *) (g :: * -> *) e x.
(CharParsing f, Monad f, Monad g, Show e) =>
(forall a. f a -> ByteString -> Either e a)
-> Decoder g x
-> ByteString
-> g (Either (DecodeError, CursorHistory) x)
D.decodeFromByteString forall a. Parser ByteString a -> ByteString -> Either String a
AB.parseOnly Decoder f a
decoder
pureDecodeAttoparsecText
  :: Decoder Identity a
  -> Text
  -> Either (DecodeError, CursorHistory) a
pureDecodeAttoparsecText :: Decoder Identity a -> Text -> Either (DecodeError, CursorHistory) a
pureDecodeAttoparsecText Decoder Identity a
decoder =
  (forall a. Parser Text a -> Text -> Either String a)
-> Decoder Identity a
-> Text
-> Either (DecodeError, CursorHistory) a
forall (f :: * -> *) e x.
(Monad f, CharParsing f, Show e) =>
(forall a. f a -> Text -> Either e a)
-> Decoder Identity x
-> Text
-> Either (DecodeError, CursorHistory) x
D.pureDecodeFromText forall a. Parser Text a -> Text -> Either String a
AT.parseOnly Decoder Identity a
decoder
pureDecodeAttoparsecByteString
  :: Decoder Identity a
  -> ByteString
  -> Either (DecodeError, CursorHistory) a
pureDecodeAttoparsecByteString :: Decoder Identity a
-> ByteString -> Either (DecodeError, CursorHistory) a
pureDecodeAttoparsecByteString Decoder Identity a
decoder =
  (forall a. Parser ByteString a -> ByteString -> Either String a)
-> Decoder Identity a
-> ByteString
-> Either (DecodeError, CursorHistory) a
forall (f :: * -> *) e x.
(Monad f, CharParsing f, Show e) =>
(forall a. f a -> ByteString -> Either e a)
-> Decoder Identity x
-> ByteString
-> Either (DecodeError, CursorHistory) x
D.pureDecodeFromByteString forall a. Parser ByteString a -> ByteString -> Either String a
AB.parseOnly Decoder Identity a
decoder