• Places
    • Home
    • Graphs
    • Prefixes
  • Admin
    • Users
    • Settings
    • Plugins
    • Statistics
  • CPACK
    • Home
    • List packs
    • Submit pack
  • Repository
    • Load local file
    • Load from HTTP
    • Load from library
    • Remove triples
    • Clear repository
  • Query
    • YASGUI SPARQL Editor
    • Simple Form
    • SWISH Prolog shell
  • Help
    • Documentation
    • Tutorial
    • Roadmap
    • HTTP Services
  • Login

Google's Protocol Buffers Library
All Application Manual Name SummaryHelp

  • Documentation
    • Reference manual
    • Packages
      • Google's Protocol Buffers Library
        • Google's Protocol Buffers
          • Overview
          • Processing protobufs with Prolog
          • protoc
          • The low-level SWI-Prolog Implementation
        • Appendix (examples)
        • library(protobufs): Google's Protocol Buffers ("protobufs")

1 Google's Protocol Buffers

1.1 Overview

Protocol Buffers ("protobufs") 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.

See https://developers.google.com/protocol-buffers

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 Processing protobufs with Prolog

There are two ways you can use protobufs in Prolog: with a compiled ".proto" file and protobuf_parse_from_codes/3 and protobuf_serialize_to_codes/3; or with a lower-level interface protobuf_message/2, which allows you to define your own domain-specific language for parsing and serliazing protobufs.

1.3 protoc

A protobuf ".proto" file can be processed by the protobuf compiler (protoc), using a Prolog specific plugin. You can do this by either adding /usr/lib/swi-prolog/library/protobufs to your PATH or by specifying the option --plugin=protoc-gen-swipl=/usr/lib/swi-prolog/library/protobufs/protoc-gen-swipl. You specify where the generated files go with the --swipl_out option, which must be an existing directory.

When using protoc, it's important to specify the --protopath (or -I) and files correctly. The idea of protopath is that it gives a list of source "roots", and the files are specified relative to that. If you want to include the current directory, you must also specify it (e.g., protoc -I. swipl_out=. foo.proto). For example, when bootstrapping the "swipl" plugin, these are used:

protoc -I/usr/include --swipl_out=gen_pb google/include/descriptor.proto google/include/compiler/plugin.proto

which creates these files:

gen_pb/google/protobuf/descriptor_pb.pl
gen_pb/google/protobuf/compiler/plugin_pb.pl

The plugin_pb is used by:

:- use_module(gen_pb/google/protobuf/compiler/plugin_pb)

which has this (import is relative to the current module):

:- use_module('../descriptor_pb').

Each X.proto file generates a X_pb.pl file in the directory specified by --swipl_out. The file contains a module name X, some debugging information, and meta-data facts that go into the protobufs module (all the facts start with "proto_meta_") -- protobuf_parse_from_codes/3 uses these facts to parse the wire form of the message into a Prolog term and protobuf_serialize_to_codes/3 uses them to serialize the data to wire form.

The generated code does not rely on any Google-supplied code.

You must compile all the ".proto" files separately but you only need to load the top-level generated file -- it contains the necessary load directives for things that it uses. You can find out the dependencies for a .proto file by running PATH="$PATH:/usr/lib/swipl/library/protobufs" protoc -I... --dependency_out=FILE --swipl_out=. SRC.proto

1.3.1 protobuf_serialize_to_codes/3

The Prolog term corresponding to a protobuf message is a dict, with the keys corresponding to the field names in the message (the dict tag is treated as a comment). Repeated fields are represented as lists; enums are looked up and converted to atoms; bools are represented by false and true; strings are represented by Prolog strings or atoms; bytes are represented by lists of codes.

TODO: Add an option to omit default values (this is the proto3 behavior).

When serializing, the dict tag is treated as a comment and is ignored. So, you can use any dict tags when creating data for output. For example, both of these will generate the same output:

protobuf_serialize_to_codes(_{people:[_{id:1234,name:"John Doe"}]}, 'tutorial.AddressBook', WireCodes).
protobuf_serialize_to_codes('tutorial.AddressBook'{people:['tutorial.Person'{name:"John Doe",id:1234}]}, 'tutorial.AddressBook', WireCodes).

NOTE: if the wire codes can't be parsed, protobuf_parse_from_codes/3 fails. One common cause is if you give an incorrect field name. Typically, this shows up in a call to protobufs:field_segment/3, when protobufs:proto_meta_field_name/4 fails.

1.3.2 protobuf_parse_from_codes/3

