| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Mu.Adapter.ProtoBuf
Description
Just import the module and you can turn any
value with a ToSchema and FromSchema from
and to Protocol Buffers. Since Protocol Buffers
need information about field identifiers, you
need to annotate your schema using ProtoBufAnnotation.
Synopsis
- data ProtoBufAnnotation
- = ProtoBufId Nat [(Symbol, ProtoBufOptionConstant)]
- | ProtoBufOneOfIds [Nat]
- data ProtoBufOptionConstant
- class ProtoBridgeTerm sch (sch :/: sty) => IsProtoSchema sch sty
- toProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema sch sty, ToSchema sch sty a) => a -> MessageBuilder
- fromProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema sch sty, FromSchema sch sty a) => Parser RawMessage a
- parseProtoViaSchema :: forall sch a sty. (IsProtoSchema sch sty, FromSchema sch sty a) => ByteString -> Either ParseError a
- class FromProtoBufRegistry (ms :: Mappings Nat Schema') t
- fromProtoBufWithRegistry :: forall (r :: Registry) t. FromProtoBufRegistry r t => Parser RawMessage t
- parseProtoBufWithRegistry :: forall (r :: Registry) t. FromProtoBufRegistry r t => ByteString -> Either ParseError t
Custom annotations
data ProtoBufAnnotation Source #
Annotations for Protocol Buffers fields.
Constructors
| ProtoBufId Nat [(Symbol, ProtoBufOptionConstant)] | Numeric field identifier for normal fields and whether it should be packed (only used for lists of number-like values) |
| ProtoBufOneOfIds [Nat] | List of identifiers for fields which contain a union |
Instances
| type AnnotatedSchema ProtoBufAnnotation ExampleProtoBufSchema | |
Defined in Mu.Quasi.ProtoBuf.Example type AnnotatedSchema ProtoBufAnnotation ExampleProtoBufSchema = '['AnnField "person" "firstName" ('ProtoBufId 1 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "lastName" ('ProtoBufId 2 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "age" ('ProtoBufId 3 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "gender" ('ProtoBufId 4 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "address" ('ProtoBufId 5 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "lucky_numbers" ('ProtoBufId 6 '['("packed", 'ProtoBufOptionConstantBool 'True)]), 'AnnField "address" "postcode" ('ProtoBufId 1 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "address" "country" ('ProtoBufId 2 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "gender" "nb" ('ProtoBufId 0 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "gender" "male" ('ProtoBufId 1 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "gender" "female" ('ProtoBufId 2 ('[] :: [(Symbol, ProtoBufOptionConstant)]))] | |
| type AnnotatedSchema ProtoBufAnnotation Example2ProtoBufSchema | |
Defined in Mu.Quasi.ProtoBuf.Example type AnnotatedSchema ProtoBufAnnotation Example2ProtoBufSchema = '['AnnField "gender" "male" ('ProtoBufId 1 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "gender" "female" ('ProtoBufId 2 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "gender" "nonbinary" ('ProtoBufId 3 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "names" ('ProtoBufId 1 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "age" ('ProtoBufId 2 ('[] :: [(Symbol, ProtoBufOptionConstant)])), 'AnnField "person" "gender" ('ProtoBufId 3 ('[] :: [(Symbol, ProtoBufOptionConstant)]))] | |
Conversion using schemas
class ProtoBridgeTerm sch (sch :/: sty) => IsProtoSchema sch sty Source #
Represents those Schemas which are supported by Protocol Buffers.
Some values which can be represented as Terms cannot be so in
Protocol Buffers. For example, you cannot have a list within an option.
Instances
| ProtoBridgeTerm sch (sch :/: sty) => IsProtoSchema (sch :: Schema t f) (sty :: t) Source # | |
Defined in Mu.Adapter.ProtoBuf | |
toProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema sch sty, ToSchema sch sty a) => a -> MessageBuilder Source #
Conversion to Protocol Buffers mediated by a schema.
fromProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema sch sty, FromSchema sch sty a) => Parser RawMessage a Source #
Conversion from Protocol Buffers mediated by a schema.
This function requires a RawMessage, which means
that we already know that the Protocol Buffers message
is well-formed. Use parseProtoViaSchema to parse directly
from a ByteString.
parseProtoViaSchema :: forall sch a sty. (IsProtoSchema sch sty, FromSchema sch sty a) => ByteString -> Either ParseError a Source #
Conversion from Protocol Buffers mediated by a schema.
This function receives the ByteString directly,
and parses it as part of its duty.
Conversion using registry
class FromProtoBufRegistry (ms :: Mappings Nat Schema') t Source #
Represents Registrys for which every Schema
is supported by the Protocol Buffers format.
Minimal complete definition
fromProtoBufRegistry'
Instances
| FromProtoBufRegistry ('[] :: [Mapping Nat Schema']) t Source # | |
Defined in Mu.Adapter.ProtoBuf Methods fromProtoBufRegistry' :: Proxy '[] -> Parser RawMessage t | |
| (IsProtoSchema s sty, FromSchema s sty t, FromProtoBufRegistry ms t) => FromProtoBufRegistry ((n :-> s) ': ms) t Source # | |
Defined in Mu.Adapter.ProtoBuf Methods fromProtoBufRegistry' :: Proxy ((n :-> s) ': ms) -> Parser RawMessage t | |
fromProtoBufWithRegistry :: forall (r :: Registry) t. FromProtoBufRegistry r t => Parser RawMessage t Source #
Conversion from Protocol Buffers by checking
all the Schemas in a Registry.
As fromProtoViaSchema, this version requires
an already well-formed Protocol Buffers message.
parseProtoBufWithRegistry :: forall (r :: Registry) t. FromProtoBufRegistry r t => ByteString -> Either ParseError t Source #
Conversion from Protocol Buffers by checking
all the Schemas in a Registry.
As parseProtoViaSchema, this version receives
a ByteString and parses it as part of its duty.