{-# LANGUAGE RankNTypes #-}
module Waargonaut.Decode.Runners
(
decodeWithInput
, decodeFromString
, decodeFromText
, decodeFromByteString
, pureDecodeWithInput
, pureDecodeFromText
, pureDecodeFromByteString
, pureDecodeFromString
, overrideParser
, parseWith
) where
import Prelude (Show, String, show)
import Control.Category (id, (.))
import Control.Monad (Monad (..))
import Control.Monad.Reader (local)
import Data.Bifunctor (first)
import Data.Either (Either (..))
import Data.Function (const)
import Data.Functor.Identity (Identity, runIdentity)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Text.Parser.Char (CharParsing)
import Data.ByteString (ByteString)
import Waargonaut.Decode.Error (DecodeError (..))
import Waargonaut.Types
import qualified Waargonaut.Decode.Internal as DI
import Waargonaut.Decode.Types (CursorHistory, DecodeResult (..),
Decoder (..), mkCursor)
decodeWithInput
:: ( CharParsing f
, Show e
, Monad g
, Monad f
)
=> (forall a. f a -> i -> Either e a)
-> (ByteString -> i)
-> (i -> ByteString)
-> Decoder g x
-> i
-> g (Either (DecodeError, CursorHistory) x)
decodeWithInput :: (forall a. f a -> i -> Either e a)
-> (ByteString -> i)
-> (i -> ByteString)
-> Decoder g x
-> i
-> g (Either (DecodeError, CursorHistory) x)
decodeWithInput forall a. f a -> i -> Either e a
parserFn ByteString -> i
toI i -> ByteString
fromI Decoder g x
decode = DecodeResultT Count DecodeError g x
-> g (Either (DecodeError, CursorHistory) x)
forall (f :: * -> *) i a.
Monad f =>
DecodeResultT i DecodeError f a
-> f (Either (DecodeError, CursorHistory' i) a)
DI.runDecoderResultT
(DecodeResultT Count DecodeError g x
-> g (Either (DecodeError, CursorHistory) x))
-> (i -> DecodeResultT Count DecodeError g x)
-> i
-> g (Either (DecodeError, CursorHistory) x)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Decoder g x
-> ParseFn -> JCurs -> DecodeResultT Count DecodeError g x
forall (f :: * -> *) a.
Decoder f a
-> ParseFn -> JCurs -> DecodeResultT Count DecodeError f a
runDecoder Decoder g x
decode ((f Json -> i -> Either e Json)
-> f Json -> i -> Either DecodeError Json
forall (f :: * -> *) e a i.
(CharParsing f, Show e) =>
(f a -> i -> Either e a) -> f a -> i -> Either DecodeError a
parseWith f Json -> i -> Either e Json
forall a. f a -> i -> Either e a
parserFn f Json
forall (f :: * -> *). (Monad f, CharParsing f) => f Json
parseWaargonaut (i -> Either DecodeError Json) -> (ByteString -> i) -> ParseFn
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> i
toI)
(JCurs -> DecodeResultT Count DecodeError g x)
-> (i -> JCurs) -> i -> DecodeResultT Count DecodeError g x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> JCurs
mkCursor
(ByteString -> JCurs) -> (i -> ByteString) -> i -> JCurs
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. i -> ByteString
fromI
decodeFromString
:: ( CharParsing f
, Monad f
, Monad g
, Show e
)
=> (forall a. f a -> String -> Either e a)
-> Decoder g x
-> String
-> g (Either (DecodeError, CursorHistory) x)
decodeFromString :: (forall a. f a -> String -> Either e a)
-> Decoder g x
-> String
-> g (Either (DecodeError, CursorHistory) x)
decodeFromString forall a. f a -> String -> Either e a
parseFn = (forall a. f a -> String -> Either e a)
-> (ByteString -> String)
-> (String -> ByteString)
-> Decoder g x
-> String
-> g (Either (DecodeError, CursorHistory) x)
forall (f :: * -> *) e (g :: * -> *) i x.
(CharParsing f, Show e, Monad g, Monad f) =>
(forall a. f a -> i -> Either e a)
-> (ByteString -> i)
-> (i -> ByteString)
-> Decoder g x
-> i
-> g (Either (DecodeError, CursorHistory) x)
decodeWithInput forall a. f a -> String -> Either e a
parseFn
(Text -> String
Text.unpack (Text -> String) -> (ByteString -> Text) -> ByteString -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Text
Text.decodeUtf8)
(Text -> ByteString
Text.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Text
Text.pack)
decodeFromByteString
:: ( 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)
decodeFromByteString :: (forall a. f a -> ByteString -> Either e a)
-> Decoder g x
-> ByteString
-> g (Either (DecodeError, CursorHistory) x)
decodeFromByteString forall a. f a -> ByteString -> Either e a
parseFn =
(forall a. f a -> ByteString -> Either e a)
-> (ByteString -> ByteString)
-> (ByteString -> ByteString)
-> Decoder g x
-> ByteString
-> g (Either (DecodeError, CursorHistory) x)
forall (f :: * -> *) e (g :: * -> *) i x.
(CharParsing f, Show e, Monad g, Monad f) =>
(forall a. f a -> i -> Either e a)
-> (ByteString -> i)
-> (i -> ByteString)
-> Decoder g x
-> i
-> g (Either (DecodeError, CursorHistory) x)
decodeWithInput forall a. f a -> ByteString -> Either e a
parseFn ByteString -> ByteString
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id ByteString -> ByteString
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
decodeFromText
:: ( 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)
decodeFromText :: (forall a. f a -> Text -> Either e a)
-> Decoder g x -> Text -> g (Either (DecodeError, CursorHistory) x)
decodeFromText forall a. f a -> Text -> Either e a
parseFn =
(forall a. f a -> Text -> Either e a)
-> (ByteString -> Text)
-> (Text -> ByteString)
-> Decoder g x
-> Text
-> g (Either (DecodeError, CursorHistory) x)
forall (f :: * -> *) e (g :: * -> *) i x.
(CharParsing f, Show e, Monad g, Monad f) =>
(forall a. f a -> i -> Either e a)
-> (ByteString -> i)
-> (i -> ByteString)
-> Decoder g x
-> i
-> g (Either (DecodeError, CursorHistory) x)
decodeWithInput forall a. f a -> Text -> Either e a
parseFn ByteString -> Text
Text.decodeUtf8 Text -> ByteString
Text.encodeUtf8
pureDecodeWithInput
:: ( Monad f
, CharParsing f
, Show e
)
=> ( forall g. Monad g
=> (forall a. f a -> i -> Either e a)
-> Decoder g x
-> i
-> g (Either (DecodeError, CursorHistory) x)
)
-> (forall a. f a -> i -> Either e a)
-> Decoder Identity x
-> i
-> Either (DecodeError, CursorHistory) x
pureDecodeWithInput :: (forall (g :: * -> *).
Monad g =>
(forall a. f a -> i -> Either e a)
-> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> i -> Either e a)
-> Decoder Identity x
-> i
-> Either (DecodeError, CursorHistory) x
pureDecodeWithInput forall (g :: * -> *).
Monad g =>
(forall a. f a -> i -> Either e a)
-> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x)
decodeRunner forall a. f a -> i -> Either e a
parseFn Decoder Identity x
decoder =
Identity (Either (DecodeError, CursorHistory) x)
-> Either (DecodeError, CursorHistory) x
forall a. Identity a -> a
runIdentity (Identity (Either (DecodeError, CursorHistory) x)
-> Either (DecodeError, CursorHistory) x)
-> (i -> Identity (Either (DecodeError, CursorHistory) x))
-> i
-> Either (DecodeError, CursorHistory) x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (forall a. f a -> i -> Either e a)
-> Decoder Identity x
-> i
-> Identity (Either (DecodeError, CursorHistory) x)
forall (g :: * -> *).
Monad g =>
(forall a. f a -> i -> Either e a)
-> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x)
decodeRunner forall a. f a -> i -> Either e a
parseFn Decoder Identity x
decoder
pureDecodeFromText
:: ( Monad f
, CharParsing f
, Show e
)
=> (forall a. f a -> Text -> Either e a)
-> Decoder Identity x
-> Text
-> Either (DecodeError, CursorHistory) x
pureDecodeFromText :: (forall a. f a -> Text -> Either e a)
-> Decoder Identity x
-> Text
-> Either (DecodeError, CursorHistory) x
pureDecodeFromText =
(forall (g :: * -> *).
Monad g =>
(forall a. f a -> Text -> Either e a)
-> Decoder g x
-> Text
-> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> Text -> Either e a)
-> Decoder Identity x
-> Text
-> Either (DecodeError, CursorHistory) x
forall (f :: * -> *) e i x.
(Monad f, CharParsing f, Show e) =>
(forall (g :: * -> *).
Monad g =>
(forall a. f a -> i -> Either e a)
-> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> i -> Either e a)
-> Decoder Identity x
-> i
-> Either (DecodeError, CursorHistory) x
pureDecodeWithInput forall (g :: * -> *).
Monad g =>
(forall a. f a -> Text -> Either e a)
-> Decoder g x -> Text -> g (Either (DecodeError, CursorHistory) x)
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)
decodeFromText
pureDecodeFromByteString
:: ( Monad f
, CharParsing f
, Show e
)
=> (forall a. f a -> ByteString -> Either e a)
-> Decoder Identity x
-> ByteString
-> Either (DecodeError, CursorHistory) x
pureDecodeFromByteString :: (forall a. f a -> ByteString -> Either e a)
-> Decoder Identity x
-> ByteString
-> Either (DecodeError, CursorHistory) x
pureDecodeFromByteString =
(forall (g :: * -> *).
Monad g =>
(forall a. f a -> ByteString -> Either e a)
-> Decoder g x
-> ByteString
-> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> ByteString -> Either e a)
-> Decoder Identity x
-> ByteString
-> Either (DecodeError, CursorHistory) x
forall (f :: * -> *) e i x.
(Monad f, CharParsing f, Show e) =>
(forall (g :: * -> *).
Monad g =>
(forall a. f a -> i -> Either e a)
-> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> i -> Either e a)
-> Decoder Identity x
-> i
-> Either (DecodeError, CursorHistory) x
pureDecodeWithInput forall (g :: * -> *).
Monad g =>
(forall a. f a -> ByteString -> Either e a)
-> Decoder g x
-> ByteString
-> g (Either (DecodeError, CursorHistory) x)
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)
decodeFromByteString
pureDecodeFromString
:: ( Monad f
, CharParsing f
, Show e
)
=> (forall a. f a -> String -> Either e a)
-> Decoder Identity x
-> String
-> Either (DecodeError, CursorHistory) x
pureDecodeFromString :: (forall a. f a -> String -> Either e a)
-> Decoder Identity x
-> String
-> Either (DecodeError, CursorHistory) x
pureDecodeFromString =
(forall (g :: * -> *).
Monad g =>
(forall a. f a -> String -> Either e a)
-> Decoder g x
-> String
-> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> String -> Either e a)
-> Decoder Identity x
-> String
-> Either (DecodeError, CursorHistory) x
forall (f :: * -> *) e i x.
(Monad f, CharParsing f, Show e) =>
(forall (g :: * -> *).
Monad g =>
(forall a. f a -> i -> Either e a)
-> Decoder g x -> i -> g (Either (DecodeError, CursorHistory) x))
-> (forall a. f a -> i -> Either e a)
-> Decoder Identity x
-> i
-> Either (DecodeError, CursorHistory) x
pureDecodeWithInput forall (g :: * -> *).
Monad g =>
(forall a. f a -> String -> Either e a)
-> Decoder g x
-> String
-> g (Either (DecodeError, CursorHistory) x)
forall (f :: * -> *) (g :: * -> *) e x.
(CharParsing f, Monad f, Monad g, Show e) =>
(forall a. f a -> String -> Either e a)
-> Decoder g x
-> String
-> g (Either (DecodeError, CursorHistory) x)
decodeFromString
parseWith
:: ( CharParsing f
, Show e
)
=> (f a -> i -> Either e a)
-> f a
-> i
-> Either DecodeError a
parseWith :: (f a -> i -> Either e a) -> f a -> i -> Either DecodeError a
parseWith f a -> i -> Either e a
f f a
p =
(e -> DecodeError) -> Either e a -> Either DecodeError a
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> DecodeError
ParseFailed (Text -> DecodeError) -> (e -> Text) -> e -> DecodeError
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Text
Text.pack (String -> Text) -> (e -> String) -> e -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. e -> String
forall a. Show a => a -> String
show) (Either e a -> Either DecodeError a)
-> (i -> Either e a) -> i -> Either DecodeError a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. f a -> i -> Either e a
f f a
p
overrideParser
:: ( CharParsing g
, Monad g
, Monad f
, Show e
)
=> (forall x. g x -> i -> Either e x)
-> (ByteString -> i)
-> g Json
-> DecodeResult f a
-> DecodeResult f a
overrideParser :: (forall x. g x -> i -> Either e x)
-> (ByteString -> i)
-> g Json
-> DecodeResult f a
-> DecodeResult f a
overrideParser forall x. g x -> i -> Either e x
newParseFn ByteString -> i
floop g Json
parser =
(ParseFn -> ParseFn) -> DecodeResult f a -> DecodeResult f a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (ParseFn -> ParseFn -> ParseFn
forall a b. a -> b -> a
const ((g Json -> i -> Either e Json)
-> g Json -> i -> Either DecodeError Json
forall (f :: * -> *) e a i.
(CharParsing f, Show e) =>
(f a -> i -> Either e a) -> f a -> i -> Either DecodeError a
parseWith g Json -> i -> Either e Json
forall x. g x -> i -> Either e x
newParseFn g Json
parser (i -> Either DecodeError Json) -> (ByteString -> i) -> ParseFn
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> i
floop))