proto3-wire-1.2.0: A low-level implementation of the Protocol Buffers (version 3) wire format

Safe HaskellNone
LanguageHaskell2010

Proto3.Wire.Encode

Contents

Description

Low level functions for writing the protobufs wire format.

Because protobuf messages are encoded as a collection of fields, one can use the Monoid instance for MessageBuilder to encode multiple fields.

One should be careful to make sure that FieldNumbers appear in increasing order.

In protocol buffers version 3, all fields are optional. To omit a value for a field, simply do not append it to the MessageBuilder. One can create functions for wrapping optional fields with a Maybe type.

Similarly, repeated fields can be encoded by concatenating several values with the same FieldNumber.

For example:

strings :: Foldable f => FieldNumber -> f String -> MessageBuilder
strings = foldMap . string

1 `strings` Just "some string" <>
2 `strings` [ "foo", "bar", "baz" ]
Synopsis

MessageBuilder type

data MessageBuilder Source #

A MessageBuilder represents a serialized protobuf message

Use the utilities provided by this module to create MessageBuilders

You can concatenate two messages using the Monoid instance for MessageBuilder

Use toLazyByteString when you're done assembling the MessageBuilder

reverseMessageBuilder :: MessageBuilder -> BuildR Source #

Convert a message builder to a BuildR.

vectorMessageBuilder :: forall v a. Vector v a => (a -> MessageBuilder) -> v a -> MessageBuilder Source #

Essentially foldMap, but iterates right to left for efficiency.

messageLength :: MessageBuilder -> Word Source #

O(n): Retrieve the length of a message, in bytes.

toLazyByteString :: MessageBuilder -> ByteString Source #

Convert a message to a lazy ByteString

unsafeFromLazyByteString :: ByteString -> MessageBuilder Source #

This lets you cast an arbitrary ByteString to a MessageBuilder, whether or not the ByteString corresponds to a valid serialized protobuf message

Do not use this function unless you know what you're doing because it lets you assemble malformed protobuf MessageBuilders

Standard Integers

int32 :: FieldNumber -> Int32 -> MessageBuilder Source #

Encode a 32-bit "standard" integer

For example:

>>> 1 `int32` 42
Proto3.Wire.Encode.unsafeFromLazyByteString "\b*"
>>> 1 `int64` (-42)
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\214\255\255\255\255\255\255\255\255\SOH"

NOTE: Protobuf encoding converts an int32 to a 64-bit unsigned value before encoding it, not a 32-bit value (which would be more efficient).

To quote the specification: "If you use int32 or int64 as the type for a negative number, the resulting varint is always ten bytes long..." https://developers.google.com/protocol-buffers/docs/encoding#varints

int64 :: FieldNumber -> Int64 -> MessageBuilder Source #

Encode a 64-bit "standard" integer

For example:

>>> 1 `int32` 42
Proto3.Wire.Encode.unsafeFromLazyByteString "\b*"
>>> 1 `int64` (-42)
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\214\255\255\255\255\255\255\255\255\SOH"

Unsigned Integers

uint32 :: FieldNumber -> Word32 -> MessageBuilder Source #

Encode a 32-bit unsigned integer

For example:

>>> 1 `uint32` 42
Proto3.Wire.Encode.unsafeFromLazyByteString "\b*"

uint64 :: FieldNumber -> Word64 -> MessageBuilder Source #

Encode a 64-bit unsigned integer

For example:

>>> 1 `uint64` 42
Proto3.Wire.Encode.unsafeFromLazyByteString "\b*"

Signed Integers

sint32 :: FieldNumber -> Int32 -> MessageBuilder Source #

Encode a 32-bit signed integer

For example:

>>> 1 `sint32` (-42)
Proto3.Wire.Encode.unsafeFromLazyByteString "\bS"
>>> 1 `sint32` maxBound
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\254\255\255\255\SI"
>>> 1 `sint32` minBound
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\255\255\255\255\SI"

sint64 :: FieldNumber -> Int64 -> MessageBuilder Source #

Encode a 64-bit signed integer

For example:

>>> 1 `sint64` (-42)
Proto3.Wire.Encode.unsafeFromLazyByteString "\bS"
>>> 1 `sint64` maxBound
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\254\255\255\255\255\255\255\255\255\SOH"
>>> 1 `sint64` minBound
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\255\255\255\255\255\255\255\255\255\SOH"

