| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- type Key = Key
- keyFromText :: Text -> Key
- class ToJSONPB a where
- class FromJSONPB a where
- parseJSONPB :: Value -> Parser a
- encode :: ToJSONPB a => Options -> a -> ByteString
- eitherDecode :: FromJSONPB a => ByteString -> Either String a
- class Monoid m => KeyValuePB m where
- (.=) :: (HasDefault v, ToJSONPB v, KeyValuePB kvp) => Text -> v -> Options -> kvp
- (.:) :: (FromJSONPB a, HasDefault a) => Object -> Text -> Parser a
- parseField :: FromJSONPB a => Object -> Key -> Parser a
- data Options = Options {}
- defaultOptions :: Options
- jsonPBOptions :: Options
- dropNamedPrefix :: Named a => Proxy# a -> String -> String
- object :: [Options -> [Pair]] -> Options -> Value
- objectOrNull :: [Options -> [Pair]] -> Options -> Value
- pairs :: [Options -> Series] -> Options -> Encoding
- pairsOrNull :: [Options -> Series] -> Options -> Encoding
- enumFieldString :: forall a. (Named a, Show a) => a -> Value
- enumFieldEncoding :: forall a. (Named a, Show a) => a -> Encoding
- toAesonValue :: ToJSONPB a => a -> Value
- toAesonEncoding :: ToJSONPB a => a -> Encoding
- parseFP :: (FromJSON a, FromJSONKey a) => String -> Value -> Parser a
- parseNumOrDecimalString :: FromJSON a => String -> Value -> Parser a
- bsToJSONPB :: ByteString -> Value
- enumToJSONPB :: (e -> Options -> a) -> a -> Enumerated e -> Options -> a
Documentation
keyFromText :: Text -> Key Source #
Typeclass definitions
class ToJSONPB a where Source #
Minimal complete definition
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
| ToJSONPB Bool Source # | |
| ToJSONPB Double Source # | |
| ToJSONPB Float Source # | |
| ToJSONPB Int32 Source # | |
| ToJSONPB Int64 Source # | |
| ToJSONPB Word32 Source # | |
| ToJSONPB Word64 Source # | |
| ToJSONPB ByteString Source # | |
Defined in Proto3.Suite.JSONPB.Class Methods toJSONPB :: ByteString -> Options -> Value Source # toEncodingPB :: ByteString -> Options -> Encoding Source # | |
| ToJSONPB Encoding Source # | |
| ToJSONPB Value Source # | |
| ToJSONPB Text Source # | |
| ToJSONPB Timestamp Source # | |
| ToJSONPB a => ToJSONPB (Maybe a) Source # | |
| ToJSONPB a => ToJSONPB (Vector a) Source # | |
| ToJSONPB e => ToJSONPB (Enumerated e) Source # | |
Defined in Proto3.Suite.JSONPB.Class Methods toJSONPB :: Enumerated e -> Options -> Value Source # toEncodingPB :: Enumerated e -> Options -> Encoding Source # | |
| ToJSONPB (Fixed Int32) Source # | |
| ToJSONPB (Fixed Int64) Source # | |
| ToJSONPB (Fixed Word32) Source # | |
| ToJSONPB (Fixed Word64) Source # | |
| (ToJSONKey k, ToJSONPB k, ToJSONPB v) => ToJSONPB (Map k v) Source # | |
class FromJSONPB a where Source #
Instances
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
(.=) :: (HasDefault v, ToJSONPB v, KeyValuePB kvp) => Text -> v -> Options -> kvp Source #
(.:) :: (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
parseField :: FromJSONPB a => Object -> Key -> Parser a Source #
JSONPB rendering and parsing options
Constructors
| Options | |
Fields
| |
Instances
| Eq Options Source # | |
| Show Options Source # | |
| Generic Options Source # | |
| Arbitrary Options Source # | |
| type Rep Options Source # | |
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
toAesonValue :: ToJSONPB a => a -> Value Source #
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
bsToJSONPB :: ByteString -> Value 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 |