{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}

-- Ported from https://github.com/awakesecurity/proto3-suite (Apache v2 License)
-- and modified to work with proto-lens.
--
-- | Support for the "JSONPB" canonical JSON encoding described at
-- https://developers.google.com/protocol-buffers/docs/proto3#json.
--
-- This modules provides 'Data.Aeson'-like helper functions, typeclasses, and
-- instances for converting to and from values of types which have a JSONPB
-- representation and equivalent underlying 'Data.Aeson' representations.
--
-- This module also presents a (very minimal) surface syntax for Aeson-like
-- operations; the idea is that we can write 'ToJSONPB' and 'FromJSONPB'
-- instances in a very similar manner to 'A.ToJSON' and 'A.FromJSON' instances,
-- except that doing so specifies JSONPB codecs instead of vanilla JSON codecs.
--
-- Example use:
--
-- @
-- message Scalar32 {
--   int32     i32 = 1;
--   uint32    u32 = 2;
--   sint32    s32 = 3;
--   fixed32   f32 = 4;
--   sfixed32 sf32 = 5;
-- }
--
-- instance ToJSONPB Scalar32 where
--   toJSONPB (Scalar32 i32 u32 s32 f32 sf32) = object
--       [ "i32"  .= i32
--       , "u32"  .= u32
--       , "s32"  .= s32
--       , "f32"  .= f32
--       , "sf32" .= sf32
--       ]
--   toEncodingPB (Scalar32 i32 u32 s32 f32 sf32) = pairs
--       [ "i32"  .= i32
--       , "u32"  .= u32
--       , "s32"  .= s32
--       , "f32"  .= f32
--       , "sf32" .= sf32
--       ]
--
-- instance FromJSONPB Scalar32 where
--   parseJSONPB = withObject "Scalar32" $ \obj ->
--     pure Scalar32
--     <*> obj .: "i32"
--     <*> obj .: "u32"
--     <*> obj .: "s32"
--     <*> obj .: "f32"
--     <*> obj .: "sf32"
-- @
module Data.ProtoLens.JSONPB.Class where

import qualified Data.Aeson as A (Encoding, FromJSON(..), FromJSONKey(..), FromJSONKeyFunction(..), ToJSON(..), Value(..), eitherDecode, json, (.!=))

import qualified Data.Aeson.Encoding as E
import qualified Data.Aeson.Internal as A (formatError, iparse)
import qualified Data.Aeson.Parser as A (eitherDecodeWith)
import qualified Data.Aeson.Types as A (Object, Pair, Parser, Series, explicitParseField, explicitParseFieldMaybe, object, typeMismatch)
import qualified Data.Attoparsec.ByteString as Atto (skipWhile)
import qualified Data.Attoparsec.ByteString.Char8 as Atto (Parser, endOfInput)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Lazy as LBS
import           Data.ProtoLens.Runtime.Data.ProtoLens (FieldDefault(..))
import           Data.String (fromString)
import           Data.Text (Text, unpack)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Vector as V
import           GHC.Int (Int32, Int64)
import           GHC.Word (Word32, Word64)


-- * Typeclass definitions

-- | 'A.ToJSON' variant for JSONPB direct encoding via 'A.Encoding'
class ToJSONPB a where
  -- | 'A.toJSON' variant for JSONPB encoders.
  toJSONPB :: a -> Options -> A.Value
  -- | 'A.toEncoding' variant for JSONPB encoders. If an implementation is not
  -- provided, uses 'toJSONPB' (which is less efficient since it indirects
  -- through the 'A.Value' IR).
  toEncodingPB :: a -> Options -> A.Encoding
  toEncodingPB a
x = Value -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding (Value -> Encoding) -> (Options -> Value) -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB a
x

-- | 'A.FromJSON' variant for JSONPB decoding from the 'A.Value' IR
class FromJSONPB a where
  -- | 'A.parseJSON' variant for JSONPB decoders.
  parseJSONPB :: A.Value -> A.Parser a

-- * JSONPB codec entry points

