{-# options_haddock prune #-}
module Polysemy.Http.Interpreter.AesonEntity where
import Data.Aeson (eitherDecode', eitherDecodeStrict', encode)
import Polysemy.Http.Effect.Entity (EntityDecode, EntityEncode, EntityError (EntityError))
import qualified Polysemy.Http.Effect.Entity as Entity (EntityDecode (..), EntityEncode (..))
interpretEntityEncodeAesonAs ::
ToJSON j =>
(d -> j) ->
Sem (EntityEncode d : r) a ->
Sem r a
interpretEntityEncodeAesonAs :: (d -> j) -> Sem (EntityEncode d : r) a -> Sem r a
interpretEntityEncodeAesonAs d -> j
convert =
(forall (rInitial :: EffectRow) x.
EntityEncode d (Sem rInitial) x -> Sem r x)
-> Sem (EntityEncode d : r) a -> Sem r a
forall (e :: (* -> *) -> * -> *) (r :: EffectRow) a.
FirstOrder e "interpret" =>
(forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x)
-> Sem (e : r) a -> Sem r a
interpret \case
Entity.Encode a ->
ByteString -> Sem r ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (j -> ByteString
forall a. ToJSON a => a -> ByteString
encode (d -> j
convert d
a))
Entity.EncodeStrict a ->
x -> Sem r x
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> x
forall l s. LazyStrict l s => l -> s
toStrict (j -> ByteString
forall a. ToJSON a => a -> ByteString
encode (d -> j
convert d
a)))
{-# inline interpretEntityEncodeAesonAs #-}
interpretEntityEncodeAeson ::
ToJSON d =>
Sem (EntityEncode d : r) a ->
Sem r a
interpretEntityEncodeAeson :: Sem (EntityEncode d : r) a -> Sem r a
interpretEntityEncodeAeson =
(d -> d) -> Sem (EntityEncode d : r) a -> Sem r a
forall j d (r :: EffectRow) a.
ToJSON j =>
(d -> j) -> Sem (EntityEncode d : r) a -> Sem r a
interpretEntityEncodeAesonAs d -> d
forall a. a -> a
id
{-# inline interpretEntityEncodeAeson #-}
decodeWith ::
ConvertUtf8 Text s =>
(s -> Either String a) ->
s ->
Sem r (Either EntityError a)
decodeWith :: (s -> Either String a) -> s -> Sem r (Either EntityError a)
decodeWith s -> Either String a
dec s
body =
Either EntityError a -> Sem r (Either EntityError a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either EntityError a -> Sem r (Either EntityError a))
-> (Either String a -> Either EntityError a)
-> Either String a
-> Sem r (Either EntityError a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> EntityError) -> Either String a -> Either EntityError a
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft (Text -> Text -> EntityError
EntityError (s -> Text
forall a b. ConvertUtf8 a b => b -> a
decodeUtf8 s
body) (Text -> EntityError) -> (String -> Text) -> String -> EntityError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. ToText a => a -> Text
toText) (Either String a -> Sem r (Either EntityError a))
-> Either String a -> Sem r (Either EntityError a)
forall a b. (a -> b) -> a -> b
$ s -> Either String a
dec s
body
{-# inline decodeWith #-}
interpretEntityDecodeAesonAs ::
FromJSON j =>
(j -> d) ->
Sem (EntityDecode d : r) a ->
Sem r a
interpretEntityDecodeAesonAs :: (j -> d) -> Sem (EntityDecode d : r) a -> Sem r a
interpretEntityDecodeAesonAs j -> d
convert =
(forall (rInitial :: EffectRow) x.
EntityDecode d (Sem rInitial) x -> Sem r x)
-> Sem (EntityDecode d : r) a -> Sem r a
forall (e :: (* -> *) -> * -> *) (r :: EffectRow) a.
FirstOrder e "interpret" =>
(forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x)
-> Sem (e : r) a -> Sem r a
interpret \case
Entity.Decode body ->
(j -> d) -> Either EntityError j -> Either EntityError d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap j -> d
convert (Either EntityError j -> Either EntityError d)
-> Sem r (Either EntityError j) -> Sem r (Either EntityError d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ByteString -> Either String j)
-> ByteString -> Sem r (Either EntityError j)
forall s a (r :: EffectRow).
ConvertUtf8 Text s =>
(s -> Either String a) -> s -> Sem r (Either EntityError a)
decodeWith ByteString -> Either String j
forall a. FromJSON a => ByteString -> Either String a
eitherDecode' ByteString
body
Entity.DecodeStrict body ->
(j -> d) -> Either EntityError j -> Either EntityError d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap j -> d
convert (Either EntityError j -> Either EntityError d)
-> Sem r (Either EntityError j) -> Sem r (Either EntityError d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ByteString -> Either String j)
-> ByteString -> Sem r (Either EntityError j)
forall s a (r :: EffectRow).
ConvertUtf8 Text s =>
(s -> Either String a) -> s -> Sem r (Either EntityError a)
decodeWith ByteString -> Either String j
forall a. FromJSON a => ByteString -> Either String a
eitherDecodeStrict' ByteString
body
{-# inline interpretEntityDecodeAesonAs #-}
interpretEntityDecodeAeson ::
FromJSON d =>
Sem (EntityDecode d : r) a ->
Sem r a
interpretEntityDecodeAeson :: Sem (EntityDecode d : r) a -> Sem r a
interpretEntityDecodeAeson =
(d -> d) -> Sem (EntityDecode d : r) a -> Sem r a
forall j d (r :: EffectRow) a.
FromJSON j =>
(j -> d) -> Sem (EntityDecode d : r) a -> Sem r a
interpretEntityDecodeAesonAs d -> d
forall a. a -> a
id
{-# inline interpretEntityDecodeAeson #-}