34
35:- module(protobufs,
36 [ protobuf_message/2, 37 protobuf_message/3 38 ]). 39:- autoload(library(error),[must_be/2]). 40:- autoload(library(lists),[append/3]). 41:- autoload(library(utf8),[utf8_codes/3]).
78:- use_foreign_library(foreign(protobufs)). 79
80wire_type(varint, 0).
81wire_type(fixed64, 1).
82wire_type(length_delimited, 2).
83wire_type(start_group, 3).
84wire_type(end_group, 4).
85wire_type(fixed32, 5).
86
90
91fixed_int32(X, [A0, A1, A2, A3 | Rest], Rest) :-
92 int32_codes(X, [A0, A1, A2, A3]).
93
94fixed_int64(X, [A0, A1, A2, A3, A4, A5, A6, A7 | Rest], Rest) :-
95 int64_codes(X, [A0, A1, A2, A3, A4, A5, A6, A7]).
96
97fixed_float64(X, [A0, A1, A2, A3, A4, A5, A6, A7 | Rest], Rest) :-
98 float64_codes(X, [A0, A1, A2, A3, A4, A5, A6, A7]).
99
100fixed_float32(X, [A0, A1, A2, A3 | Rest], Rest) :-
101 float32_codes(X, [A0, A1, A2, A3]).
102
106
107code_string(N, Codes, Rest, Rest1) :-
108 length(Codes, N),
109 append(Codes, Rest1, Rest),
110 !.
123
124var_int(A, [A | Rest], Rest) :-
125 A < 128,
126 !.
127var_int(X, [A | Rest], Rest1) :-
128 nonvar(X),
129 X1 is X >> 7,
130 A is 128 + (X /\ 0x7f),
131 var_int(X1, Rest, Rest1),
132 !.
133var_int(X, [A | Rest], Rest1) :-
134 var_int(X1, Rest, Rest1),
135 X is (X1 << 7) + A - 128,
136 !.
139
140tag_type(Tag, Type, Rest, Rest1) :-
141 nonvar(Tag), nonvar(Type),
142 wire_type(Type, X),
143 A is Tag << 3 \/ X,
144 var_int(A, Rest, Rest1),
145 !.
146tag_type(Tag, Type, Rest, Rest1) :-
147 var_int(A, Rest, Rest1),
148 X is A /\ 0x07,
149 wire_type(Type, X),
150 Tag is A >> 3.
152prolog_type(Tag, double) --> tag_type(Tag, fixed64).
153prolog_type(Tag, integer64) --> tag_type(Tag, fixed64).
154prolog_type(Tag, float) --> tag_type(Tag, fixed32).
155prolog_type(Tag, integer32) --> tag_type(Tag, fixed32).
156prolog_type(Tag, integer) --> tag_type(Tag, varint).
157prolog_type(Tag, unsigned) --> tag_type(Tag, varint).
158prolog_type(Tag, boolean) --> tag_type(Tag, varint).
159prolog_type(Tag, enum) --> tag_type(Tag, varint).
160prolog_type(Tag, atom) --> tag_type(Tag, length_delimited).
161prolog_type(Tag, codes) --> tag_type(Tag, length_delimited).
162prolog_type(Tag, utf8_codes) --> tag_type(Tag, length_delimited).
163prolog_type(Tag, string) --> tag_type(Tag, length_delimited).
164prolog_type(Tag, embedded) --> tag_type(Tag, length_delimited).
170:- meta_predicate enumeration(1,*,*). 171
172enumeration(Type) -->
173 { call(Type, Value) },
174 payload(unsigned, Value).
175
176payload(enum, A) -->
177 enumeration(A).
178payload(double, A) -->
179 fixed_float64(A).
180payload(integer64, A) -->
181 fixed_int64(A).
182payload(float, A) -->
183 fixed_float32(A).
184payload(integer32, A) -->
185 fixed_int32(A).
186payload(integer, A) -->
187 { nonvar(A), integer_zigzag(A,X) },
188 !,
189 var_int(X).
190payload(integer, A) -->
191 var_int(X),
192 { integer_zigzag(A, X) }.
193payload(unsigned, A) -->
194 { nonvar(A)
195 -> A >= 0
196 ; true
197 },
198 var_int(A).
199payload(codes, A) -->
200 { nonvar(A), !, length(A, Len)},
201 var_int(Len),
202 code_string(Len, A).
203payload(codes, A) -->
204 var_int(Len),
205 code_string(Len, A).
206payload(utf8_codes, A) -->
207 { nonvar(A),
208 !,
209 phrase(utf8_codes(A), B)
210 },
211 payload(codes, B).
212payload(utf8_codes, A) -->
213 payload(codes, B),
214 { phrase(utf8_codes(A), B) }.
215payload(atom, A) -->
216 { nonvar(A),
217 atom_codes(A, Codes)
218 },
219 payload(utf8_codes, Codes),
220 !.
221payload(atom, A) -->
222 payload(utf8_codes, Codes),
223 { atom_codes(A, Codes) }.
224payload(boolean, true) -->
225 payload(unsigned, 1).
226payload(boolean, false) -->
227 payload(unsigned, 0).
228payload(string, A) -->
229 { nonvar(A)
230 -> string_codes(A, Codes)
231 ; true
232 },
233 payload(codes, Codes),
234 { string_codes(A, Codes) }.
235payload(embedded, protobuf(A)) -->
236 { ground(A),
237 phrase(protobuf(A), Codes)
238 },
239 payload(codes, Codes),
240 !.
241payload(embedded, protobuf(A)) -->
242 payload(codes, Codes),
243 { phrase(protobuf(A), Codes) }.
244
245start_group(Tag) --> tag_type(Tag, start_group).
246
247end_group(Tag) --> tag_type(Tag, end_group).
250nothing([]) --> [], !.
251
252protobuf([A | B]) -->
253 { A =.. [ Type, Tag, Payload] },
254 message_sequence(Type, Tag, Payload),
255 !,
256 ( protobuf(B)
257 ; nothing(B)
258 ).
259
260
261repeated_message_sequence(repeated_enum, Tag, Type, [A | B]) -->
262 { Compound =.. [Type, A] },
263 message_sequence(enum, Tag, Compound),
264 ( repeated_message_sequence(repeated_enum, Tag, Type, B)
265 ; nothing(B)
266 ).
267repeated_message_sequence(Type, Tag, [A | B]) -->
268 message_sequence(Type, Tag, A),
269 repeated_message_sequence(Type, Tag, B).
270repeated_message_sequence(_Type, _Tag, A) -->
271 nothing(A).
272
273
274message_sequence(repeated, Tag, enum(Compound)) -->
275 { Compound =.. [ Type, List] },
276 repeated_message_sequence(repeated_enum, Tag, Type, List).
277message_sequence(repeated, Tag, Compound) -->
278 { Compound =.. [Type, A] },
279 repeated_message_sequence(Type, Tag, A).
280message_sequence(group, Tag, A) -->
281 start_group(Tag),
282 protobuf(A),
283 end_group(Tag),
284 !.
285message_sequence(PrologType, Tag, Payload) -->
286 prolog_type(Tag, PrologType),
287 payload(PrologType, Payload).
307protobuf_message(protobuf(Template), Wirestream) :-
308 must_be(list, Template),
309 phrase(protobuf(Template), Wirestream),
310 !.
311
312protobuf_message(protobuf(Template), Wirestream, Residue) :-
313 must_be(list, Template),
314 phrase(protobuf(Template), Wirestream, Residue)
Google's Protocol Buffers
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 and decode 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 and tool set. In SWI-Prolog, you define your message template as a list of predefined Prolog terms that correspond to production rules in the Definite Clause Grammar (DCG) that realizes the interpreter. Each production rule has an equivalent rule in the protobuf grammar. The process is not unlike specifiying the format of a regular expression. To encode a template to a wire-stream, you pass a grounded template,
X
, and variable,Y
, to protobuf_message/2. To decode a wire-stream,Y
, 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.For an overview and tutorial with examples, see
protobufs_overview.txt
. Examples of usage may also be found by inspectingtest_protobufs.pl
.