-- | 'Data.Aeson.encode' variant for serializing a JSONPB value as a lazy
-- 'LBS.ByteString'.
encode :: ToJSONPB a => Options -> a -> LBS.ByteString
encode :: forall a. ToJSONPB a => Options -> a -> ByteString
encode Options
opts a
x = Encoding -> ByteString
forall a. Encoding' a -> ByteString
E.encodingToLazyByteString (a -> Options -> Encoding
forall a. ToJSONPB a => a -> Options -> Encoding
toEncodingPB a
x Options
opts)

{-# INLINE encode #-}
-- | 'Data.Aeson.eitherDecode' variant for deserializing a JSONPB value from a
-- lazy 'LBS.ByteString'.
eitherDecode :: FromJSONPB a => LBS.ByteString -> Either String a
eitherDecode :: forall a. FromJSONPB a => ByteString -> Either [Char] a
eitherDecode =
  Either (JSONPath, [Char]) a -> Either [Char] a
forall {b}. Either (JSONPath, [Char]) b -> Either [Char] b
eitherFormatError (Either (JSONPath, [Char]) a -> Either [Char] a)
-> (ByteString -> Either (JSONPath, [Char]) a)
-> ByteString
-> Either [Char] a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser Value
-> (Value -> IResult a)
-> ByteString
-> Either (JSONPath, [Char]) a
forall a.
Parser Value
-> (Value -> IResult a)
-> ByteString
-> Either (JSONPath, [Char]) a
A.eitherDecodeWith Parser Value
jsonEOF ((Value -> Parser a) -> Value -> IResult a
forall a b. (a -> Parser b) -> a -> IResult b
A.iparse Value -> Parser a
forall a. FromJSONPB a => Value -> Parser a
parseJSONPB)
  where
    eitherFormatError :: Either (JSONPath, [Char]) b -> Either [Char] b
eitherFormatError = ((JSONPath, [Char]) -> Either [Char] b)
-> (b -> Either [Char] b)
-> Either (JSONPath, [Char]) b
-> Either [Char] b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Either [Char] b
forall a b. a -> Either a b
Left ([Char] -> Either [Char] b)
-> ((JSONPath, [Char]) -> [Char])
-> (JSONPath, [Char])
-> Either [Char] b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (JSONPath -> [Char] -> [Char]) -> (JSONPath, [Char]) -> [Char]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry JSONPath -> [Char] -> [Char]
A.formatError) b -> Either [Char] b
forall a b. b -> Either a b
Right
    {-# INLINE eitherFormatError #-}
    -- NB: cribbed from aeson-1.1.1.0:Data.Aeson.Parser.Internal.jsonEOF, which
    -- is not exported. It's simple, so we just inline it here. Might be worth
    -- submitting a PR to export this.
    jsonEOF :: Atto.Parser A.Value
    jsonEOF :: Parser Value
jsonEOF = Parser Value
A.json Parser Value -> Parser ByteString () -> Parser Value
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString ()
skipSpace Parser Value -> Parser ByteString () -> Parser Value
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString ()
forall t. Chunk t => Parser t ()
Atto.endOfInput
      where
        skipSpace :: Atto.Parser ()
        skipSpace :: Parser ByteString ()
skipSpace =
          (Word8 -> Bool) -> Parser ByteString ()
Atto.skipWhile ((Word8 -> Bool) -> Parser ByteString ())
-> (Word8 -> Bool) -> Parser ByteString ()
forall a b. (a -> b) -> a -> b
$ \Word8
w ->
            Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x20 Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x0a Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x0d Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x09
        {-# INLINE skipSpace #-}

{-# INLINE eitherDecode #-}
-- * Operator definitions
-- | JSONPB-encoded monoidal key-value pairs
class Monoid m =>
      KeyValuePB m
  where
  pair :: ToJSONPB v => Text -> v -> Options -> m

instance KeyValuePB A.Series where
  pair :: forall v. ToJSONPB v => Text -> v -> Options -> Series
pair Text
k v
v Options
opts = Key -> Encoding -> Series
E.pair ([Char] -> Key
forall a. IsString a => [Char] -> a
fromString (Text -> [Char]
unpack Text
k)) (v -> Options -> Encoding
forall a. ToJSONPB a => a -> Options -> Encoding
toEncodingPB v
v Options
opts)

instance KeyValuePB [A.Pair] where
  pair :: forall v. ToJSONPB v => Text -> v -> Options -> [Pair]
pair Text
k v
v Options
opts = Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> Key
forall a. IsString a => [Char] -> a
fromString (Text -> [Char]
unpack Text
k), v -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB v
v Options
opts)

-- | Construct a monoidal key-value pair, using 'mempty' to represent omission
-- of default values (unless the given 'Options' force their emission).
(.=) ::
     (ToJSONPB v, KeyValuePB kvp, FieldDefault v, Eq v) => Text -> v -> Options -> kvp
Text
k .= :: forall v kvp.
(ToJSONPB v, KeyValuePB kvp, FieldDefault v, Eq v) =>
Text -> v -> Options -> kvp
.= v
v = Options -> kvp
forall {a}. KeyValuePB a => Options -> a
mk
  where
    mk :: Options -> a
mk opts :: Options
opts@Options {Bool
optEmitDefaultValuedFields :: Bool
optEmitDefaultValuedFields :: Options -> Bool
..} -- = pair k v opts
      | Bool -> Bool
not Bool
optEmitDefaultValuedFields Bool -> Bool -> Bool
&& v
forall value. FieldDefault value => value
fieldDefault v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
v = a
forall a. Monoid a => a
mempty
      | Bool
otherwise = Text -> v -> Options -> a
forall m v. (KeyValuePB m, ToJSONPB v) => Text -> v -> Options -> m
forall v. ToJSONPB v => Text -> v -> Options -> a
pair Text
k v
v Options
opts

-- | 'Data.Aeson..:' variant for JSONPB; if the given key is missing from the
-- object, or if it is present but its value is null, we produce the default
-- protobuf value for the field type
(.:) :: (FromJSONPB a, FieldDefault a) => A.Object -> Text -> A.Parser a
Object
obj .: :: forall a.
(FromJSONPB a, FieldDefault a) =>
Object -> Text -> Parser a
.: Text
key = Object
obj Object -> Key -> Parser (Maybe a)
.:? [Char] -> Key
forall a. IsString a => [Char] -> a
fromString (Text -> [Char]
unpack Text
key) Parser (Maybe a) -> a -> Parser a
forall a. Parser (Maybe a) -> a -> Parser a
A..!= a
forall value. FieldDefault value => value
fieldDefault
  where
    .:? :: Object -> Key -> Parser (Maybe a)
(.:?) = (Value -> Parser a) -> Object -> Key -> Parser (Maybe a)
forall a. (Value -> Parser a) -> Object -> Key -> Parser (Maybe a)
A.explicitParseFieldMaybe Value -> Parser a
forall a. FromJSONPB a => Value -> Parser a
parseJSONPB

parseField :: FromJSONPB a => A.Object -> Text -> A.Parser a
parseField :: forall a. FromJSONPB a => Object -> Text -> Parser a
parseField Object
o = (Value -> Parser a) -> Object -> Key -> Parser a
forall a. (Value -> Parser a) -> Object -> Key -> Parser a
A.explicitParseField Value -> Parser a
forall a. FromJSONPB a => Value -> Parser a
parseJSONPB Object
o (Key -> Parser a) -> (Text -> Key) -> Text -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Key
forall a. IsString a => [Char] -> a
fromString ([Char] -> Key) -> (Text -> [Char]) -> Text -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
unpack

-- * JSONPB rendering and parsing options
data Options =
  Options
    { Options -> Bool
optEmitDefaultValuedFields :: Bool
    }
  deriving (Int -> Options -> [Char] -> [Char]
[Options] -> [Char] -> [Char]
Options -> [Char]
(Int -> Options -> [Char] -> [Char])
-> (Options -> [Char])
-> ([Options] -> [Char] -> [Char])
-> Show Options
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Options -> [Char] -> [Char]
showsPrec :: Int -> Options -> [Char] -> [Char]
$cshow :: Options -> [Char]
show :: Options -> [Char]
$cshowList :: [Options] -> [Char] -> [Char]
showList :: [Options] -> [Char] -> [Char]
Show)

-- | Default options for JSONPB encoding. By default, all options are @False@.
defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Options {optEmitDefaultValuedFields :: Bool
optEmitDefaultValuedFields = Bool
False}

-- * Helper types and functions
-- dropNamedPrefix :: Named a => Proxy a -> String -> String
-- dropNamedPrefix p = drop (length (nameOf p :: String))

object :: [Options -> [A.Pair]] -> Options -> A.Value
object :: [Options -> [Pair]] -> Options -> Value
object [Options -> [Pair]]
fs = [Pair] -> Value
A.object ([Pair] -> Value) -> (Options -> [Pair]) -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Options -> [Pair]] -> Options -> [Pair]
forall a. Monoid a => [a] -> a
mconcat [Options -> [Pair]]
fs

pairs :: [Options -> A.Series] -> Options -> E.Encoding
pairs :: [Options -> Series] -> Options -> Encoding
pairs [Options -> Series]
fs = Series -> Encoding
E.pairs (Series -> Encoding) -> (Options -> Series) -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Options -> Series] -> Options -> Series
forall a. Monoid a => [a] -> a
mconcat [Options -> Series]
fs

