{-# 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 parserFn toI fromI decode = DI.runDecoderResultT
. runDecoder decode (parseWith parserFn parseWaargonaut . toI)
. mkCursor
. 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 parseFn = decodeWithInput parseFn
(Text.unpack . Text.decodeUtf8)
(Text.encodeUtf8 . 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 parseFn =
decodeWithInput parseFn id 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 parseFn =
decodeWithInput parseFn Text.decodeUtf8 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 decodeRunner parseFn decoder =
runIdentity . decodeRunner parseFn 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 =
pureDecodeWithInput 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 =
pureDecodeWithInput 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 =
pureDecodeWithInput decodeFromString
parseWith
:: ( CharParsing f
, Show e
)
=> (f a -> i -> Either e a)
-> f a
-> i
-> Either DecodeError a
parseWith f p =
first (ParseFailed . Text.pack . show) . f 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 newParseFn floop parser =
local (const (parseWith newParseFn parser . floop))