Google's Protocol Buffers Library
AllApplicationManualNameSummaryHelp

  • Documentation
    • Reference manual
    • Packages
      • Google's Protocol Buffers Library
        • Google's Protocol Buffers
          • Overview
          • The SWI-Prolog Implementation
          • Wiretypes
          • Tags
          • Basic Usage
          • Alternation, Aggregation, Encapsulation, and Enumeration
          • Groups (deprecated)
          • Advanced Topics
        • Appendix
        • library(protobufs): Google's Protocol Buffers

1 Google's Protocol Buffers

1.1 Overview

Protocol buffers are Google's language-neutral, platform-neutral, extensible mechanism for serializing structured data -- think XML, but smaller, faster, and simpler. You define how you want your data to be structured once. This takes the form of a template that describes the data structure. You use this template to encode your data structure into wire-streams that may be sent-to or read-from your peers. The underlying wire stream is platform independent, lossless, and may be used to interwork with a variety of languages and systems regardless of word size or endianness. Techniques exist to safely extend your data structure without breaking deployed programs that are compiled against the "old" format.

The idea behind Google's Protocol Buffers is that you define your structured messages using a domain-specific language. This takes the form of a .proto source file. You pass this file through a Google provided tool that generates source code for a target language, creating an interpreter that can encode/decode your structured data. You then compile and build this interpreter into your application program. Depending on the platform, the underlying runtime support is provided by a Google supplied library that is also bound into your program.

1.2 The SWI-Prolog Implementation

In SWI-Prolog, the wire stream interpreter is embodied in the form of a Definite Clause Grammar (DCG). It has a small underlying C-support library that loads when the Prolog module loads. This implementation does not depend on any code that is provided by Google and thus, is not bound by its license terms.

On the Prolog side, you define your message template as a list of predefined Prolog terms that correspond to production rules in the DCG. The process is not unlike specifiying the format of a regular expression. To encode a message, X, to wire-stream, Y, you pass a grounded template, X, and a variable, Y, to protobuf_message/2. To decode a wire-stream, Y, to template, X, you pass an ungrounded template, X, along with a grounded wire-stream, Y, to protobuf_message/2. The interpreter will unify the unbound variables in the template with values decoded from the wire-stream.

1.3 Wiretypes

The wire-stream consists of six primitive payload types, two of which have been deprecated. A primitive in the wire-stream is a multi-byte string that provides three pieces of information: a wire-type, a user-specified tag, and the raw payload. Except for the tag and its wire-type, protobuf payloads are not instantaneously recognizable because the wire-stream contains no payload type information. The interpreter uses the tag to associate the raw payload with a local host type specified by the template. Hence, the message can only be properly decoded using the template that was used to encode it. Note also that the primitive is interpreted according to the needs of a local host. Local word-size and endianness are dealt with at this level.

The following table shows the association between various "host types" used by several peer languages, and the primitives used in the wire-stream:

Prolog Wirestream C++Java Notes
doublefixed64doubledouble
integer64fixed64int64long
floatfixed32floatfloat
integer32fixed32int32int
integervarintint32/64int/long1, 2
unsignedvarintuint32/64int/long2, 3
booleanvarintboolboolean2
enumvarintintint2
atomlength delimitedstringString4
codeslength delimitedstringByteString
utf8_codeslength delimitedstringByteString4
stringlength delimitedstringString4

Notes:

  1. Encoded using a compression technique known as zig-zagging.
  2. Encoded as a modulo 128 string. Its length is proprotional to its magnitude. The intrinsic word length is decoupled between parties.
  3. Prolog's unbounded integer may be expressed as unsigned. This is not portable across languages.
  4. Encoded as UTF8 in the wire-stream.

1.4 Tags

A tag is a small integer that is present in every wire-stream primitive. The tag is the only means that the interpreter has to synchronize the wire-stream with its template. Tags are user defined for each term in each message of the wire-stream. It is important therefore, that they be chosen carefully and in such a way as to not introduce ambiguity.

1.5 Basic Usage

A protobuf wire-stream is a byte string that is comprised of zero or more of the above multi-byte wire-stream primitives. Templates are lists of Prolog terms. Each term corresponds to a production rule in the DCG. The purpose of the template is to provide a recipe and value set for encoding and decoding a particular message. Each term in the template has an arity of two. The term's functor is the local "host type". Argument 1 is its tag, which must always be ground, and argument 2 is its associated value, which may or may not be ground.

Note: It is an error to attempt to encode a message using a template that is not ground. Decoding a message into a template that has unbound variables has the effect of unifying the variables with their corresponding values in the wire-stream.

Map a Prolog structure to a Protocol Buffer:

command(add(X,Y), Proto) :-

   Proto = protobuf([atom(1, command),
                     atom(2, add),
                     integer(3, X),
                     integer(4, Y)
                    ]).

Later on:

   ... prepare X, Y for command ...

   command(add(X,Y), Proto),

   protobuf_message(Proto, Msg),

   ... send the message ...

Proto is the protobuf template. Each template describes exactly one message. Msg is the wire-stream. If you are interworking with other systems and languages, then the protobuf templates that you supply to protobuf_message/2 must be equivalent to those described in the .proto file that is used on the other side.

1.6 Alternation, Aggregation, Encapsulation, and Enumeration

1.6.1 Alternation

The protobuf grammar provides a reserved word, optional, that indicates that the production rule that it refers to may appear once or not at all in a protobuf message. Since Prolog has its own means of alternation, this reserved word is not supported on the Prolog side. It is anticipated that customary Prolog mechanisms for nondeterminism (e.g. backtracking) will be used to generate and test alternatives.