-- enumFieldString ::
--      forall a. (Named a, Show a)
--   => a
--   -> A.Value
-- enumFieldString = A.String . T.pack . dropNamedPrefix (Proxy @a) . show

-- enumFieldEncoding ::
--      forall a. (Named a, Show a)
--   => a
--   -> A.Encoding
-- enumFieldEncoding = E.string . dropNamedPrefix (Proxy @a) . show

-- | A 'Data.Aeson' 'A.Value' encoder for values which can be
-- JSONPB-encoded
toAesonValue :: ToJSONPB a => a -> A.Value
toAesonValue :: forall a. ToJSONPB a => a -> Value
toAesonValue = (a -> Options -> Value) -> Options -> a -> Value
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB Options
defaultOptions

-- | A direct 'A.Encoding' for values which can be JSONPB-encoded
toAesonEncoding :: ToJSONPB a => a -> A.Encoding
toAesonEncoding :: forall a. ToJSONPB a => a -> Encoding
toAesonEncoding = (a -> Options -> Encoding) -> Options -> a -> Encoding
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Options -> Encoding
forall a. ToJSONPB a => a -> Options -> Encoding
toEncodingPB Options
defaultOptions

-- | Parse a JSONPB floating point value; first parameter provides context for
-- type mismatches
parseFP :: (A.FromJSON a, A.FromJSONKey a) => String -> A.Value -> A.Parser a
parseFP :: forall a.
(FromJSON a, FromJSONKey a) =>
[Char] -> Value -> Parser a
parseFP [Char]
tyDesc Value
v =
  case Value