Non-varint Numbers

fixed32 :: FieldNumber -> Word32 -> MessageBuilder Source #

Encode a fixed-width 32-bit integer

For example:

>>> 1 `fixed32` 42
Proto3.Wire.Encode.unsafeFromLazyByteString "\r*\NUL\NUL\NUL"

fixed64 :: FieldNumber -> Word64 -> MessageBuilder Source #

Encode a fixed-width 64-bit integer

For example:

>>> 1 `fixed64` 42
Proto3.Wire.Encode.unsafeFromLazyByteString "\t*\NUL\NUL\NUL\NUL\NUL\NUL\NUL"

sfixed32 :: FieldNumber -> Int32 -> MessageBuilder Source #

Encode a fixed-width signed 32-bit integer

For example:

1 `sfixed32` (-42)

sfixed64 :: FieldNumber -> Int64 -> MessageBuilder Source #

Encode a fixed-width signed 64-bit integer

For example:

>>> 1 `sfixed64` (-42)
Proto3.Wire.Encode.unsafeFromLazyByteString "\t\214\255\255\255\255\255\255\255"

float :: FieldNumber -> Float -> MessageBuilder Source #

Encode a floating point number

For example:

>>> 1 `float` 3.14
Proto3.Wire.Encode.unsafeFromLazyByteString "\r\195\245H@"

double :: FieldNumber -> Double -> MessageBuilder Source #

Encode a double-precision number

For example:

>>> 1 `double` 3.14
Proto3.Wire.Encode.unsafeFromLazyByteString "\t\US\133\235Q\184\RS\t@"

enum :: ProtoEnum e => FieldNumber -> e -> MessageBuilder Source #

Encode a value with an enumerable type.

You should instantiate ProtoEnum for a type in order to emulate enums appearing in .proto files.

For example:

>>> :{
    data Shape = Circle | Square | Triangle deriving (Bounded, Enum)
    instance ProtoEnum Shape
    data Gap = Gap0 | Gap3
    instance ProtoEnum Gap where
      toProtoEnumMay i = case i of
        0 -> Just Gap0
        3 -> Just Gap3
        _ -> Nothing
      fromProtoEnum g = case g of
        Gap0 -> 0
        Gap3 -> 3
:}
>>> 1 `enum` Triangle <> 2 `enum` Gap3
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\STX\DLE\ETX"

bool :: FieldNumber -> Bool -> MessageBuilder Source #

Encode a boolean value

For example:

>>> 1 `bool` True
Proto3.Wire.Encode.unsafeFromLazyByteString "\b\SOH"

Strings

bytes :: FieldNumber -> BuildR -> MessageBuilder Source #

Encode a sequence of octets as a field of type bytes.

>>> 1 `bytes` (Proto3.Wire.Reverse.stringUtf8 "testing")
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\atesting"

string :: FieldNumber -> String -> MessageBuilder Source #

Encode a UTF-8 string.

For example:

>>> 1 `string` "testing"
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\atesting"

text :: FieldNumber -> Text -> MessageBuilder Source #

Encode lazy Text as UTF-8

For example:

>>> 1 `text` "testing"
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\atesting"

byteString :: FieldNumber -> ByteString -> MessageBuilder Source #

Encode a collection of bytes in the form of a strict ByteString.

For example:

>>> 1 `byteString` "testing"
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\atesting"

lazyByteString :: FieldNumber -> ByteString -> MessageBuilder Source #

Encode a lazy bytestring.

For example:

>>> 1 `lazyByteString` "testing"
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\atesting"

Embedded Messages

embedded :: FieldNumber -> MessageBuilder -> MessageBuilder Source #

Encode an embedded message.

The message is represented as a MessageBuilder, so it is possible to chain encoding functions.

For example:

>>> 1 `embedded` (1 `string` "this message" <> 2 `string` " is embedded")
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\FS\n\fthis message\DC2\f is embedded"

Packed repeated fields

packedVarints :: Foldable f => FieldNumber -> f Word64 -> MessageBuilder Source #

Encode varints in the space-efficient packed format. But consider packedVarintsV, which may be faster.

The values to be encoded are specified by mapping the elements of a vector.

>>> packedVarints 1 [1, 2, 3]
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\ETX\SOH\STX\ETX"

packedVarintsV :: Vector v a => (a -> Word64) -> FieldNumber -> v a -> MessageBuilder Source #