1.6.2 Aggregation

It is possible to specify homogeneous vectors of things (e.g. lists of numbers) using the repeated attribute. You specify a repeated field as follows:

    repeated(22, float([1,2,3,4])),
    repeated(23, enum(tank_state([empty, half_full, full]))).

The first clause above, will cause all four items in the list to be encoded in the wire-stream as IEEE-754 32-bit floating point numbers, all with tag 22. The decoder will aggregate all items in the wire-stream with tag 22 into a list as above. Likewise, the all items listed in the second clause will be encoded in the wire-stream according to the mapping defined in an enumeration (described below) tank_state/2, each with tag 23.

Notes:

Beware that there is no explicit means to encode an empty set. The protobuf specification provides that a repeated field may match a tag zero or more times. The empty set, while legal, produces no output on encode. While decoding a repeated term, failure to match the specified tag will yield an empty set of the specified host type.

The protobuf grammar provides a variant of the repeated field known as "packed." Packed, repeated fields are currently not supported by our interpreter.

1.6.3 Encapsulation and Enumeration

It is possible to embed one protocol buffer specification inside another using the embedded term. The following example shows a vector of numbers being placed in an envelope that contains a command enumeration.

Enumerations are a compact method of sending tokens from one system to another. Most occupy only two bytes in the wire-stream. An enumeration requires that you specify a callable predicate like commands/2, below. The first argument is an atom specifying the name of token, and the second is an non-negative integer that specifies the token's value. These must of course, match a corresponding enumeration in the .proto file.

Note: You must expose this predicate to the protobufs module by assigning it explicitly.


protobufs:commands(Key, Value) :-
        commands(Key, Value).

commands(square, 1).
commands(decimate, 2).
commands(transform, 3).
commands(inverse_transform, 4).

basic_vector(Type, Proto) :-
        vector_type(Type, Tag),

        Proto = protobuf([ repeated(Tag, Type) ]).

send_command(Command, Vector, Msg) :-

        basic_vector(Vector, Proto1),

        Proto = protobuf([enum(1, commands(Command)),
                          embedded(2, Proto1)]),

        protobuf_message(Proto, Msg).

Use it as follows:

?- send_command(square, double([1,22,3,4]), Msg).
Msg = [8, 1, 18, 36, 17, 0, 0, 0, 0, 0, 0, 240, 63, 17, 0, 0, 0, 0, 0,
0, 54, 64, 17, 0, 0, 0, 0, 0, 0, 8, 64, 17, 0, 0, 0, 0, 0, 0, 16, 64].

?- send_command(Cmd, V, $Msg).
Cmd = square,
V = double([1.0, 22.0, 3.0, 4.0]) .

Compatibility Note: The protobuf grammar (protobuf-2.1.0) permits enumerations to assume negative values. This requires them to be encoded as integers. But Google's own Golden Message unit-test framework has enumerations encoded as unsigned. Consequently, parsers that encode them as integers cannot properly parse the Golden Message. So it's probably a good idea to avoid negative values in enumerations. Our parser forbids it anyway.

1.6.4 Heterogeneous Collections

Using Protocol Buffers, it is quite an easy matter to specify fixed data structures and homogeneous vectors like one might find in languages like C++ and Java. It is however, quite another matter to interwork with these languages when requirements call for working with compound structures, arrays of compound structures, or unstructured collections (e.g. bags) of data.

At bottom, a wire-stream is nothing more than a concatenated stream of primitive wire type strings. As long as you can associate a tag with its host type in advance, you will have no difficulty in decoding the message. You do this by supplying the structure. Tell the parser what is possible and let the parser figure it out on its own, one production at a time. An example may be found in the appendix.

1.7 Groups (deprecated)

Protocol Buffer Groups provide a means for constructing unitary messages consisting of ad-hoc lists of terms. The following protobuf fragment shows the definition of a group carrying a complex number.

     Proto = group(2, [ double(1, Real_part), double(2, Img_part) ]).

Groups have been replaced by embedded messages, which are slightly less expensive to encode.

1.8 Advanced Topics

1.8.1 Precompiled Messages

Performance can be significantly improved using a strategy of precompiling the constant portions of your message. Enumerations for example, are excellent candidates for precompilation. Using protobuf_message/3, the precompiled portion of the message is inserted directly in the wire-stream on encode, and is unified with, and removed from the wire-stream on decode. The following shows how the "send_command" example above, can be converted to precompiled form:


:- dynamic precompiled_message/3.

send_precompiled_command(Command, Vector, Msg) :-
        basic_vector(Vector, Proto1),

        precompiled_message(commands(Command), Msg, Tail),

        protobuf_message(protobuf([embedded(3, Proto1)]), Tail).

precompile_commands :-
        abolish(precompiled_message/3),
        forall(protobufs:commands(Key, _),
              ( Proto = protobuf([atom(1, command),
                                  enum(2, commands(Key))]),
                protobuf_message(Proto, Msg, Tail),
                assert(precompiled_message(commands(Key), Msg, Tail))
              )),
        compile_predicates([precompiled_message/3]).

*
*
*
:- initialization
     precompile_commands.

1.8.2 Supplying Your Own Host Type Message Sequences

You can extend the parser to support your own compound host types. These are treated as first class entities by the parser. That is they can be used either by themselves, or in repeated and embedded clauses just as any other host type would be. You do this by hooking into the parser and adding your own message_sequence productions. Your hook eventually calls back into the parser with your substitution/expansion protobuf, which is then embedded in the wire stream. Recursive structures can be defined this way. A simple example of a recursive XML like structure is shown in the appendix.