v of
    A.Number {} -> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
A.parseJSON Value
v
    A.String Text
t ->
      case FromJSONKeyFunction a
forall a. FromJSONKey a => FromJSONKeyFunction a
A.fromJSONKey of
        A.FromJSONKeyTextParser Text -> Parser a
p -> Text -> Parser a
p Text
t
        FromJSONKeyFunction a
_                         -> [Char] -> Parser a
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"internal: parseKeyPB: unexpected FromJSONKey summand"
    Value
_ -> [Char] -> Value -> Parser a
forall a. [Char] -> Value -> Parser a
A.typeMismatch [Char]
tyDesc Value
v

-- | Liberally parse an integer value (e.g. 42 or "42" as 42); first parameter
-- provides context for type mismatches
parseNumOrDecimalString :: (A.FromJSON a) => String -> A.Value -> A.Parser a
parseNumOrDecimalString :: forall a. FromJSON a => [Char] -> Value -> Parser a
parseNumOrDecimalString [Char]
tyDesc Value
v =
  case Value
v of
    A.Number {} -> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
A.parseJSON Value
v
    A.String Text
t ->
      ([Char] -> Parser a)
-> (a -> Parser a) -> Either [Char] a -> Parser a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either [Char] -> Parser a
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail a -> Parser a
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either [Char] a -> Parser a)
-> (Text -> Either [Char] a) -> Text -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either [Char] a
forall a. FromJSON a => ByteString -> Either [Char] a
A.eitherDecode (ByteString -> Either [Char] a)
-> (Text -> ByteString) -> Text -> Either [Char] a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8 (Text -> ByteString) -> (Text -> Text) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.fromStrict (Text -> Parser a) -> Text -> Parser a
forall a b. (a -> b) -> a -> b
$ Text
t
    Value
