mu-protobuf-0.2.0.0: Protocol Buffers serialization and gRPC schema import for Mu microservices
Safe HaskellNone
LanguageHaskell2010

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

Custom annotations

data ProtoBufAnnotation Source #

Annotations for Protocol Buffers fields.

Constructors

ProtoBufId Nat

Numeric field identifier for normal fields

ProtoBufOneOfIds [Nat]

List of identifiers for fields which contain a union

Instances

Instances details
type AnnotatedSchema ProtoBufAnnotation ExampleProtoBufSchema 
Instance details

Defined in Mu.Quasi.ProtoBuf.Example

type AnnotatedSchema ProtoBufAnnotation ExampleProtoBufSchema = '['AnnField "person" "firstName" ('ProtoBufId 1), 'AnnField "person" "lastName" ('ProtoBufId 2), 'AnnField "person" "age" ('ProtoBufId 3), 'AnnField "person" "gender" ('ProtoBufId 4), 'AnnField "person" "address" ('ProtoBufId 5), 'AnnField "address" "postcode" ('ProtoBufId 1), 'AnnField "address" "country" ('ProtoBufId 2), 'AnnField "gender" "nb" ('ProtoBufId 0), 'AnnField "gender" "male" ('ProtoBufId 1), 'AnnField "gender" "female" ('ProtoBufId 2)]
type AnnotatedSchema ProtoBufAnnotation Example2ProtoBufSchema 
Instance details

Defined in Mu.Quasi.ProtoBuf.Example

type AnnotatedSchema ProtoBufAnnotation Example2ProtoBufSchema = '['AnnField "gender" "male" ('ProtoBufId 1), 'AnnField "gender" "female" ('ProtoBufId 2), 'AnnField "gender" "nonbinary" ('ProtoBufId 3), 'AnnField "person" "names" ('ProtoBufId 1), 'AnnField "person" "age" ('ProtoBufId 2), 'AnnField "person" "gender" ('ProtoBufId 3)]

Conversion using schemas

class ProtoBridgeTerm w sch (sch :/: sty) => IsProtoSchema w 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

Instances details
ProtoBridgeTerm w sch (sch :/: sty) => IsProtoSchema w (sch :: Schema t f) (sty :: t) Source # 
Instance details

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 #

Represents Registrys for which every Schema is supported by the Protocol Buffers format.

Minimal complete definition

fromProtoBufRegistry'

Instances

Instances details
FromProtoBufRegistry ('[] :: [Mapping Nat Schema']) t Source # 
Instance details

Defined in Mu.Adapter.ProtoBuf

(IsProtoSchema Maybe s sty, FromSchema Maybe s sty t, FromProtoBufRegistry ms t) => FromProtoBufRegistry ((n :-> s) ': ms) t Source # 
Instance details

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.

Orphan instances

ProtoEnum Bool Source # 
Instance details

Alternative (Parser i) Source # 
Instance details

Methods

empty :: Parser i a #

(<|>) :: Parser i a -> Parser i a -> Parser i a #

some :: Parser i a -> Parser i [a] #

many :: Parser i a -> Parser i [a] #