{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Hasql.Interpolate.Internal.Json
( Json (..),
Jsonb (..),
AsJson (..),
AsJsonb (..),
)
where
import Data.Aeson
import qualified Data.Aeson as Aeson
import Data.Bifunctor (first)
import qualified Data.ByteString.Lazy as BL
import Data.Coerce
import Data.Functor.Contravariant
import qualified Data.Text as T
import qualified Hasql.Decoders as D
import qualified Hasql.Encoders as E
import Hasql.Interpolate.Internal.Decoder
import Hasql.Interpolate.Internal.Encoder
newtype Jsonb = Jsonb Value
newtype Json = Json Value
newtype AsJson a = AsJson a
newtype AsJsonb a = AsJsonb a
instance DecodeValue Jsonb where
decodeValue :: Value Jsonb
decodeValue = coerce :: forall a b. Coercible a b => a -> b
coerce Value Value
D.jsonb
instance DecodeValue Json where
decodeValue :: Value Json
decodeValue = coerce :: forall a b. Coercible a b => a -> b
coerce Value Value
D.json
instance Aeson.FromJSON a => DecodeValue (AsJson a) where
decodeValue :: Value (AsJson a)
decodeValue = forall a. a -> AsJson a
AsJson forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. (ByteString -> Either Text a) -> Value a
D.jsonBytes (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict)
instance Aeson.FromJSON a => DecodeValue (AsJsonb a) where
decodeValue :: Value (AsJsonb a)
decodeValue = forall a. a -> AsJsonb a
AsJsonb forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. (ByteString -> Either Text a) -> Value a
D.jsonbBytes (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict)
instance EncodeValue Json where
encodeValue :: Value Json
encodeValue = coerce :: forall a b. Coercible a b => a -> b
coerce Value Value
E.json
instance EncodeValue Jsonb where
encodeValue :: Value Jsonb
encodeValue = coerce :: forall a b. Coercible a b => a -> b
coerce Value Value
E.jsonb
instance Aeson.ToJSON a => EncodeValue (AsJson a) where
encodeValue :: Value (AsJson a)
encodeValue = ByteString -> ByteString
BL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
Aeson.encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. coerce :: forall a b. Coercible a b => a -> b
coerce @_ @a forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
>$< Value ByteString
E.jsonBytes
instance Aeson.ToJSON a => EncodeValue (AsJsonb a) where
encodeValue :: Value (AsJsonb a)
encodeValue = ByteString -> ByteString
BL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
Aeson.encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. coerce :: forall a b. Coercible a b => a -> b
coerce @_ @a forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
>$< Value ByteString
E.jsonbBytes