_ -> [Char] -> Value -> Parser a
forall a. [Char] -> Value -> Parser a
A.typeMismatch [Char]
tyDesc Value
v

-- * Common instances for jsonpb codec implementations
-- ** Instances for scalar types
--------------------------------------------------------------------------------
-- Boolean scalar type
instance ToJSONPB Bool where
  toJSONPB :: Bool -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Bool -> Value) -> Bool -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Bool -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Bool -> Encoding) -> Bool -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB Bool where
  parseJSONPB :: Value -> Parser Bool
parseJSONPB = Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
A.parseJSON

--------------------------------------------------------------------------------
-- Integer scalar types
--
--   * 32 bit integer values render to JSON decimal numbers; either numbers or
--     strings are accepted.
--
--   * 64 bit integer values render to JSON decimal strings; either numbers
--     or strings are accepted.
--
-- int32 / sint32
instance ToJSONPB Int32 where
  toJSONPB :: Int32 -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Int32 -> Value) -> Int32 -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Int32 -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Int32 -> Encoding) -> Int32 -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB Int32 where
  parseJSONPB :: Value -> Parser Int32
parseJSONPB = [Char] -> Value -> Parser Int32
forall a. FromJSON a => [Char] -> Value -> Parser a
parseNumOrDecimalString [Char]
"int32 / sint32"

-- uint32
instance ToJSONPB Word32 where
  toJSONPB :: Word32 -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Word32 -> Value) -> Word32 -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Word32 -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Word32 -> Encoding) -> Word32 -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB Word32 where
  parseJSONPB :: Value -> Parser Word32
parseJSONPB = [Char] -> Value -> Parser Word32
forall a. FromJSON a => [Char] -> Value -> Parser a
parseNumOrDecimalString [Char]
"uint32"

-- int64 / sint64
instance ToJSONPB Int64 where
  toJSONPB :: Int64 -> Options -> Value
toJSONPB Int64
x Options
_ = Text -> Value
A.String (Text -> Value) -> (Int64 -> Text) -> Int64 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text) -> (Int64 -> [Char]) -> Int64 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> [Char]
forall a. Show a => a -> [Char]
show (Int64 -> Value) -> Int64 -> Value
forall a b. (a -> b) -> a -> b
$ Int64
x
  toEncodingPB :: Int64 -> Options -> Encoding
toEncodingPB Int64
x Options
_ = [Char] -> Encoding
forall a. [Char] -> Encoding' a
E.string (Int64 -> [Char]
forall a. Show a => a -> [Char]
show Int64
x)

instance FromJSONPB Int64 where
  parseJSONPB :: Value -> Parser Int64
parseJSONPB = [Char] -> Value -> Parser Int64
forall a. FromJSON a => [Char] -> Value -> Parser a
parseNumOrDecimalString [Char]
"int64 / sint64"

-- unit64
instance ToJSONPB Word64 where
  toJSONPB :: Word64 -> Options -> Value
toJSONPB Word64
x Options
_ = Text -> Value
A.String (Text -> Value) -> (Word64 -> Text) -> Word64 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text) -> (Word64 -> [Char]) -> Word64 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> [Char]
forall a. Show a => a -> [Char]
show (Word64 -> Value) -> Word64 -> Value
forall a b. (a -> b) -> a -> b
$ Word64
x
  toEncodingPB :: Word64 -> Options -> Encoding
toEncodingPB Word64
x Options
_ = [Char] -> Encoding
forall a. [Char] -> Encoding' a
E.string (Word64 -> [Char]
forall a. Show a => a -> [Char]
show Word64
x)

