{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module ByteString.Aeson.Orphans where import Data.Aeson import Data.ByteString (ByteString) import qualified Data.ByteString.Base64 as B64 import qualified Data.ByteString.Lazy as LBS import Data.Text.Encoding (decodeUtf8, encodeUtf8) instance ToJSON ByteString where toJSON :: ByteString -> Value toJSON = Text -> Value forall a. ToJSON a => a -> Value toJSON (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Text decodeUtf8 (ByteString -> Text) -> (ByteString -> ByteString) -> ByteString -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString B64.encode instance FromJSON ByteString where parseJSON :: Value -> Parser ByteString parseJSON Value o = (String -> Parser ByteString) -> (ByteString -> Parser ByteString) -> Either String ByteString -> Parser ByteString forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either String -> Parser ByteString forall a. String -> Parser a forall (m :: * -> *) a. MonadFail m => String -> m a fail ByteString -> Parser ByteString forall a. a -> Parser a forall (m :: * -> *) a. Monad m => a -> m a return (Either String ByteString -> Parser ByteString) -> (Text -> Either String ByteString) -> Text -> Parser ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Either String ByteString B64.decode (ByteString -> Either String ByteString) -> (Text -> ByteString) -> Text -> Either String ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> ByteString encodeUtf8 (Text -> Parser ByteString) -> Parser Text -> Parser ByteString forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< Value -> Parser Text forall a. FromJSON a => Value -> Parser a parseJSON Value o instance ToJSON LBS.ByteString where toJSON :: ByteString -> Value toJSON = Text -> Value forall a. ToJSON a => a -> Value toJSON (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Text decodeUtf8 (ByteString -> Text) -> (ByteString -> ByteString) -> ByteString -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString B64.encode (ByteString -> ByteString) -> (ByteString -> ByteString) -> ByteString -> ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString LBS.toStrict instance FromJSON LBS.ByteString where parseJSON :: Value -> Parser ByteString parseJSON Value o = (String -> Parser ByteString) -> (ByteString -> Parser ByteString) -> Either String ByteString -> Parser ByteString forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either String -> Parser ByteString forall a. String -> Parser a forall (m :: * -> *) a. MonadFail m => String -> m a fail (ByteString -> Parser ByteString forall a. a -> Parser a forall (m :: * -> *) a. Monad m => a -> m a return (ByteString -> Parser ByteString) -> (ByteString -> ByteString) -> ByteString -> Parser ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString LBS.fromStrict) (Either String ByteString -> Parser ByteString) -> (Text -> Either String ByteString) -> Text -> Parser ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Either String ByteString B64.decode (ByteString -> Either String ByteString) -> (Text -> ByteString) -> Text -> Either String ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> ByteString encodeUtf8 (Text -> Parser ByteString) -> Parser Text -> Parser ByteString forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< Value -> Parser Text forall a. FromJSON a => Value -> Parser a parseJSON Value o instance ToJSONKey ByteString instance FromJSONKey ByteString