This is the inverse of protobuf_serialize_to_codes/3 -- it takes a wire stream (list of codes) and creates a dict. The dict tags are the fully qualified names of the messages. Repeated fields that aren't in the wire stream get set to the value []; other fields that aren't in the wire stream get their default value (typically the empty string or zero, depending on type). Embedded messages and groups are omitted if not in the wire stream; you can test for their presence using get_dict/3. Enums are looked up and converted to atoms; bools are represented by false and true; strings are represented by Prolog strings (not atoms); bytes are represented by lists of codes.

There is no mechanism for determining whether a field was in the wire stream or not (that is, there is no equivalent of the Python implementation's HasField).

The "oneof" feature causes a slightly different behavior. Only the field that's in the wire stream gets set; the other fields are omitted. And if none of the fields in the "oneof" are set, then none of the fields appears. You can check which field is set by using get_dict/3.

Currently, there is no special support for the protobuf "map" feature. It is treated as an ordinary message field. The convenience predicates protobuf_field_is_map/3 and protobuf_map_pairs/3 can be used to convert between a "map" field and a key-value list, which gives you the freedom to use any kind of association list for the map. See also Issue #12 For example:

message MapMessage {
  map<string, sint64> number_ints = 5;
}

is treated as if it is

message MapMessage {
  message KeyValue {
    optional string  Key = 1;
    optional sint64  Value = 2;
  }
  repeated KeyValue number_ints = 5;
}

You can handle this on input by

protobuf_parse_from_codes(WireCodes, 'MapMessage', Term),
protobuf_map_pairs(Term.number_ints, _, Pairs).

and on output by

protobuf_map_pairs(TermNnumberInts, _, Pairs),
protobuf_serialize_to_codes(_{number_ints:TermNumberInts}, WireCodes).

1.3.3 addressbook example

The Google documentation has a tutorial example of a simple addressbook: https://developers.google.com/protocol-buffers/docs/tutorials The Prolog equivalent is in /usr/lib/swi-prolog/oc/packages/examples/protobufs/interop/addressbook.pl and you can run it by make run_addressbook, which will run protoc to generate the _pb.pl files and then run the example. The resulting file is addressbook.wire.

1.4 The low-level SWI-Prolog Implementation

For most users, protobuf_serialize_to_codes/3 and protobuf_parse_from_codes/3 suffice. However, if you need greater control, or wish to define your own domain-specific language that maps to protobufs, you can use protobuf_message/2.

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.

An example template is:

protobuf([
        unsigned(1, 100),
        string(2, "abcd"),
        repeated(3, atom([foo, bar])),
        boolean(4, true),
        embedded(5, protobuf([integer(1, -666), string(2, "negative 666")])),
        repeated(6, embedded([
            protobuf([integer(1, 1234), string(2, "onetwothreefour")]),
            protobuf([integer(1, 2222), string(2, "four twos")])])),
        repeated(7, integer([1,2,3,4])),
        packed(8, integer([5,6,7,8]))
    ])

This corresponds to a message created with this .proto definition (using proto2 syntax):

syntax = "proto2";
package my.protobuf;
message SomeMessage {
  optional int32 first = 1;  // example template also works with int64, uint32, uint64
  optional string second = 2;
  repeated string third = 3;
  optional bool fourth = 4;
  message NestedMessage {
    optional sint32 value = 1;
    optional string text = 2;
  }
  optional NestedMessage fifth = 5;
  repeated NestedMessage sixth = 6;
  repeated sint32 seventh = 7;
  repeated sint32 eighth = 8 [packed=true];
}

The wire format message can be displayed:

$ protoc --decode=my.protobuf.SomeMessage some_message.proto <some_message.wire
first: 100
second: "abcd"
third: "foo"
third: "bar"
fourth: true
fifth {
  value: -666
  text: "negative 666"
}
sixth {
  value: 1234
  text: "onetwothreefour"
}
sixth {
  value: 2222
  text: "four twos"
}
seventh: 1
seventh: 2
seventh: 3
seventh: 4
eighth: 100
eighth: -200
eighth: 1000

and the actual message would be created in Python by code similar to this:

import some_message_pb2

msg = some_message_pb2.SomeMessage()
msg.first = 100
msg.second = "abcd"
msg.third[:] = ["foo", "bar"]
msg.fourth = True
msg.fifth.value = -666
msg.fifth.text = "negative 666"

m1 = msg.sixth.add()
m1.value = 1234
m1.text = "onetwothreefour"
msg.sixth.append(msg.NestedMessage(value=2222, text="four twos"))
msg.seventh.extend([1,2,3,4])
msg.eighth.extend([100,-200,1000])

or

msg2 = some_message_pb2.SomeMessage(
    first = 100,
    second = "abcd",
    third = ["foo", "bar"],
    fourth = True,
    fifth = some_message_pb2.SomeMessage.NestedMessage(value=-666, text="negative 666"),
    sixth = [some_message_pb2.SomeMessage.NestedMessage(value=1234, text="onetwothreefour"),
             some_message_pb2.SomeMessage.NestedMessage(value=2222, text="four twos")],
    seventh = [1,2,3,4],
    eighth = [100,-200,1000],
    )

Note that the fields can be in any order (they are disambiguated by their tags) and if there is no value for a field, it would be simply omitted in the template. The field names and message names can be changed without any change to the wire format.

1.4.1 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 (field number), 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 the types in the .proto file and the primitives used in the wire-stream. For how these correspond to other programming languages, such as C++, Java, etc. see Protocol Buffers Scalar Value Types, which also has advice on how to choose between the various integer types. (Python3 types are also given here, because Python is used in some of the interoperability tests.)

Prolog Wirestream .proto file C++ Python3 Notes
doublefixed64doubledoublefloat
unsigned64fixed64fixed64uint64int
integer64fixed64sfixed64int64
floatfixed32floatfloatfloat
unsigned32fixed32fixed32uint32int
integer32fixed32sfixed32int32
integervarintsint32int32int1, 2, 9
integervarintsint64int64int1, 2, 9
signed32varintint32int32int2, 3, 10
signed64varintint64int64int2, 3, 10
unsignedvarintuint32uint32int2, 3
unsignedvarintuint64uint64int2, 3
booleanvarintboolboolbool2, 8
enumvarint(enum)(enum)(enum)
atomlength delimitedstringstr (unicode)
codeslength delimitedbytesbytes
utf8_codeslength delimitedstringstr (unicode)
stringlength delimitedstringstringstr (unicode)
embeddedlength delimitedmessage(class)5
repeatedlength delimitedrepeated(list)6
repeated_embeddedlength delimitedrepeated(list)11
packedlength delimitedpacked repeated(list)

Notes:

  1. Encoded using a compression technique known as zig-zagging, which is more efficient for negative values, but which is slightly less efficient if you know the values will always be non-negative.
  2. Encoded as a modulo 128 string. Its length is proportional to its magnitude. The intrinsic word length is decoupled between parties. If zig-zagging is not used (see note 1), negative numbers become maximum length.
  3. SWI-Prolog has unbounded integers, so an unsigned integer isn't a special case (it is range-checked and an exception thrown if its representation would require more than 32 or 64 bits).
  4. Encoded as UTF8 in the wire-stream.
  5. Specified as embedded(Tag,protobuf([...])).
  6. Specified as repeated(Tag,Type([...,...])), where Type is =unsigned, integer, string, etc.
  7. repeated ... [packed=true] in proto2. Can not contain "length delimited" types.
  8. Prolog boolean(Tag,false) maps to 0 and boolean(Tag,true) maps to 1.
  9. Uses "zig-zag" encoding, which is more space-efficient for negative numbers.
  10. The documentation says that this doesn't use "zig-zag" encoding, so it's less space-efficient for negative numbers. In particular, both C++ and Python encode negative numbers as 10 bytes, and this implementation does the same for wire-stream compatibility (note that SWI-Prolog typically uses 64-bit integers anyway). Therefore, signed64 is used for both .proto types int32 and int64.
  11. Specified as repeated_embedded(Tag,protobuf([...]),Fields)

1.4.2 Tags (field numbers)

A tag (or field number) 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. The protobuf specification requires that each field within a message has a unique field number; the protobuf compiler (protoc) will produce an error if a field number is reused (field numbers are unique only within a message; an embedded message can use the same field numbers without ambigituity).

1.4.3 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 (field number), which must always be ground, and argument 2 is its associated value, which may or may not be ground.

A protobuf "message" is a list of fields and is encoded in the template as protobufs([Field1, Field2, ...]), where each field is of the form Type(Tag,Value and Type can be any scalar or compound type.

Scalar fields are encoded as Type(Tag,Value). For example, if a field is defined in a .proto file by optional string some_field = 10, then it could be encoded by string(10,"some field's contents") or by atom(10, 'some field\'s contents').

Repeated fields are done by repeated(Tag,Type([Value1,Value2,...]), where Type is any type.

Embedded messages are done by embedded(Tag,protobuf([Field1,Field2,...])) (this is the same =protobuf(...)= as is used at the top level).

Repeated embedded messages are done by repeated_embedded(Tag,protobuf([Field1,Field2,...]),Fields), which gets repeated items and combines them into a list. For example, repeated_embedded(Tag, protobuf([string(1,_Key),string(2,_Value)]), Fields) could unify Fields to [protobuf([string(1,"key1"),string(2,"value1")]), protobuf([string(1,"key2"),string(2,"value2")])]. Note that the variables in the protobuf part of the term do not get instantiated: they are similar to the Template in findall/3 and similar.

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.

Assume a .proto definition:

message Command {
  optional string msg_type = 1;
  optional string command  = 2;
  optional int32  x        = 3;
  optional int32  y        = 4;
}

Map a Prolog structure to a Protocol Buffer:

%! command(+Term, -Proto) is det.
% Map a Prolog term to a corresponding protobuf term.
command(add(X,Y), Proto) :-
   freeze(X, must_be(integer, X)),  % for debugging
   freeze(Y, must_be(integer, Y)),  % for debugging
   Proto = protobuf([atom(1, command),
                     atom(2, add),
                     integer(3, X),
                     integer(4, Y)
                    ]).

Later on:

   ... prepare X, Y for command/2 ...

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

   % send the message
   open('filename', write, Stream, [encoding(octet),type(binary)]),
   format(Stream, '~s', [WireCodes]),
   close(Stream)

Proto is the protobuf template. Each template describes exactly one message. WireCodes is the wire-stream, which encodes bytes (values between 0 and 255 inclusive). 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.4.4 Alternation, Aggregation, Encapsulation, and Enumeration

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.

Note that required and optional have been removed from the proto3 specification, making all fields optional. This has been partially revised in releases 3.12 and later. In general, you should not expect any field to exist, nor can you expect a repeated field to have at least one item.

Also note that the handling of missing fields is slightly different in proto2 and proto3 -- proto2 allows specifying a default value but proto3 uses 0 and =""= as defaults for numbers and strings and omits encoding any field that has one of those default values.

TODO: determine correct behvaior for oneof with a default field value.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, all the 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.

You can also encode vectors of embedded messages using repeated_embedded. This uses a "template" for the individual messages and a list of messages in the wire stream. For example: repeated_embedded(Tag, protobuf([string(1,_Key),string(2,_Value)]), Fields) where Fields gets a list (possibly empty), with each item of the form protobuf([string(1,_Key),string(2,_Value)]).

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.

An omitted optional field is handled the same way as a repeated field with an empty set.

The protobuf grammar provides a variant of the repeated field known as "packed." This is represented similar to repeated, e.g.:

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

Handling missing fields

For input, you can wrap fields in repeated, so that if a field is there, it gets a length-1 list and if it's missing, an empty list:

?- Codes = [82,9,105,110,112,117,116,84,121,112,101],
   protobuf_message(protobuf([embedded(10, protobuf([repeated(13, integer64(I))]))]),  Codes),
   protobuf_message(protobuf([embedded(10, protobuf([repeated(13, double(D))]))]),  Codes),
   protobuf_message(protobuf([repeated(10, string(S))]), Codes).
I = [7309475598860382318],
D = [4.272430685433854e+180],
S = ["inputType"].
?- Codes = [82,9,105,110,112,117,116,84,121,112,101],
      protobuf_message(protobuf([repeated(10, string(S)),
                                 repeated(11, integer64(I))]), Codes).
S = ["inputType"],
I = [].

This technique can also be used for output - a missing field simply produces nothing in the wire format:

?- protobuf_message(protobuf([repeated(10, string([]))]), Codes).
Codes = [].
?- protobuf_message(protobuf([repeated(10, string(S))]), []).
S = [].

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 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, WireCodes) :-
    basic_vector(Vector, Proto1),
    Proto = protobuf([enum(1, commands(Command)),
                      embedded(2, Proto1)]),
    protobuf_message(Proto, WireCodes).

Use it as follows:

?- send_command(square, double([1,22,3,4]), WireCodes).
WireCodes = [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, $WireCodes).
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. Google's own Golden Message unit-test framework has enumerations encoded as regular integers, without the "zigzag" encoding. Therefore, negative values are space-inefficient, but they are allowed.

An earlier version of protobuf_message/2 assumed that enumeration values could not be zero, and there might still be incorrect assumptions in the code, resulting in either exceptions or silent failure.Heterogeneous Collections

Using Protocol Buffers, it is easy 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.4.5 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.4.6 Advanced Topics

Precompiled Messages

Performance can be 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:

send_precompiled_command(Command, Vector, WireCodes) :-
    basic_vector(Vector, Proto1),
    % precompiled_message/3 is created by term_expansion
    precompiled_message(commands(Command), WireCodes, Tail),
    protobuf_message(protobuf([embedded(3, Proto1)]), Tail).

term_expansion(precompile_commands, Clauses) :-
    findall(precompiled_message(commands(Key), WireCodes, Tail),
            (   protobufs:commands(Key, _),
                Proto = protobuf([atom(1, command),
                                  enum(2, commands(Key))]),
                protobuf_message(Proto, WireCodes, Tail)
            ),
            Clauses).

*
*
*
precompile_commands.  % Trigger the term-expansion precompilation

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.

ClioPatria (version V3.1.1-51-ga0b30a5)