instance FromJSONPB Word64 where
  parseJSONPB :: Value -> Parser Word64
parseJSONPB = [Char] -> Value -> Parser Word64
forall a. FromJSON a => [Char] -> Value -> Parser a
parseNumOrDecimalString [Char]
"int64 / sint64"

-- -- fixed32
-- instance ToJSONPB (Fixed Word32) where
--   toJSONPB = coerce (toJSONPB @Word32)
--   toEncodingPB = coerce (toEncodingPB @Word32)

-- instance FromJSONPB (Fixed Word32) where
--   parseJSONPB = coerce (parseJSONPB @Word32)

-- -- fixed64
-- instance ToJSONPB (Fixed Word64) where
--   toJSONPB = coerce (toJSONPB @Word64)
--   toEncodingPB = coerce (toEncodingPB @Word64)

-- instance FromJSONPB (Fixed Word64) where
--   parseJSONPB = coerce (parseJSONPB @Word64)

-- -- sfixed32
-- instance ToJSONPB (Fixed Int32) where
--   toJSONPB = coerce (toJSONPB @Int32)
--   toEncodingPB = coerce (toEncodingPB @Int32)

-- instance FromJSONPB (Fixed Int32) where
--   parseJSONPB = coerce (parseJSONPB @Int32)

-- -- sfixed64
-- instance ToJSONPB (Fixed Int64) where
--   toJSONPB = coerce (toJSONPB @Int64)
--   toEncodingPB = coerce (toEncodingPB @Int64)

-- instance FromJSONPB (Fixed Int64) where
--   parseJSONPB = coerce (parseJSONPB @Int64)

--------------------------------------------------------------------------------
-- Floating point scalar types
--
-- JSON value will be a number or one of the special string values "NaN",
-- "Infinity", and "-Infinity". Either numbers or strings are accepted. Exponent
-- notation is also accepted.
-- float
instance ToJSONPB Float where
  toJSONPB :: Float -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Float -> Value) -> Float -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Float -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Float -> Encoding) -> Float -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB Float where
  parseJSONPB :: Value -> Parser Float
parseJSONPB = [Char] -> Value -> Parser Float
forall a.
(FromJSON a, FromJSONKey a) =>
[Char] -> Value -> Parser a
parseFP [Char]
"float"

-- double
instance ToJSONPB Double where
  toJSONPB :: Double -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Double -> Value) -> Double -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Double -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Double -> Encoding) -> Double -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB Double where
  parseJSONPB :: Value -> Parser Double
parseJSONPB = [Char] -> Value -> Parser Double
forall a.
(FromJSON a, FromJSONKey a) =>
[Char] -> Value -> Parser a
parseFP [Char]
"double"

--------------------------------------------------------------------------------
-- Stringly types (string and bytes)
-- string
instance ToJSONPB TL.Text where
  toJSONPB :: Text -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Text -> Value) -> Text -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Text -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Text -> Encoding) -> Text -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB TL.Text where
  parseJSONPB :: Value -> Parser Text
parseJSONPB = Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
A.parseJSON

instance ToJSONPB T.Text where
  toJSONPB :: Text -> Options -> Value
toJSONPB = Value -> Options -> Value
forall a b. a -> b -> a
const (Value -> Options -> Value)
-> (Text -> Value) -> Text -> Options -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON
  toEncodingPB :: Text -> Options -> Encoding
toEncodingPB = Encoding -> Options -> Encoding
forall a b. a -> b -> a
const (Encoding -> Options -> Encoding)
-> (Text -> Encoding) -> Text -> Options -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding

instance FromJSONPB T.Text where
  parseJSONPB :: Value -> Parser Text
parseJSONPB = Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
A.parseJSON

-- bytes
bsToJSONPB :: BS.ByteString -> A.Value
bsToJSONPB :: ByteString -> Value
bsToJSONPB (ByteString -> Either UnicodeException Text
T.decodeUtf8' (ByteString -> Either UnicodeException Text)
-> (ByteString -> ByteString)
-> ByteString
-> Either UnicodeException Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64.encode -> Either UnicodeException Text
ebs) =
  case Either UnicodeException Text
