Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- | ProtoBufOneOfIds [Nat]
- class ProtoBridgeTerm w sch (sch :/: sty) => IsProtoSchema w sch sty
- toProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema Maybe sch sty, ToSchema Maybe sch sty a) => a -> MessageBuilder
- fromProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema Maybe sch sty, FromSchema Maybe sch sty a) => Parser RawMessage a
- parseProtoViaSchema :: forall sch a sty. (IsProtoSchema Maybe sch sty, FromSchema Maybe 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.
ProtoBufId Nat | Numeric field identifier for normal fields |
ProtoBufOneOfIds [Nat] | List of identifiers for fields which contain a union |
Instances
Conversion using schemas
class ProtoBridgeTerm w sch (sch :/: sty) => IsProtoSchema w sch sty Source #
Represents those Schema
s which are supported by Protocol Buffers.
Some values which can be represented as Term
s cannot be so in
Protocol Buffers. For example, you cannot have a list within an option.
Instances
ProtoBridgeTerm w sch (sch :/: sty) => IsProtoSchema w (sch :: Schema t f) (sty :: t) Source # | |
Defined in Mu.Adapter.ProtoBuf |
toProtoViaSchema :: forall t f (sch :: Schema t f) a sty. (IsProtoSchema Maybe sch sty, ToSchema Maybe 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 Maybe sch sty, FromSchema Maybe 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 Maybe sch sty, FromSchema Maybe 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 #
fromProtoBufRegistry'
Instances
FromProtoBufRegistry ([] :: [Mapping Nat Schema']) t Source # | |
Defined in Mu.Adapter.ProtoBuf fromProtoBufRegistry' :: Proxy [] -> Parser RawMessage t | |
(IsProtoSchema Maybe s sty, FromSchema Maybe s sty t, FromProtoBufRegistry ms t) => FromProtoBufRegistry ((n :-> s) ': ms) t Source # | |
Defined in Mu.Adapter.ProtoBuf 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 Schema
s 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 Schema
s in a Registry
.
As parseProtoViaSchema
, this version receives
a ByteString
and parses it as part of its duty.