• 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
        • Appendix (examples)
          • Example directories
          • Example: A Simple XML Like Structure
          • Example: Vectors of Numbers
          • Example: Heterogeneous Collections
        • library(protobufs): Google's Protocol Buffers ("protobufs")

2 Appendix (examples)

2.1 Example directories

The examples are in‘/usr/share/swi-prolog/doc/packages/examples/protobufs`, which is part of the swi-prolog-doc package. Each directory has a README. To run these, you will need to copy them to a writeable directory.

  • bootstrap - This contains the file common.mk file, which is used by the demo and interop Makefiles.
  • demo - the test goal runs some examples.
  • interop - used for testing interoperability with C++ and Python Additional tests are in test\_protobufs.pl.

    See also Addressbook example (section 1.3.3).

    The protobuf compiler (protoc) uses two protobuf formats to communicate with the plugin:

  • plugin.proto
  • descriptor.proto The Prolog code that were generated from these, as part of the bootstrap process, are:
  • plugin\_pb.pl
  • descriptor\_pb.pl

2.2 Example: A Simple XML Like Structure

This is an example of using the low-level interface for implementing a domain-specific language that maps to protobufs.

In this example we demonstrate managing a recursive structure like XML. The structure shown in xml_proto/1 below, is similar to the structure returned by load_xml_file/2, which is part of the SGML library. We supply three message_sequence decorators: kv_pair, xml_element, and aux_xml_element. These are treated as first class host types.

:- multifile protobufs:message_sequence//3.

protobufs:message_sequence(Type, Tag, Value)  -->
    { my_message_sequence(Type, Value, Proto) },
    protobufs:message_sequence(embedded, Tag, Proto), !.
%
% On encode, the value type determines the tag. And on decode
% the tag to determines the value type.
%

guard(Type, Value) :-
    ( nonvar(Value) -> is_of_type(Type, Value); true ).

my_message_sequence(kv_pair, Key=Value, Proto) :-
    Proto = protobuf([atom(30, Key), X]),
    ( ( guard(integer, Value), X = integer(31, Value) )
    ; ( guard(float, Value),   X = double(32,  Value) )
    ; ( guard(atom, Value),    X = atom(33,    Value)) ).

my_message_sequence(xml_element,
                    element(Name, Attributes, Contents), Proto) :-
    Proto = protobuf([ atom(21, Name),
                       repeated(22, kv_pair(Attributes)),
                       repeated(23, aux_xml_element(Contents))]).

my_message_sequence(aux_xml_element, Contents, Proto) :-
    Contents = element(_Name, _Attributes, _ElementContents),
    Proto = protobuf([xml_element(40, Contents)]).

my_message_sequence(aux_xml_element, Contents, Proto) :-
    Proto = protobuf([atom(43, Contents)]).

xml_proto([element(space1,
                   [foo='1', bar='2'],
                   [fum,
                    bar,
                    element(space2,
                            [fum=3.1415, bum= -14],
                            ['more stuff for you']),
                    element(space2b,
                            [],
                            [this, is, embedded, also]),
                    to,
                    you])]).

test_xml(X, Y) :-
    Proto = protobuf([repeated(20, xml_element(X))]),

    protobuf_message(Proto, Y).

% And test it:

?- xml_proto(X), test_xml(X,Y), test_xml(Z,Y), Z == X.
X = Z,
Z = [element(space1,
             [foo='1', bar='2'],
             [fum,
              bar,
              element(space2,
                      [fum=3.1415, bum= -14],
                      ['more stuff for you']
                    ),
              element(space2b,
                      [],
                      [this, is|...]
                     ),
              to,
              you])],
Y = [162, 1, 193, 1, 170, 1, 6, 115, 112|...],

A protobuf description that is compatible with the above wire stream follows:

message kv_pair {
  required string key = 30;
  optional sint64  int_value = 31;
  optional double float_value  = 32;
  optional string atom_value = 33;
}

message aux_xml_element {
  optional string atom = 43;
  optional xml_element element = 40;
}

message xml_element {
  required string name = 21;
  repeated kv_pair attributes = 22;
  repeated aux_xml_element contents = 23;
}

message XMLFile {
  repeated xml_element elements = 20;
}

Verify the wire stream using the protobuf compiler's decoder:

$ protoc --decode=XMLFile pb_vector.proto <tmp98.tmp
elements {
  name: "space1"
  attributes {
    key: "foo"
    atom_value: "1"
  }
  attributes {
    key: "bar"
    atom_value: "2"
  }
  contents {
    atom: "fum"
  }
  contents {
    atom: "bar"
  }
  contents {
    element {
      name: "space2"
      attributes {
        key: "fum"
        float_value: 3.1415
      }
      attributes {
        key: "bum"
        int_value: -14
      }
      contents {
        atom: "more stuff for you"
      }
    }
  }
  contents {
    element {
      name: "space2b"
      contents {
        atom: "this"
      }
      contents {
        atom: "is"
      }
      contents {
        atom: "embedded"
      }
      contents {
        atom: "also"
      }
    }
  }
  contents {
    atom: "to"
  }
  contents {
    atom: "you"
  }
}

2.3 Example: Vectors of Numbers

This is an example of using the low-level interface.

In the Prolog client:

vector_type(double(_List), 2).
vector_type(float(_List), 3).
vector_type(integer(_List), 4).
vector_type(integer64(_List), 5).
vector_type(integer32(_List), 6).
vector_type(unsigned(_List), 7).
vector_type(codes(_List), 8).
vector_type(atom(_List), 9).
vector_type(string(_List), 10).

vector(Type, B):-
    vector_type(Type, Tag),
    Proto = protobuf([ repeated(Tag, Type) ]),
    protobuf_message(Proto, B).

A protobuf description that is compatible with the above wire stream follows:

  message Vector {
  repeated double double_values     = 2;
  repeated float float_values       = 3;
  repeated sint32 integer_values    = 4;
  repeated fixed64 integer64_values = 5;
  repeated fixed32 integer32_values = 6;
  repeated uint32 unsigned_values   = 7;
  repeated bytes bytes_values       = 8;
  repeated string atom_values       = 9;
  repeated string string_values     = 10;
  }

A typical application might consist of an abstract adapter class along with a collection of concrete subclasses that refine an abstract behavior in order to hide the interaction with the underlying protobuf interpreter. An example of such a class written in C++ may be found in the demos.

On the Prolog side:

  :- meta_predicate ~>(0,0).
  :- op(950, xfy, ~>).

  ~>(P, Q) :-
    setup_call_cleanup(P, (true; fail), assertion(Q)).

  write_as_proto(Vector) :-
    vector(Vector, WireStream),
    open('tmp99.tmp', write, S, [encoding(octet),type(binary)])
      ~> close(S),
    format(S, '~s', [WireStream]), !.

  testv1(V) :-
    read_file_to_codes('tmp99.tmp', Codes, [encoding(octet),type(binary)]),
    vector(V, Codes).

Run the Prolog side:

?- X is pi,
   write_as_proto(double([-2.2212, -7.6675, X, 0, 1.77e-9, 2.54e222])).
X = 3.14159.

?- testv1(Vector).
Vector = double([-2.2212, -7.6675, 3.14159, 0.0, 1.77e-09, 2.54e+222])
?-

Verify the wire stream using the protobuf compiler's decoder:

$ protoc --decode=Vector pb_vector.proto <tmp99.tmp
double_values: -2.2212
double_values: -7.6675
double_values: 3.1415926535897931
double_values: 0
double_values: 1.77e-09
double_values: 2.5400000000000002e+222

2.4 Example: Heterogeneous Collections

This is an example of using the low-level interface.

The following example shows how one can specify a Protocol Buffer message that can deal with variable-length, unstructured bags of numbers:

compound_protobuf(complex(Real, Img), group(12, [double(1, Real), double(2, Img)])).
compound_protobuf(float(Val), float(13, Val)).
compound_protobuf(double(Val), double(14, Val)).
compound_protobuf((Num rdiv Den), group(15, [integer(1, Num), integer(2, Den)])).
compound_protobuf(integer(Val), integer(16, Val)).

protobuf_bag([], []).

protobuf_bag([ Type | More], WireCodes) :-
    compound_protobuf(Type, X),
    Proto = protobuf([embedded(1, protobuf([X]))]),
    protobuf_message(Proto, WireCodes, WireCodes1),
    protobuf_bag(More, WireCodes1), !.

Use it as follows:

?- protobuf_bag([complex(2,3), complex(4,5),
                 complex(6,7), 355 rdiv -113, integer(11)], X).

X = [10, 20, 99, 9, 0, 0, 0, 0, 0|...].

?- protobuf_bag(Y, $X).
Y = [complex(2.0, 3.0), complex(4.0, 5.0),
     complex(6.0, 7.0), 355 rdiv -113, integer(11)].

A protobuf description that is compatible with the above wire stream follows:

message compound_protobuf {
optional group Complex = 12 {
    required double real = 1;
    required double img = 2;
};
optional group Fraction = 15 {
    required sint64 num = 1;
    required sint64 den = 2;
};
optional float float = 13;
optional double double = 14;
optional sint32 integer = 16;
}

message protobuf_bag {
    repeated compound_protobuf bag = 1;

Verify the wire stream using the protobuf compiler's decoder:

$ protoc --decode=protobuf_bag pb_vector.proto <tmp96.tmp
bag {
  Complex {
    real: 2
    img: 3
  }
}
bag {
  Complex {
    real: 4
    img: 5
  }
}
bag {
  Complex {
    real: 6
    img: 7
  }
}
bag {
  Fraction {
    num: 355
    den: -113
  }
}
bag {
  integer: 11
}

ClioPatria (version V3.1.1-51-ga0b30a5)