ebs of
    Right Text
bs -> Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON Text
bs
    Left UnicodeException
e ->
      [Char] -> Value
forall a. HasCallStack => [Char] -> a
error ([Char]
"internal: failed to encode B64-encoded bytestring: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ UnicodeException -> [Char]
forall a. Show a => a -> [Char]
show UnicodeException
e)
              -- NB: T.decodeUtf8' should never fail because we B64-encode the
              -- incoming bytestring.

instance ToJSONPB BS.ByteString where
  toJSONPB :: ByteString -> Options -> Value
toJSONPB ByteString
bs Options
_ = ByteString -> Value
bsToJSONPB ByteString
bs
  toEncodingPB :: ByteString -> Options -> Encoding
toEncodingPB ByteString
bs Options
opts = Value -> Encoding
E.value (ByteString -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB ByteString
bs Options
opts)

instance FromJSONPB BS.ByteString where
  parseJSONPB :: Value -> Parser ByteString
parseJSONPB (A.String Text
b64enc) =
    ByteString -> Parser ByteString
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Parser ByteString)
-> (Text -> ByteString) -> Text -> Parser ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64.decodeLenient (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8 (Text -> Parser ByteString) -> Text -> Parser ByteString
forall a b. (a -> b) -> a -> b
$ Text
b64enc
  parseJSONPB Value
v = [Char] -> Value -> Parser ByteString
forall a. [Char] -> Value -> Parser a
A.typeMismatch [Char]
"bytes" Value
v

-- --------------------------------------------------------------------------------
-- -- Enumerated types
-- enumToJSONPB ::
--      (e -> Options -> a) -- ^ JSONPB encoder function to use
--   -> a -- ^ null value to use for out-of-range enums
--   -> Enumerated e -- ^ the enumerated value to encode
--   -> Options -- ^ JSONPB encoding options
--   -> a -- ^ the JSONPB-encoded value
-- enumToJSONPB enc null_ (Enumerated e) opts =
--   either err (\input -> enc input opts) e
--   where
--     err 0 = error "enumToJSONPB: The first enum value must be zero in proto3"
--             -- TODO: Raise a compilation error when the first enum value in an
--             -- enumeration is not zero.
--             --
--             -- See https://github.com/awakesecurity/proto3-suite/issues/28
--             --
--             -- The proto3 spec states that the default value is the first
--             -- defined enum value, which must be 0. Since we currently don't
--             -- raise a compilation error for this like we should, we have to
--             -- handle this case.
--             --
--             -- For now, die horribly to mimic what should be a compilation
--             -- error.
--     err _ = null_
--             -- From the JSONPB spec:
--             --
--             --   If a value is missing in the JSON-encoded data or if its value
--             --   is null, it will be interpreted as the appropriate default
--             --   value when parsed into a protocol buffer.
--             --
--             -- Thus, interpreting a wire value out of enum range as "missing",
--             -- we yield null here to mean the default value.
--
-- instance ToJSONPB e => ToJSONPB (Enumerated e) where
--   toJSONPB = enumToJSONPB toJSONPB A.Null
--   toEncodingPB = enumToJSONPB toEncodingPB E.null_
--
-- instance (Bounded e, Enum e, FromJSONPB e) => FromJSONPB (Enumerated e) where
--   parseJSONPB A.Null = pure def -- So CG does not have to handle this case in
--                                 -- every generated instance
--   parseJSONPB v      = Enumerated . Right <$> parseJSONPB v

-- ** Instances for composite types
--------------------------------------------------------------------------------
-- Instances for repeated messages
--
-- JSON value will be the vector elements encoded as a JSON array. The null
-- value is accepted as the empty list, @[]@.
instance ToJSONPB a => ToJSONPB (V.Vector a) where
  toJSONPB :: Vector a -> Options -> Value
toJSONPB Vector a
v Options
opts = Array -> Value
A.Array ((a -> Value) -> Vector a -> Array
forall a b. (a -> b) -> Vector a -> Vector b
V.map (\a
x -> a -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB a
x Options
opts) Vector a
v)
  toEncodingPB :: Vector a -> Options -> Encoding
toEncodingPB Vector a
v Options
opts = (a -> Encoding) -> [a] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
E.list (\a
x -> a -> Options -> Encoding
forall a. ToJSONPB a => a -> Options -> Encoding
toEncodingPB a
x Options
opts) (Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
v)

instance FromJSONPB a => FromJSONPB (V.Vector a) where
  parseJSONPB :: Value -> Parser (Vector a)
parseJSONPB (A.Array Array
vs) = (Value -> Parser a) -> Array -> Parser (Vector a)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Vector a -> m (Vector b)
mapM Value -> Parser a
forall a. FromJSONPB a => Value -> Parser a
parseJSONPB Array
vs
  parseJSONPB Value
A.Null       = Vector a -> Parser (Vector a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
  parseJSONPB Value
v            = [Char] -> Value -> Parser (Vector a)
forall a. [Char] -> Value -> Parser a
A.typeMismatch [Char]
"repeated" Value
v

--------------------------------------------------------------------------------
-- Instances for nested messages
instance ToJSONPB a => ToJSONPB (Maybe a) where
  toJSONPB :: Maybe a -> Options -> Value
toJSONPB Maybe a
mx Options
opts = Value -> (a -> Value) -> Maybe a -> Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Value
A.Null (\a
x -> a -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB a
x Options
opts) Maybe a
mx
  toEncodingPB :: Maybe a -> Options -> Encoding
toEncodingPB Maybe a
mx Options
opts = Encoding -> (a -> Encoding) -> Maybe a -> Encoding
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Encoding
E.null_ (\a
x -> a -> Options -> Encoding
forall a. ToJSONPB a => a -> Options -> Encoding
toEncodingPB a
x Options
opts) Maybe a
mx

instance FromJSONPB a => FromJSONPB (Maybe a) where
  parseJSONPB :: Value -> Parser (Maybe a)
parseJSONPB Value
A.Null = Maybe a -> Parser (Maybe a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
  parseJSONPB Value
v      = (a -> Maybe a) -> Parser a -> Parser (Maybe a)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just (Value -> Parser a
forall a. FromJSONPB a => Value -> Parser a
parseJSONPB Value
v)

instance ToJSONPB a => ToJSONPB [a] where
  toJSONPB :: [a] -> Options -> Value
toJSONPB [a]
xs Options
opts = Array -> Value
A.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ((a -> Value) -> [a] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
x -> a -> Options -> Value
forall a. ToJSONPB a => a -> Options -> Value
toJSONPB a
x Options
opts) [a]
xs)
  toEncodingPB :: [a] -> Options -> Encoding
toEncodingPB [a]
xs Options
opts = (a -> Encoding) -> [a] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
E.list (\a
x -> a -> Options -> Encoding
forall a. ToJSONPB a => a -> Options -> Encoding
toEncodingPB a
x Options
opts) [a]
xs

instance FromJSONPB a => FromJSONPB [a] where
  parseJSONPB :: Value -> Parser [a]
parseJSONPB (A.Array Array
xs) = (Value -> Parser a) -> [Value] -> Parser [a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Value -> Parser a
forall a. FromJSONPB a => Value -> Parser a
parseJSONPB (Array -> [Value]
forall a. Vector a -> [a]
V.toList Array
xs)
  parseJSONPB Value
A.Null       = [a] -> Parser [a]
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
  parseJSONPB Value
v            = [Char] -> Value -> Parser [a]
forall a. [Char] -> Value -> Parser a
A.typeMismatch [Char]
"repeated" Value
v

-- A couple of orphaned FieldDefault instances
-- NB: Not ideal, should contribute back to proto-lens or come up with another concept of default fields.
instance FieldDefault [a] where
  fieldDefault :: [a]
fieldDefault = [a]
forall a. Monoid a => a
mempty

instance FieldDefault (Maybe a) where
  fieldDefault :: Maybe a
fieldDefault = Maybe a
forall a. Maybe a
Nothing