A faster but more specialized variant of:

\f num -> packedVarints num . fmap f
>>> packedVarintsV (subtract 10) 1 ([11, 12, 13] :: Data.Vector.Vector Word64)
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\ETX\SOH\STX\ETX"

packedBoolsV :: Vector v a => (a -> Bool) -> FieldNumber -> v a -> MessageBuilder Source #

A faster but more specialized variant of:

packedVarintsV (fromIntegral . fromEnum) num
>>> packedBoolsV not 1 ([False, True] :: Data.Vector.Vector Bool)
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\STX\SOH\NUL"

packedFixed32 :: Foldable f => FieldNumber -> f Word32 -> MessageBuilder Source #

Encode fixed-width Word32s in the space-efficient packed format. But consider packedFixed32V, which may be faster.

The values to be encoded are specified by mapping the elements of a vector.

>>> packedFixed32 1 [1, 2, 3]
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\f\SOH\NUL\NUL\NUL\STX\NUL\NUL\NUL\ETX\NUL\NUL\NUL"

packedFixed32V :: Vector v a => (a -> Word32) -> FieldNumber -> v a -> MessageBuilder Source #

A faster but more specialized variant of:

\f num -> packedFixed32 num . fmap f
>>> packedFixed32V (subtract 10) 1 ([11, 12, 13] :: Data.Vector.Vector Word32)
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\f\SOH\NUL\NUL\NUL\STX\NUL\NUL\NUL\ETX\NUL\NUL\NUL"

packedFixed64 :: Foldable f => FieldNumber -> f Word64 -> MessageBuilder Source #

Encode fixed-width Word64s in the space-efficient packed format. But consider packedFixed64V, which may be faster.

The values to be encoded are specified by mapping the elements of a vector.

>>> packedFixed64 1 [1, 2, 3]
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\CAN\SOH\NUL\NUL\NUL\NUL\NUL\NUL\NUL\STX\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ETX\NUL\NUL\NUL\NUL\NUL\NUL\NUL"

packedFixed64V :: Vector v a => (a -> Word64) -> FieldNumber -> v a -> MessageBuilder Source #

A faster but more specialized variant of:

\f num -> packedFixed64 num . fmap f
>>> packedFixed64V (subtract 10) 1 ([11, 12, 13] :: Data.Vector.Vector Word64)
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\CAN\SOH\NUL\NUL\NUL\NUL\NUL\NUL\NUL\STX\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ETX\NUL\NUL\NUL\NUL\NUL\NUL\NUL"

packedFloats :: Foldable f => FieldNumber -> f Float -> MessageBuilder Source #

Encode floats in the space-efficient packed format. But consider packedFloatsV, which may be faster.

>>> 1 `packedFloats` [1, 2, 3]
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\f\NUL\NUL\128?\NUL\NUL\NUL@\NUL\NUL@@"

packedFloatsV :: Vector v a => (a -> Float) -> FieldNumber -> v a -> MessageBuilder Source #

A faster but more specialized variant of:

\f num -> packedFloats num . fmap f
>>> packedFloatsV (subtract 10) 1 ([11, 12, 13] :: Data.Vector.Vector Float)
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\f\NUL\NUL\128?\NUL\NUL\NUL@\NUL\NUL@@"

packedDoubles :: Foldable f => FieldNumber -> f Double -> MessageBuilder Source #

Encode doubles in the space-efficient packed format. But consider packedDoublesV, which may be faster.

>>> 1 `packedDoubles` [1, 2, 3]
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\CAN\NUL\NUL\NUL\NUL\NUL\NUL\240?\NUL\NUL\NUL\NUL\NUL\NUL\NUL@\NUL\NUL\NUL\NUL\NUL\NUL\b@"

packedDoublesV :: Vector v a => (a -> Double) -> FieldNumber -> v a -> MessageBuilder Source #

A faster but more specialized variant of:

\f num -> packedDoubles num . fmap f
>>> packedDoublesV (subtract 10) 1 ([11, 12, 13] :: Data.Vector.Vector Double)
Proto3.Wire.Encode.unsafeFromLazyByteString "\n\CAN\NUL\NUL\NUL\NUL\NUL\NUL\240?\NUL\NUL\NUL\NUL\NUL\NUL\NUL@\NUL\NUL\NUL\NUL\NUL\NUL\b@"