proto3-suite-0.5.1: A higher-level API to the proto3-wire library
Safe HaskellNone
LanguageHaskell2010

Proto3.Suite.JSONPB.Class

Description

Support for the JSONPB canonical JSON encoding described at https://developers.google.com/protocol-buffers/docs/proto3#json.

This modules provides Aeson-like helper functions, typeclasses, and instances for converting to and from values of types which have a JSONPB representation and equivalent underlying 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 ToJSON and 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"
Synopsis

Documentation

type Key = Key Source #

Typeclass definitions

class ToJSONPB a where Source #

ToJSON variant for JSONPB direct encoding via Encoding

Minimal complete definition

toJSONPB

Methods

toJSONPB :: a -> Options -> Value Source #

toJSON variant for JSONPB encoders.

toEncodingPB :: a -> Options -> Encoding Source #

toEncoding variant for JSONPB encoders. If an implementation is not provided, uses toJSONPB (which is less efficient since it indirects through the Value IR).

Instances

Instances details
ToJSONPB Bool Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Double Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Float Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Int32 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Int64 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Word32 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Word64 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB ByteString Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Encoding Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Value Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Text Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB Timestamp Source # 
Instance details

Defined in Google.Protobuf.Timestamp

ToJSONPB a => ToJSONPB (Maybe a) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB a => ToJSONPB (Vector a) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB e => ToJSONPB (Enumerated e) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB (Fixed Int32) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB (Fixed Int64) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB (Fixed Word32) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

ToJSONPB (Fixed Word64) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

(ToJSONKey k, ToJSONPB k, ToJSONPB v) => ToJSONPB (Map k v) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

class FromJSONPB a where Source #

FromJSON variant for JSONPB decoding from the Value IR

Methods

parseJSONPB :: Value -> Parser a Source #

parseJSON variant for JSONPB decoders.

Instances

Instances details
FromJSONPB Bool Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Double Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Float Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Int32 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Int64 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Word32 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Word64 Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB ByteString Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Value Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Text Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB Timestamp Source # 
Instance details

Defined in Google.Protobuf.Timestamp

FromJSONPB a => FromJSONPB (Maybe a) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB a => FromJSONPB (Vector a) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

(ProtoEnum e, FromJSONPB e) => FromJSONPB (Enumerated e) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB (Fixed Int32) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB (Fixed Int64) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB (Fixed Word32) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

FromJSONPB (Fixed Word64) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

(Ord k, FromJSONKey k, FromJSONPB k, FromJSONPB v) => FromJSONPB (Map k v) Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

Methods

parseJSONPB :: Value -> Parser (Map k v) Source #

JSONPB codec entry points

encode :: ToJSONPB a => Options -> a -> ByteString Source #

encode variant for serializing a JSONPB value as a lazy ByteString.

eitherDecode :: FromJSONPB a => ByteString -> Either String a Source #

eitherDecode variant for deserializing a JSONPB value from a lazy ByteString.

Operator definitions

class Monoid m => KeyValuePB m where Source #

JSONPB-encoded monoidal key-value pairs

Methods

pair :: ToJSONPB v => Text -> v -> Options -> m Source #

Instances

Instances details
KeyValuePB Series Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

Methods

pair :: ToJSONPB v => Text -> v -> Options -> Series Source #

KeyValuePB [Pair] Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

Methods

pair :: ToJSONPB v => Text -> v -> Options -> [Pair] Source #

(.=) :: (HasDefault v, ToJSONPB v, KeyValuePB kvp) => Text -> v -> Options -> kvp Source #

Construct a monoidal key-value pair, using mempty to represent omission of default values (unless the given Options force their emission).

(.:) :: (FromJSONPB a, HasDefault a) => Object -> Text -> Parser a Source #

.: 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

JSONPB rendering and parsing options

data Options Source #

Constructors

Options 

Fields

  • optEmitDefaultValuedFields :: Bool
     
  • optEmitNamedOneof :: Bool

    For compatibility with the Go JSONPB implementation.

    If False, the following message

    message MyMessage {
      oneof animal {
        Cat cat = 1;
        Dog dog = 2;
      }
    }

    will be serialized as

    MyMessage (Animal (Cat "Simba")) => { "cat": "Simba" }

    instead of

    MyMessage (Animal (Cat "Simba")) => { "animal": { "cat": "Simba" } }

Instances

Instances details
Eq Options Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

Methods

(==) :: Options -> Options -> Bool #

(/=) :: Options -> Options -> Bool #

Show Options Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

Generic Options Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

Associated Types

type Rep Options :: Type -> Type #

Methods

from :: Options -> Rep Options x #

to :: Rep Options x -> Options #

Arbitrary Options Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

type Rep Options Source # 
Instance details

Defined in Proto3.Suite.JSONPB.Class

type Rep Options = D1 ('MetaData "Options" "Proto3.Suite.JSONPB.Class" "proto3-suite-0.5.1-KgIMs0pOzZ0CPM0GxpZWzf" 'False) (C1 ('MetaCons "Options" 'PrefixI 'True) (S1 ('MetaSel ('Just "optEmitDefaultValuedFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "optEmitNamedOneof") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

defaultOptions :: Options Source #

Default options for JSON encoding. By default, all options are True.

jsonPBOptions :: Options Source #

Options for JSONPB encoding.

Helper types and functions

objectOrNull :: [Options -> [Pair]] -> Options -> Value Source #

As object, but produces Null when there are no pairs to wrap (cf. the empty object result of 'object)

>>> object [const []] defaultOptions
Object (fromList [])
>>> objectOrNull [const []] defaultOptions
Null

pairsOrNull :: [Options -> Series] -> Options -> Encoding Source #

As pairs, but produces the "null" when there is no series to encode (cf. the empty object encoding of pairs)

>>> pairs [const mempty] defaultOptions
"{}"
>>> pairsOrNull [const mempty] defaultOptions
"null"

enumFieldString :: forall a. (Named a, Show a) => a -> Value Source #

enumFieldEncoding :: forall a. (Named a, Show a) => a -> Encoding Source #

toAesonValue :: ToJSONPB a => a -> Value Source #

A Aeson Value encoder for values which can be JSONPB-encoded.

toAesonEncoding :: ToJSONPB a => a -> Encoding Source #

A direct Encoding for values which can be JSONPB-encoded.

parseFP :: (FromJSON a, FromJSONKey a) => String -> Value -> Parser a Source #

Parse a JSONPB floating point value; first parameter provides context for type mismatches

parseNumOrDecimalString :: FromJSON a => String -> Value -> Parser a Source #

Liberally parse an integer value (e.g. 42 or "42" as 42); first parameter provides context for type mismatches

Common instances for jsonpb codec implementations

Instances for scalar types

enumToJSONPB Source #

Arguments

:: (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

Instances for composite types

Orphan instances

HasDefault Encoding Source #
>>> isDefault (def @E.Encoding)
True
Instance details

HasDefault Value Source #
>>> isDefault (def @A.Value)
True
Instance details