View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jeffrey Rosenwald, extended by Peter Ludemann
    4    E-mail:        jeffrose@acm.org, peter.ludemann@gmail.com
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2013, Jeffrey Rosenwald;
    7                   2021-2025, SWI-Prolog Solutions b.v.
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(protobufs,
   37          [ protobuf_message/2,   % ?Template ?Codes
   38            protobuf_message/3,   % ?Template ?Codes ?Rest
   39            protobuf_parse_from_codes/3, % +WireCodes, +MessageType, -Term
   40            protobuf_serialize_to_codes/3,  % +Term, +MessageType, -WireCodes
   41            protobuf_field_is_map/2, % +MessageType, +FieldName
   42            protobuf_map_pairs/3 % ?ProtobufTermList, ?DictTag, ?Pairs
   43
   44            % TODO: Restore the following to the public interface, if
   45            %       someone needs them.  For now, the tests directly specify
   46            %       them using, e.g. protobufs:uint32_codes(..., ...).
   47            %
   48            % protobuf_segment_message/2,  % ?Segments ?Codes
   49            % protobuf_segment_convert/2,  % +Form1 ?Form2
   50            % uint32_codes/2,
   51            % int32_codes/2,
   52            % float32_codes/2,
   53            % uint64_codes/2,
   54            % int64_codes/2,
   55            % float64_codes/2,
   56            % int64_zigzag/2,
   57            % uint32_int32/2,
   58            % uint64_int64/2,
   59            % uint32_codes_when/2,
   60            % int32_codes_when/2,  % TODO: unused
   61            % float32_codes_when/2,
   62            % uint64_codes_when/2,
   63            % int64_codes_when/2,  % TODO: unused
   64            % float64_codes_when/2,
   65            % int64_zigzag_when/2,
   66            % uint32_int32_when/2,
   67            % uint64_int64_when/2,
   68            % int64_float64_when/2,
   69            % int32_float32_when/2,
   70            % protobuf_var_int//1,
   71            % protobuf_tag_type//2
   72          ]).   73
   74:- use_module(library(apply_macros)).  % autoload(library(apply), [maplist/3, foldl/4]).
   75:- autoload(library(error), [must_be/2, domain_error/2, existence_error/2]).   76:- autoload(library(lists), [append/3]).   77:- autoload(library(utf8), [utf8_codes//1]).   78:- autoload(library(dif), [dif/2]).   79:- autoload(library(dcg/high_order), [sequence//2]).   80:- autoload(library(when), [when/2]).   81:- use_module(library(debug), [assertion/1]). % TODO: remove
   82
   83:- set_prolog_flag(optimise, true). % For arithmetic using is/2.
   84
   85/** <module> Google's Protocol Buffers ("protobufs")
   86
   87Protocol  buffers  are  Google's    language-neutral,  platform-neutral,
   88extensible mechanism for serializing structured data  --  think XML, but
   89smaller, faster, and simpler. You define how   you  want your data to be
   90structured once. This takes the form of   a  template that describes the
   91data structure. You use this template  to   encode  and decode your data
   92structure into wire-streams that may be sent-to or read-from your peers.
   93The underlying wire stream is platform independent, lossless, and may be
   94used to interwork with a variety of  languages and systems regardless of
   95word size or endianness. Techniques  exist   to  safely extend your data
   96structure without breaking deployed programs   that are compiled against
   97the "old" format.
   98
   99The idea behind Google's Protocol Buffers is that you define your
  100structured messages using a domain-specific language and tool
  101set. Further documentation on this is at
  102[https://developers.google.com/protocol-buffers](https://developers.google.com/protocol-buffers).
  103
  104There are two ways you can use protobufs in Prolog:
  105  * with a compiled =|.proto|= file: protobuf_parse_from_codes/3 and
  106    protobuf_serialize_to_codes/3.
  107  * with a lower-level interface protobuf_message/2, which allows you
  108    to define your own domain-specific language for parsing and
  109    serializing protobufs.
  110
  111The protobuf_parse_from_codes/3 and protobuf_serialize_to_codes/3
  112interface translates between a "wire stream" and a Prolog term. This
  113interface takes advantage of SWI-Prolog's
  114[dict](</pldoc/man?section=bidicts>).
  115The =protoc= plugin (=protoc-gen-swipl=) generates a
  116Prolog file of meta-information that captures the =|.proto|= file's
  117definition in the =protobufs= module, with the following facts:
  118   * =|proto_meta_normalize(Unnormalized, Normalized)|=
  119   * =|proto_meta_package(Package, FileName, Options)|=
  120   * =|proto_meta_message_type(Fqn, Package, Name)|=
  121   * =|proto_meta_message_type_map_entry(Fqn)|=
  122   * =|proto_meta_field_name(Fqn, FieldNumber, FieldName, FqnName)|=
  123   * =|proto_meta_field_json_name(FqnName, JsonName)|=
  124   * =|proto_meta_field_label(FqnName, LabelRepeatOptional) % 'LABEL_OPTIONAL', 'LABEL_REQUIRED', 'LABEL_REPEATED'|=
  125   * =|proto_meta_field_type(FqnName, Type) % 'TYPE_INT32', 'TYPE_MESSAGE', etc|=
  126   * =|proto_meta_field_type_name(FqnName, TypeName)|=
  127   * =|proto_meta_field_default_value(FqnName, DefaultValue)|=
  128   * =|proto_meta_field_option_packed(FqnName)|=
  129   * =|proto_meta_enum_type(FqnName, Fqn, Name)|=
  130   * =|proto_meta_enum_value(FqnName, Name, Number)|=
  131   * =|proto_meta_field_oneof_index(FqnName, Index)|=
  132   * =|proto_meta_oneof(FqnName, Index, Name)|=
  133
  134The protobuf_message/2 interface allows you to define your message
  135template as a list of predefined
  136Prolog terms that correspond to production  rules in the Definite Clause
  137Grammar (DCG) that realizes the interpreter. Each production rule has an
  138equivalent rule in the  protobuf  grammar.   The  process  is not unlike
  139specifiying the format of a regular  expression. To encode a template to
  140a wire-stream, you pass a grounded template, =X=, and  variable, =Y=, to
  141protobuf_message/2. To decode a wire-stream, =Y=, you pass an ungrounded
  142template, =X=,  along  with  a   grounded    wire-stream,   =Y=,  to
  143protobuf_message/2. The interpreter will unify  the unbound variables in
  144the template with values decoded from the wire-stream.
  145
  146For an overview and tutorial with examples, see
  147[library(protobufs): Google's Protocol Buffers](#protobufs-main)
  148Examples of usage may also be found by inspecting
  149[[test_protobufs.pl][https://github.com/SWI-Prolog/contrib-protobufs/blob/master/test_protobufs.pl]]
  150and the
  151[[demo][https://github.com/SWI-Prolog/contrib-protobufs/tree/master/demo]]
  152directory, or by looking at the "addressbook" example that is typically
  153installed at
  154/usr/lib/swi-prolog/doc/packages/examples/protobufs/interop/addressbook.pl
  155
  156@see https://developers.google.com/protocol-buffers
  157@see https://developers.google.com/protocol-buffers/docs/encoding
  158@author Jeffrey Rosenwald (JeffRose@acm.org)
  159@author Peter Ludemann (peter.ludemann@gmail.org)
  160@compat SWI-Prolog
  161*/
  162
  163:- use_foreign_library(foreign(protobufs)).  164
  165%! protobuf_parse_from_codes(+WireCodes:list(int), +MessageType:atom, -Term) is semidet.
  166% Process bytes (list of int) that is the serialized form of a message (designated
  167% by =MessageType=), creating a Prolog term.
  168%
  169% =Protoc= must have been run (with the =|--swipl_out=|= option and the resulting
  170% top-level _pb.pl file loaded. For more details, see the "protoc" section of the
  171% overview documentation.
  172%
  173% Fails if the message can't be parsed or if the appropriate meta-data from =protoc=
  174% hasn't been loaded.
  175%
  176% All fields that are omitted from the =WireCodes= are set to their
  177% default values (typically the empty string or 0, depending on the
  178% type; or =|[]|= for repeated groups). There is no way of testing
  179% whether a value was specified in =WireCodes= or given its default
  180% value (that is, there is no equivalent of the Python
  181% implementation's =HasField`). Optional embedded messages and groups
  182% do not have any default value -- you must check their existence by
  183% using get_dict/3 or similar. If a field is part of a "oneof" set,
  184% then none of the other fields is set. You can determine which field
  185% had a value by using get_dict/3.
  186%
  187% @tbd document the generated terms (see library(json) and json_read_dict/3)
  188% @tbd add options such as =true= and =value_string_as= (similar to json_read_dict/3)
  189% @tbd add option for form of the [dict](</pldoc/man?section=bidicts>) tags (fully qualified or not)
  190% @tbd add option for outputting fields in the C++/Python/Java order
  191%       (by field number rather than by field name).
  192%
  193% @bug Ignores =|.proto|= [extensions](https://developers.google.com/protocol-buffers/docs/proto#extensions).
  194% @bug =map= fields don't get special treatment (but see protobuf_map_pairs/3).
  195% @bug Generates fields in a different order from the C++, Python,
  196%      Java implementations, which use the field number to determine
  197%      field order whereas currently this implementation uses field
  198%      name.  (This isn't stricly speaking a bug, because it's allowed
  199%      by the specification; but it might cause some surprise.)
  200%
  201% @param WireCodes Wire format of the message from e.g., read_stream_to_codes/2.
  202%          (The stream should have options `encoding(octet)` and `type(binary)`,
  203%          either as options to read_file_to_codes/3 or by calling set_stream/2
  204%          on the stream to read_stream_to_codes/2.)
  205% @param MessageType Fully qualified message name (from the =|.proto|= file's =package= and =message=).
  206%        For example, if the =package= is =google.protobuf= and the
  207%        message is =FileDescriptorSet=, then you would use
  208%        =|'.google.protobuf.FileDescriptorSet'|= or =|'google.protobuf.FileDescriptorSet'|=.
  209%        If there's no package name, use e.g.: =|'MyMessage|= or =|'.MyMessage'|=.
  210%        You can see the packages by looking at
  211%        =|protobufs:proto_meta_package(Pkg,File,_)|=
  212%        and the message names and fields by
  213%        =|protobufs:proto_meta_field_name('.google.protobuf.FileDescriptorSet',
  214%        FieldNumber, FieldName, FqnName)|= (the initial '.' is not optional for these facts,
  215%        only for the top-level name given to protobuf_serialize_to_codes/3).
  216% @param Term The generated term, as nested [dict](</pldoc/man?section=bidicts>)s.
  217% @see  [library(protobufs): Google's Protocol Buffers](#protobufs-serialize-to-codes)
  218% @error version_error(Module-Version) you need to recompile the =Module=
  219%        with a newer version of =|protoc|=.
  220protobuf_parse_from_codes(WireCodes, MessageType0, Term) :-
  221    verify_version,
  222    must_be(ground, MessageType0),
  223    (   proto_meta_normalize(MessageType0, MessageType)
  224    ->  true
  225    ;   existence_error(protobuf_package, MessageType0)
  226    ),
  227    protobuf_segment_message(Segments, WireCodes),
  228    % protobuf_segment_message/2 can leave choicepoints, backtracking
  229    % through all the possibilities would have combinatoric explosion;
  230    % instead use segment_to_term/3 call protobuf_segment_convert/2 to
  231    % change segments that were guessed incorrectly.
  232    !,
  233    maplist(segment_to_term(MessageType), Segments, MsgFields),
  234    !, % TODO: remove
  235    combine_fields(MsgFields, MessageType{}, Term),
  236    !. % TODO: remove? - but proto_meta might have left choicepoints if loaded twice
  237
  238verify_version :-
  239    (   protoc_gen_swipl_version(Module, Version),
  240        Version @< [0,9,1] % This must be sync-ed with changes to protoc-gen-swipl
  241    ->  throw(error(version_error(Module-Version), _))
  242    ;   true
  243    ).
  244
  245%! protobuf_serialize_to_codes(+Term:dict, -MessageType:atom, -WireCodes:list(int)) is det.
  246% Process a Prolog term into bytes (list of int) that is the serialized form of a
  247% message (designated by =MessageType=).
  248%
  249% =Protoc= must have been run (with the =|--swipl_out=|= option and the resulting
  250% top-level _pb.pl file loaded. For more details, see the "protoc" section of the
  251% overview documentation.
  252%
  253% Fails if the term isn't of an appropriate form or if the appropriate
  254% meta-data from =protoc= hasn't been loaded, or if a field name is incorrect
  255% (and therefore nothing in the meta-data matches it).
  256%
  257% @bug =map= fields don't get special treatment (but see protobuf_map_pairs/3).
  258% @bug =oneof= is not checked for validity.
  259%
  260% @param Term The Prolog form of the data, as nested [dict](</pldoc/man?section=bidicts>)s.
  261% @param MessageType Fully qualified message name (from the =|.proto|= file's =package= and =message=).
  262%        For example, if the =package= is =google.protobuf= and the
  263%        message is =FileDescriptorSet=, then you would use
  264%        =|'.google.protobuf.FileDescriptorSet'|= or =|'google.protobuf.FileDescriptorSet'|=.
  265%        If there's no package name, use e.g.: =|'MyMessage|= or =|'.MyMessage'|=.
  266%        You can see the packages by looking at
  267%        =|protobufs:proto_meta_package(Pkg,File,_)|=
  268%        and the message names and fields by
  269%        =|protobufs:proto_meta_field_name('.google.protobuf.FileDescriptorSet',
  270%        FieldNumber, FieldName, FqnName)|= (the initial '.' is not optional for these facts,
  271%        only for the top-level name given to protobuf_serialize_to_codes/3).
  272% @param WireCodes Wire format of the message, which can be output using
  273%        =|format('~s', [WireCodes])|=.
  274% @see [library(protobufs): Google's Protocol Buffers](#protobufs-serialize-to-codes)
  275% @error version_error(Module-Version) you need to recompile the =Module=
  276%        with a newer version of =|protoc|=.
  277% @error existence_error if a field can't be found in the meta-data
  278protobuf_serialize_to_codes(Term, MessageType0, WireCodes) :-
  279    verify_version,
  280    must_be(ground, MessageType0),
  281    (   proto_meta_normalize(MessageType0, MessageType)
  282    ->  true
  283    ;   existence_error(protobuf_package, MessageType0)
  284    ),
  285    term_to_segments(Term, MessageType, Segments),
  286    !, % TODO: remove
  287    protobuf_segment_message(Segments, WireCodes),
  288    !. % TODO: remove? - but proto_meta might have left choicepoints if loaded twice
  289
  290%
  291% Map wire type (atom) to its encoding (an int)
  292%
  293wire_type(varint,            0). % for int32, int64, uint32, uint64, sint32, sint64, bool, enum
  294wire_type(fixed64,           1). % for fixed64, sfixed64, double
  295wire_type(length_delimited,  2). % for string, bytes, embedded messages, packed repeated fields
  296wire_type(start_group,       3). % for groups (deprecated)
  297wire_type(end_group,         4). % for groups (deprecated)
  298wire_type(fixed32,           5). % for fixed32, sfixed32, float
  299
  300%
  301%  basic wire-type processing handled by C-support code in DCG-form
  302%
  303
  304fixed_uint32(X, [A0, A1, A2, A3 | Rest], Rest) :-
  305    uint32_codes_when(X, [A0, A1, A2, A3]).
  306/* equivalent to:
  307fixed_uint32_(X) -->
  308  [ A0,A1,A2,A3 ],
  309  { uint32_codes_when(X, [A0,A1,A2,A3]) }.
  310*/
  311
  312fixed_uint64(X, [A0, A1, A2, A3, A4, A5, A6, A7 | Rest], Rest) :-
  313    uint64_codes_when(X, [A0, A1, A2, A3, A4, A5, A6, A7]).
  314
  315fixed_float64(X, [A0, A1, A2, A3, A4, A5, A6, A7 | Rest], Rest) :-
  316    float64_codes_when(X, [A0, A1, A2, A3, A4, A5, A6, A7]).
  317
  318fixed_float32(X, [A0, A1, A2, A3 | Rest], Rest) :-
  319    float32_codes_when(X, [A0, A1, A2, A3]).
  320
  321%
  322%   Start of the DCG
  323%
  324
  325code_string(N, Codes, Rest, Rest1) :-
  326    length(Codes, N),
  327    append(Codes, Rest1, Rest),
  328    !.
  329/*
  330code_string(N, Codes) -->
  331        { length(Codes, N) },
  332        Codes, !.
  333*/
  334
  335%
  336% deal with Google's method of packing unsigned integers in variable
  337% length, modulo 128 strings.
  338%
  339% protobuf_var_int//1 and protobuf_tag_type//2 productions were rewritten in straight
  340% Prolog for speed's sake.
  341%
  342
  343%! protobuf_var_int(?A:int)// is det.
  344% Conversion between an int A and a list of codes, using the
  345% "varint" encoding.
  346% The behvior is undefined if =A= is negative.
  347% This is a low-level predicate; normally, you should use
  348% template_message/2 and the appropriate template term.
  349% e.g. phrase(protobuf_var_int(300), S) => S = [172,2]
  350%      phrase(protobuf_var_int(A), [172,2]) -> A = 300
  351protobuf_var_int(A, [A | Rest], Rest) :-
  352    A < 128,
  353    !.
  354protobuf_var_int(X, [A | Rest], Rest1) :-
  355    nonvar(X),
  356    X1 is X >> 7,
  357    A is 128 + (X /\ 0x7f),
  358    protobuf_var_int(X1, Rest, Rest1),
  359    !.
  360protobuf_var_int(X, [A | Rest], Rest1) :-
  361    protobuf_var_int(X1, Rest, Rest1),
  362    X is (X1 << 7) + A - 128,
  363    !.
  364
  365%! protobuf_tag_type(?Tag:int, ?WireType:atom)// is det.
  366% Conversion between Tag (number) + WireType and wirestream codes.
  367% This is a low-level predicate; normally, you should use
  368% template_message/2 and the appropriate template term.
  369% @arg Tag The item's tag (field number)
  370% @arg WireType The item's wire type (see prolog_type//2 for how to
  371%               convert this to a Prolog type)
  372protobuf_tag_type(Tag, WireType, Rest, Rest1) :-
  373    nonvar(Tag), nonvar(WireType),
  374    wire_type(WireType, WireTypeEncoding),
  375    A is Tag << 3 \/ WireTypeEncoding,
  376    protobuf_var_int(A, Rest, Rest1),
  377    !.
  378protobuf_tag_type(Tag, WireType, Rest, Rest1) :-
  379    protobuf_var_int(A, Rest, Rest1),
  380    WireTypeEncoding is A /\ 0x07,
  381    wire_type(WireType, WireTypeEncoding),
  382    Tag is A >> 3.
  383
  384%! prolog_type(?Tag:int, ?PrologType:atom)// is semidet.
  385% Match Tag (field number) + PrologType.
  386% When Type is a variable, backtracks through all the possibilities
  387% for a given wire encoding.
  388% Note that 'repeated' isn't here because it's handled by single_message//3.
  389% See also segment_type_tag/3.
  390prolog_type(Tag, double) -->     protobuf_tag_type(Tag, fixed64).
  391prolog_type(Tag, integer64) -->  protobuf_tag_type(Tag, fixed64).
  392prolog_type(Tag, unsigned64) --> protobuf_tag_type(Tag, fixed64).
  393prolog_type(Tag, float) -->      protobuf_tag_type(Tag, fixed32).
  394prolog_type(Tag, integer32) -->  protobuf_tag_type(Tag, fixed32).
  395prolog_type(Tag, unsigned32) --> protobuf_tag_type(Tag, fixed32).
  396prolog_type(Tag, integer) -->    protobuf_tag_type(Tag, varint).
  397prolog_type(Tag, unsigned) -->   protobuf_tag_type(Tag, varint).
  398prolog_type(Tag, signed32) -->   protobuf_tag_type(Tag, varint).
  399prolog_type(Tag, signed64) -->   protobuf_tag_type(Tag, varint).
  400prolog_type(Tag, boolean) -->    protobuf_tag_type(Tag, varint).
  401prolog_type(Tag, enum) -->       protobuf_tag_type(Tag, varint).
  402prolog_type(Tag, atom) -->       protobuf_tag_type(Tag, length_delimited).
  403prolog_type(Tag, codes) -->      protobuf_tag_type(Tag, length_delimited).
  404prolog_type(Tag, utf8_codes) --> protobuf_tag_type(Tag, length_delimited).
  405prolog_type(Tag, string) -->     protobuf_tag_type(Tag, length_delimited).
  406prolog_type(Tag, embedded) -->   protobuf_tag_type(Tag, length_delimited).
  407prolog_type(Tag, packed) -->     protobuf_tag_type(Tag, length_delimited).
  408
  409%
  410%   The protobuf-2.1.0 grammar allows negative values in enums.
  411%   But they are encoded as unsigned in the  golden message.
  412%   As such, they use the maximum length of a varint, so it is
  413%   recommended that they be non-negative. However, that's controlled
  414%   by the =|.proto|= file.
  415%
  416:- meta_predicate enumeration(1,?,?).  417
  418enumeration(Type) -->
  419    { call(Type, Value) },
  420    payload(signed64, Value).
  421
  422%! payload(?PrologType, ?Payload) is det.
  423% Process the codes into =Payload=, according to =PrologType=
  424% TODO: payload//2 "mode" is sometimes module-sensitive, sometimes not.
  425%       payload(enum, A)// has A as a callable
  426%       all other uses of payload//2, the 2nd arg is not callable.
  427%     - This confuses check/0; it also makes defining an enumeration
  428%       more difficult because it has to be defined in module protobufs
  429%       (see vector_demo.pl, which defines protobufs:commands/2)
  430payload(enum, Payload) -->
  431    enumeration(Payload).
  432payload(double, Payload) -->
  433    fixed_float64(Payload).
  434payload(integer64, Payload) -->
  435    { uint64_int64_when(Payload0, Payload) },
  436    fixed_uint64(Payload0).
  437payload(unsigned64, Payload) -->
  438    fixed_uint64(Payload).
  439payload(float, Payload) -->
  440    fixed_float32(Payload).
  441payload(integer32, Payload) -->
  442    { uint32_int32_when(Payload0, Payload) },
  443    fixed_uint32(Payload0).
  444payload(unsigned32, Payload) -->
  445    fixed_uint32(Payload).
  446payload(integer, Payload) -->
  447    { nonvar(Payload), int64_zigzag(Payload, X) }, % TODO: int64_zigzag_when/2
  448    !,
  449    protobuf_var_int(X).
  450payload(integer, Payload) -->
  451    protobuf_var_int(X),
  452    { int64_zigzag(Payload, X) }. % TODO: int64_zigzag_when/2
  453payload(unsigned, Payload) -->
  454    protobuf_var_int(Payload),
  455    { Payload >= 0 }.
  456payload(signed32, Payload) --> % signed32 is not defined by prolog_type//2
  457                               % for wire-stream compatibility reasons.
  458    % signed32 ought to write 5 bytes for negative numbers, but both
  459    % the C++ and Python implementations write 10 bytes. For
  460    % wire-stream compatibility, we follow C++ and Python, even though
  461    % protoc decode appears to work just fine with 5 bytes --
  462    % presumably there are some issues with decoding 5 bytes and
  463    % getting the sign extension correct with some 32/64-bit integer
  464    % models.  See CodedOutputStream::WriteVarint32SignExtended(int32
  465    % value) in google/protobuf/io/coded_stream.h.
  466    payload(signed64, Payload).
  467payload(signed64, Payload) -->
  468    % protobuf_var_int//1 cannot handle negative numbers (note that
  469    % zig-zag encoding always results in a positive number), so
  470    % compute the 64-bit 2s complement, which is what is produced
  471    % form C++ and Python.
  472    { nonvar(Payload) },
  473    !,
  474    { uint64_int64(X, Payload) }, % TODO: uint64_int64_when
  475    protobuf_var_int(X).
  476payload(signed64, Payload) -->
  477    % See comment in previous clause about negative numbers.
  478    protobuf_var_int(X),
  479    { uint64_int64(X, Payload) }. % TODO: uint64_int64_when
  480payload(codes, Payload) -->
  481    { nonvar(Payload),
  482      !,
  483      length(Payload, Len)
  484    },
  485    protobuf_var_int(Len),
  486    code_string(Len, Payload).
  487payload(codes, Payload) -->
  488    protobuf_var_int(Len),
  489    code_string(Len, Payload).
  490payload(utf8_codes, Payload) -->
  491    { nonvar(Payload), % TODO: use freeze/2 or when/2
  492      !,
  493      phrase(utf8_codes(Payload), B)
  494    },
  495    payload(codes, B).
  496payload(utf8_codes, Payload) -->
  497    payload(codes, B),
  498    { phrase(utf8_codes(Payload), B) }.
  499payload(atom, Payload) -->
  500    { nonvar(Payload),
  501      atom_codes(Payload, Codes)
  502    },
  503    payload(utf8_codes, Codes),
  504    !.
  505payload(atom, Payload) -->
  506    payload(utf8_codes, Codes),
  507    { atom_codes(Payload, Codes) }.
  508payload(boolean, true) -->
  509    payload(unsigned, 1).
  510payload(boolean, false) -->
  511    payload(unsigned, 0).
  512payload(string, Payload) -->
  513    {   nonvar(Payload)
  514    ->  string_codes(Payload, Codes)
  515    ;   true
  516    },
  517    % string_codes produces a list of unicode, not bytes
  518    payload(utf8_codes, Codes),
  519    { string_codes(Payload, Codes) }.
  520payload(embedded, protobuf(PayloadSeq)) -->
  521    { ground(PayloadSeq),
  522      phrase(protobuf(PayloadSeq), Codes)
  523    },
  524    payload(codes, Codes),
  525    !.
  526payload(embedded, protobuf(PayloadSeq)) -->
  527    payload(codes, Codes),
  528    { phrase(protobuf(PayloadSeq), Codes) }.
  529payload(packed, TypedPayloadSeq) -->
  530    { TypedPayloadSeq =.. [PrologType, PayloadSeq],  % TypedPayloadSeq = PrologType(PayloadSeq)
  531      ground(PayloadSeq),
  532      phrase(packed_payload(PrologType, PayloadSeq), Codes)
  533    },
  534    payload(codes, Codes),
  535    !.
  536payload(packed, enum(EnumSeq)) -->
  537    !,
  538    % TODO: combine with next clause
  539    % TODO: replace =.. with a predicate that gives all the possibilities - see detag/6.
  540    { EnumSeq =.. [ Enum, Values ] }, % EnumSeq = Enum(Values)
  541    payload(codes, Codes),
  542    { phrase(packed_enum(Enum, Values), Codes) }.
  543payload(packed, TypedPayloadSeq) -->
  544    payload(codes, Codes),
  545    % TODO: replace =.. with a predicate that gives all the possibilities - see detag/6.
  546    { TypedPayloadSeq =.. [PrologType, PayloadSeq] },  % TypedPayloadSeq = PrologType(PayloadSeq)
  547    { phrase(packed_payload(PrologType, PayloadSeq), Codes) }.
  548
  549packed_payload(enum, EnumSeq) -->
  550    { ground(EnumSeq) }, !,
  551    { EnumSeq =.. [EnumType, Values] }, % EnumSeq = EnumType(Values)
  552    packed_enum(EnumType, Values).
  553packed_payload(PrologType, PayloadSeq) -->
  554    sequence_payload(PrologType, PayloadSeq).
  555
  556% sequence_payload//2 (because sequence//2 isn't compile-time expanded)
  557sequence_payload(PrologType, PayloadSeq) -->
  558    sequence_payload_(PayloadSeq, PrologType).
  559
  560sequence_payload_([], _PrologType) --> [ ].
  561sequence_payload_([Payload|PayloadSeq], PrologType) -->
  562        payload(PrologType, Payload),
  563        sequence_payload_(PayloadSeq, PrologType).
  564
  565packed_enum(Enum, [ A | As ]) -->
  566    % TODO: replace =.. with a predicate that gives all the possibilities - see detag/6.
  567    { E =.. [Enum, A] },
  568    payload(enum, E),
  569    packed_enum(Enum, As).
  570packed_enum(_, []) --> [ ].
  571
  572start_group(Tag) --> protobuf_tag_type(Tag, start_group).
  573
  574end_group(Tag) -->   protobuf_tag_type(Tag, end_group).
  575%
  576%
  577nothing([]) --> [], !.
  578
  579protobuf([Field | Fields]) -->
  580    % TODO: don't use =.. -- move logic to single_message
  581    (   { Field = repeated_embedded(Tag, protobuf(EmbeddedFields), Items) }
  582    ->  repeated_embedded_messages(Tag, EmbeddedFields, Items)
  583    ;   { Field =.. [ PrologType, Tag, Payload] },  % Field = PrologType(Tag, Payload)
  584        single_message(PrologType, Tag, Payload),
  585        (   protobuf(Fields)
  586        ;   nothing(Fields)
  587        )
  588    ),
  589    !.
  590
  591repeated_message(repeated_enum, Tag, Type, [A | B]) -->
  592    % TODO: replace =.. with a predicate that gives all the possibilities - see detag/6.
  593    { TypedPayload =.. [Type, A] },  % TypedPayload = Type(A)
  594    single_message(enum, Tag, TypedPayload),
  595    (   repeated_message(repeated_enum, Tag, Type, B)
  596    ;   nothing(B)
  597    ).
  598repeated_message(Type, Tag, [A | B]) -->
  599    { Type \= repeated_enum },
  600    single_message(Type, Tag, A),
  601    repeated_message(Type, Tag, B).
  602repeated_message(_Type, _Tag, A) -->
  603    nothing(A).
  604
  605repeated_embedded_messages(Tag, EmbeddedFields, [protobuf(A) | B]) -->
  606    { copy_term(EmbeddedFields, A) },
  607    single_message(embedded, Tag, protobuf(A)), !,
  608    repeated_embedded_messages(Tag, EmbeddedFields, B).
  609repeated_embedded_messages(_Tag, _EmbeddedFields, []) -->
  610    [ ].
  611
  612%! single_message(+PrologType:atom, ?Tag, ?Payload)// is det.
  613% Processes a single messages (e.g., one item in the list in protobuf([...]).
  614% The PrologType, Tag, Payload are from Field =.. [PrologType, Tag, Payload]
  615% in the caller
  616single_message(repeated, Tag, enum(EnumSeq)) -->
  617    !,
  618    { EnumSeq =.. [EnumType, Values] },  % EnumSeq = EnumType(Values)
  619    repeated_message(repeated_enum, Tag, EnumType, Values).
  620single_message(repeated, Tag, Payload) -->
  621    !,
  622    % TODO: replace =.. with a predicate that gives all the possibilities - see detag/6.
  623    { Payload =.. [PrologType, A] },  % Payload = PrologType(A)
  624    { PrologType \= enum },
  625    repeated_message(PrologType, Tag, A).
  626single_message(group, Tag, A) -->
  627    !,
  628    start_group(Tag),
  629    protobuf(A),
  630    end_group(Tag).
  631single_message(PrologType, Tag, Payload) -->
  632    { PrologType \= repeated, PrologType \= group },
  633    prolog_type(Tag, PrologType),
  634    payload(PrologType, Payload).
  635
  636%!  protobuf_message(?Template, ?WireStream) is semidet.
  637%!  protobuf_message(?Template, ?WireStream, ?Rest) is nondet.
  638%
  639%   Marshals  and  unmarshals   byte  streams  encoded  using   Google's
  640%   Protobuf  grammars.  protobuf_message/2  provides  a  bi-directional
  641%   parser that marshals a Prolog   structure to WireStream,  according
  642%   to rules specified by Template. It   can also unmarshal  WireStream
  643%   into  a  Prolog   structure   according    to   the   same  grammar.
  644%   protobuf_message/3 provides a difference list version.
  645%
  646%   @bug The protobuf specification states that the wire-stream can have
  647%   the fields in any order and that unknown fields are to be ignored.
  648%   This implementation assumes that the fields are in the exact order
  649%   of the definition and match exactly. If you use
  650%   protobuf_parse_from_codes/3, you can avoid this problem.o
  651%
  652%   @param Template is a  protobuf   grammar  specification.  On decode,
  653%   unbound variables in the Template are  unified with their respective
  654%   values in the WireStream. On encode, Template must be ground.
  655%
  656%   @param WireStream is a code list that   was generated by a protobuf
  657%   encoder using an equivalent template.
  658
  659protobuf_message(protobuf(TemplateList), WireStream) :-
  660    must_be(list, TemplateList),
  661    phrase(protobuf(TemplateList), WireStream),
  662    !.
  663
  664protobuf_message(protobuf(TemplateList), WireStream, Residue) :-
  665    must_be(list, TemplateList),
  666    phrase(protobuf(TemplateList), WireStream, Residue).
  667
  668%! protobuf_segment_message(+Segments:list, -WireStream:list(int)) is det.
  669%! protobuf_segment_message(-Segments:list, +WireStream:list(int)) is det.
  670%
  671%  Low level marshalling and unmarshalling of byte streams. The
  672%  processing is independent of the =|.proto|= description, similar to
  673%  the processing done by =|protoc --decode_raw|=. This means that
  674%  field names aren't shown, only field numbers.
  675%
  676%  For unmarshalling, a simple heuristic is used on length-delimited
  677%  segments: first interpret it as a message; if that fails, try to
  678%  interpret as a UTF8 string; otherwise, leave it as a "blob" (if the
  679%  heuristic was wrong, you can convert to a string or a blob by using
  680%  protobuf_segment_convert/2).  32-bit and 64-bit numbers are left as
  681%  codes because they could be either integers or floating point (use
  682%  int32_codes_when/2, float32_codes_when/2, int64_codes_when/2,
  683%  uint32_codes_when/2, uint64_codes_when/2, float64_codes_when/2 as
  684%  appropriate); variable-length numbers ("varint" in the [[Protocol
  685%  Buffers encoding
  686%  documentation][https://developers.google.com/protocol-buffers/docs/encoding#varints]]),
  687%  might require "zigzag" conversion, int64_zigzag_when/2.
  688%
  689%  For marshalling, use the predicates int32_codes_when/2,
  690%  float32_codes_when/2, int64_codes_when/2, uint32_codes_when/2,
  691%  uint64_codes_when/2, float64_codes_when/2, int64_zigzag_when/2 to
  692%  put integer and floating point values into the appropriate form.
  693%
  694%  @bug This predicate is preliminary and may change as additional
  695%       functionality is added.
  696%
  697%  @param Segments a list containing terms of the following form (=Tag= is
  698%  the field number; =Codes= is a list of integers):
  699%    * varint(Tag,Varint) - =Varint= may need int64_zigzag_when/2
  700%    * fixed64(Tag,Int) - =Int= signed, derived from the 8 codes
  701%    * fixed32(Tag,Codes) - =Int= is signed, derived from the 4 codes
  702%    * message(Tag,Segments)
  703%    * group(Tag,Segments)
  704%    * string(Tag,String) - =String= is a SWI-Prolog string
  705%    * packed(Tag,Type(Scalars)) - =Type= is one of
  706%             =varint=, =fixed64=, =fixed32=; =Scalars=
  707%             is a list of =Varint= or =Codes=, which should
  708%             be interpreted as described under those items.
  709%             Note that the protobuf specification does not
  710%             allow packed repeated string.
  711%    * length_delimited(Tag,Codes)
  712%    * repeated(List) - =List= of segments
  713%  Of these, =group= is deprecated in the protobuf documentation and
  714%  shouldn't appear in modern code, having been superseded by nested
  715%  message types.
  716%
  717%  For deciding how to interpret a length-delimited item (when
  718%  =Segments= is a variable), an attempt is made to parse the item in
  719%  the following order (although code should not rely on this order):
  720%    * message
  721%    * string (it must be in the form of a UTF string)
  722%    * packed (which can backtrack through the various =Type=s)
  723%    * length_delimited - which always is possible.
  724%
  725%  The interpretation of length-delimited items can sometimes guess
  726%  wrong; the interpretation can be undone by either backtracking or
  727%  by using protobuf_segment_convert/2 to convert the incorrect
  728%  segment to a string or a list of codes. Backtracking through all
  729%  the possibilities is not recommended, because of combinatoric
  730%  explosion (there is an example in the unit tests); instead, it is
  731%  suggested that you take the first result and iterate through its
  732%  items, calling protobuf_segment_convert/2 as needed to reinterpret
  733%  incorrectly guessed segments.
  734%
  735%  @param WireStream a code list that was generated by a protobuf
  736%  endoder.
  737%
  738%  @see https://developers.google.com/protocol-buffers/docs/encoding
  739protobuf_segment_message(Segments, WireStream) :-
  740    phrase(segment_message(Segments), WireStream).
  741
  742segment_message(Segments) -->
  743    sequence_segment(Segments).
  744
  745% sequence_segment//1 (because sequence//2 isn't compile-time expanded)
  746sequence_segment([]) --> [ ].
  747sequence_segment([Segment|Segments]) -->
  748    segment(Segment),
  749    sequence_segment(Segments).
  750
  751segment(Segment) -->
  752    { nonvar(Segment) },
  753    !,
  754    % repeated(List) can be created by field_segment_scalar_or_repeated/7
  755    (   { Segment = repeated(Segments) }
  756    ->  sequence_segment(Segments)
  757    ;   { segment_type_tag(Segment, Type, Tag) },
  758        protobuf_tag_type(Tag, Type),
  759        segment(Type, Tag, Segment)
  760    ).
  761segment(Segment) -->
  762    % { var(Segment) },
  763    protobuf_tag_type(Tag, Type),
  764    segment(Type, Tag, Segment).
  765
  766segment(varint, Tag, varint(Tag,Value)) -->
  767    protobuf_var_int(Value).
  768segment(fixed64, Tag, fixed64(Tag, Int64)) -->
  769    payload(integer64, Int64).
  770segment(fixed32, Tag, fixed32(Tag, Int32)) -->
  771    payload(integer32, Int32).
  772segment(start_group, Tag, group(Tag, Segments)) -->
  773    segment_message(Segments),
  774    protobuf_tag_type(Tag, end_group).
  775segment(length_delimited, Tag, Result) -->
  776    segment_length_delimited(Tag, Result).
  777
  778segment_length_delimited(Tag, Result) -->
  779    { nonvar(Result) },
  780    !,
  781    { length_delimited_segment(Result, Tag, Codes) },
  782    { length(Codes, CodesLen) },
  783    protobuf_var_int(CodesLen),
  784    code_string(CodesLen, Codes).
  785segment_length_delimited(Tag, Result) -->
  786    % { var(Result) },
  787    protobuf_var_int(CodesLen),
  788    code_string(CodesLen, Codes),
  789    { length_delimited_segment(Result, Tag, Codes) }.
  790
  791length_delimited_segment(message(Tag,Segments), Tag, Codes) :-
  792    protobuf_segment_message(Segments, Codes).
  793length_delimited_segment(group(Tag,Segments), Tag, Codes) :-
  794    phrase(segment_group(Tag, Segments), Codes).
  795length_delimited_segment(string(Tag,String), Tag, Codes) :-
  796    (   nonvar(String)
  797    ->  string_codes(String, StringCodes),
  798        phrase(utf8_codes(StringCodes), Codes)
  799    ;   phrase(utf8_codes(StringCodes), Codes),
  800        string_codes(String, StringCodes)
  801    ).
  802length_delimited_segment(packed(Tag,Payload), Tag, Codes) :-
  803    % We don't know the type of the fields, so we try the 3
  804    % possibilities.  This has a problem: an even number of fixed32
  805    % items can't be distinguished from half the number of fixed64
  806    % items; but it's all we can do. The good news is that usually
  807    % varint (possibly with zig-zag encoding) is more common because
  808    % it's more compact (I don't know whether 32-bit or 64-bit is more
  809    % common for floating point).
  810    packed_option(Type, Items, Payload),
  811    phrase(sequence_payload(Type, Items), Codes).
  812length_delimited_segment(length_delimited(Tag,Codes), Tag, Codes).
  813
  814segment_group(Tag, Segments) -->
  815    start_group(Tag),
  816    segment_message(Segments),
  817    end_group(Tag).
  818
  819% See also prolog_type//2. Note that this doesn't handle repeated(List),
  820% which is used internally (see field_segment_scalar_or_repeated/7).
  821segment_type_tag(varint(Tag,_Value),           varint,           Tag).
  822segment_type_tag(fixed64(Tag,_Value),          fixed64,          Tag).
  823segment_type_tag(group(Tag,_Segments),         start_group,      Tag).
  824segment_type_tag(fixed32(Tag,_Value),          fixed32,          Tag).
  825segment_type_tag(length_delimited(Tag,_Codes), length_delimited, Tag).
  826segment_type_tag(message(Tag,_Segments),       length_delimited, Tag).
  827segment_type_tag(packed(Tag,_Payload),         length_delimited, Tag).
  828segment_type_tag(string(Tag,_String),          length_delimited, Tag).
  829
  830%! detag(+Compound, -Name, -Tag, -Value, List, -CompoundWithList) is semidet.
  831% Deconstruct =Compound= or the form =|Name(Tag,Value)|= and create a
  832% new =CompoundWithList= that replaces =Value= with =List=. This is
  833% used by packed_list/2 to transform =|[varint(1,0),varint(1,1)]|= to
  834% =|varint(1,[0,1])|=.
  835%
  836% Some of =Compound= items are impossible for =packed= with the
  837% current protobuf spec, but they don't do any harm.
  838detag(varint(Tag,Value),           varint,            Tag, Value,     List, varint(List)).
  839detag(fixed64(Tag,Value),          fixed64,           Tag, Value,     List, fixed64(List)).
  840detag(fixed32(Tag,Value),          fixed32,           Tag, Value,     List, fixed32(List)).
  841detag(length_delimited(Tag,Codes), length_delimited,  Tag, Codes,     List, length_delimited(List)).
  842detag(message(Tag,Segments),       message,           Tag, Segments,  List, message(List)).
  843detag(packed(Tag,Payload),         packed,            Tag, Payload,   List, packed(List)). % TODO: delete?
  844detag(string(Tag,String),          string,            Tag, String,    List, string(List)).
  845
  846% See also prolog_type//2, but pick only one for each wirestream type
  847% For varint(Items), use one that doesn't do zigzag
  848packed_option(integer64, Items, fixed64(Items)).
  849packed_option(integer32, Items, fixed32(Items)).
  850packed_option(unsigned,  Items, varint(Items)).
  851% packed_option(integer,   Items, varint(Items)).
  852% packed_option(double,    Items, fixed64(Items)).
  853% packed_option(float,     Items, fixed32(Items)).
  854% packed_option(signed64,  Items, varint(Items)).
  855% packed_option(boolean,   Items, varint(Items)).
  856% packed_option(enum,      Items, varint(Items)).
  857
  858%! protobuf_segment_convert(+Form1, ?Form2) is multi.
  859% A convenience predicate for dealing with the situation where
  860% protobuf_segment_message/2 interprets a segment of the wire stream
  861% as a form that you don't want (e.g., as a message but it should have
  862% been a UTF8 string).
  863%
  864% =Form1= is converted back to the original wire stream, then the
  865% predicate non-deterimisticly attempts to convert the wire stream to
  866% a =|string|= or =|length_delimited|= term (or both: the lattter
  867% always succeeds).
  868%
  869% The possible conversions are:
  870%   message(Tag,Segments) => string(Tag,String)
  871%   message(Tag,Segments) => length_delimited(Tag,Codes)
  872%   string(Tag,String) => length_delimited(Tag,Codes)
  873%   length_delimited(Tag,Codes) => length_delimited(Tag,Codes)
  874%
  875% Note that for fixed32, fixed64, only the signed integer forms are
  876% given; if you want the floating point forms, then you need to do use
  877% int64_float64_when/2 and int32_float32_when/2.
  878%
  879% For example:
  880% ~~~{.pl}
  881% ?- protobuf_segment_convert(
  882%        message(10,[fixed64(13,7309475598860382318)]),
  883%        string(10,"inputType")).
  884% ?- protobuf_segment_convert(
  885%        message(10,[fixed64(13,7309475598860382318)]),
  886%        length_delimited(10,[105,110,112,117,116,84,121,112,101])).
  887% ?- protobuf_segment_convert(
  888%        string(10, "inputType"),
  889%        length_delimited(10,[105,110,112,117,116,84,121,112,101])).
  890% ?- forall(protobuf_segment_convert(string(1999,"\x1\\x0\\x0\\x0\\x2\\x0\\x0\\x0\"),Z), writeln(Z)).
  891%       string(1999,)
  892%       packed(1999,fixed64([8589934593]))
  893%       packed(1999,fixed32([1,2]))
  894%       packed(1999,varint([1,0,0,0,2,0,0,0]))
  895%       length_delimited(1999,[1,0,0,0,2,0,0,0])
  896% ~~~
  897% These come from:
  898% ~~~{.pl}
  899% Codes = [82,9,105,110,112,117,116,84,121,112,101],
  900% protobuf_message(protobuf([embedded(T1, protobuf([integer64(T2, I)]))]), Codes),
  901% protobuf_message(protobuf([string(T,S)]), Codes).
  902%    T = 10, T1 = 10, T2 = 13,
  903%    I = 7309475598860382318,
  904%    S = "inputType".
  905% ~~~
  906%
  907%  @bug This predicate is preliminary and may change as additional
  908%       functionality is added.
  909%  @bug This predicate will sometimes generate unexpected choice points,
  910%       Such as from =|protobuf_segment_convert(message(10,...), string(10,...))|=
  911%
  912% @param Form1 =|message(Tag,Pieces)|=, =|string(Tag,String)|=, =|length_delimited(Tag,Codes)|=,
  913%        =|varint(Tag,Value)|=, =|fixed64(Tag,Value)|=, =|fixed32(Tag,Value)|=.
  914% @param Form2 similar to =Form1=.
  915protobuf_segment_convert(Form, Form). % for efficiency, don't generate codes
  916protobuf_segment_convert(Form1, Form2) :-
  917    dif(Form1, Form2),          % Form1=Form2 handled by first clause
  918    protobuf_segment_message([Form1], WireCodes),
  919    phrase(tag_and_codes(Tag, Codes), WireCodes),
  920    length_delimited_segment(Form2, Tag, Codes).
  921
  922tag_and_codes(Tag, Codes) -->
  923    protobuf_tag_type(Tag, length_delimited),
  924    payload(codes, Codes).
  925
  926%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  927% Documention of the foreign predicates, which are wrapped and exported.
  928
  929%! uint32_codes_when(?Uint32, ?Codes) is det.
  930% Convert between a 32-bit unsigned integer value and its wirestream codes.
  931% This is a low-level predicate; normally, you should use
  932% template_message/2 and the appropriate template term.
  933%
  934% This predicate delays until either =Uint32= or =Codes= is
  935% sufficiently instantiated.
  936%
  937% There is also a non-delayed protobufs:uint32_codes/2
  938%
  939% SWI-Prolog doesn't have a 32-bit integer type, so 32-bit integer
  940% is simulated by doing a range check.
  941%
  942% @param Uint32 an unsigned integer that's in the 32-bit range
  943% @param Codes a list of 4 integers (codes)
  944%
  945% @error Type,Domain if =Value= or =Codes= are of the wrong
  946%                    type or out of range.
  947uint32_codes_when(Uint32, Codes) :-
  948    when((nonvar(Uint32) ; nonvar(Codes)), uint32_codes(Uint32, Codes)).
  949
  950%! int32_codes_when(?Int32, ?Codes) is det.
  951% Convert between a 32-bit signed integer value and its wirestream codes.
  952% This is a low-level predicate; normally, you should use
  953% template_message/2 and the appropriate template term.
  954%
  955% This predicate delays until either =Int32= or =Codes= is
  956% sufficiently instantiated.
  957%
  958% There is also a non-delayed protobufs:int32_codes/2
  959%
  960% SWI-Prolog doesn't have a 32-bit integer type, so 32-bit integer
  961% is simulated by doing a range check.
  962%
  963% @param Int32 an unsigned integer that's in the 32-bit range
  964% @param Codes a list of 4 integers (codes)
  965%
  966% @error Type,Domain if =Value= or =Codes= are of the wrong
  967%                    type or out of range.
  968int32_codes_when(Int32, Codes) :- % TODO: unused
  969    when((nonvar(Int32) ; nonvar(Codes)), int32_codes(Int32, Codes)).
  970
  971%! float32_codes_when(?Value, ?Codes) is det.
  972% Convert between a 32-bit floating point value and its wirestream codes.
  973% This is a low-level predicate; normally, you should use
  974% template_message/2 and the appropriate template term.
  975%
  976% This predicate delays until either =Value= or =Codes= is
  977% sufficiently instantiated.
  978%
  979% There is also a non-delayed protobufs:float32_codes/2
  980%
  981% @param Value a floating point number
  982% @param Codes a list of 4 integers (codes)
  983float32_codes_when(Value, Codes) :-
  984    when((nonvar(Value) ; nonvar(Codes)), float32_codes(Value, Codes)).
  985
  986%! uint64_codes_when(?Uint64, ?Codes) is det.
  987% Convert between a 64-bit unsigned integer value and its wirestream codes.
  988% This is a low-level predicate; normally, you should use
  989% template_message/2 and the appropriate template term.
  990%
  991% SWI-Prolog allows integer values greater than 64 bits, so
  992% a range check is done.
  993%
  994% This predicate delays until either =Uint64= or =Codes= is
  995% sufficiently instantiated.
  996%
  997% There is also a non-delayed protobufs:uint64_codes/2
  998
  999%
 1000% @param Uint64 an unsigned integer
 1001% @param Codes a list of 8 integers (codes)
 1002%
 1003% @error Type,Domain if =Uint64= or =Codes= are of the wrong
 1004%                    type or out of range.
 1005uint64_codes_when(Uint64, Codes) :-
 1006    when((nonvar(Uint64) ; nonvar(Codes)), uint64_codes(Uint64, Codes)).
 1007
 1008%! int64_codes_when(?Int64, ?Codes) is det.
 1009% Convert between a 64-bit signed integer value and its wirestream codes.
 1010% This is a low-level predicate; normally, you should use
 1011% template_message/2 and the appropriate template term.
 1012%
 1013% SWI-Prolog allows integer values greater than 64 bits, so
 1014% a range check is done.
 1015%
 1016% This predicate delays until either =Int64= or =Codes= is
 1017% sufficiently instantiated.
 1018%
 1019% There is also a non-delayed protobufs:int64_codes/2
 1020
 1021%
 1022% @param Int64 an unsigned integer
 1023% @param Codes a list of 8 integers (codes)
 1024%
 1025% @error Type,Domain if =Int64= or =Codes= are of the wrong
 1026%                    type or out of range.
 1027int64_codes_when(Int64, Codes) :-  % TODO: unused
 1028    when((nonvar(Int64) ; nonvar(Codes)), int64_codes(Int64, Codes)).
 1029
 1030%! float64_codes_when(?Value, ?Codes) is det.
 1031% Convert between a 64-bit floating point value and its wirestream codes.
 1032% This is a low-level predicate; normally, you should use
 1033% template_message/2 and the appropriate template term.
 1034%
 1035% This predicate delays until either =Value= or =Codes= is
 1036% sufficiently instantiated.
 1037%
 1038% There is also a non-delayed protobufs:float64_codes/2
 1039%
 1040% @param Value a floating point number
 1041% @param Codes a list of 8 integers (codes)
 1042%
 1043% @error instantiation error if both =Value= and =Codes= are uninstantiated.
 1044%
 1045% @bug May give misleading exception under some circumstances
 1046%      (e.g., float64_codes(_, [_,_,_,_,_,_,_,_]).
 1047float64_codes_when(Value, Codes) :-
 1048    when((nonvar(Value) ; nonvar(Codes)), float64_codes(Value, Codes)).
 1049
 1050%! int64_zigzag_when(?Original, ?Encoded) is det.
 1051% Convert between a signed integer value and its zigzag encoding,
 1052% used for the protobuf =sint32= and =sint64= types. This is a
 1053% low-level predicate; normally, you should use template_message/2 and
 1054% the appropriate template term.
 1055%
 1056% SWI-Prolog allows integer values greater than 64 bits, so
 1057% a range check is done.
 1058%
 1059% This predicate delays until either =Original= or =Encoded= is
 1060% sufficiently instantiated.
 1061%
 1062% There is also a non-delayed protobufs:int64_zigzag/2
 1063%
 1064% @see https://developers.google.com/protocol-buffers/docs/encoding#types
 1065%
 1066% @param Original an integer in the original form
 1067% @param Encoded the zigzag encoding of =Original=
 1068%
 1069% @error Type,Domain if =Original= or =Encoded= are of the wrong
 1070%                    type or out of range.
 1071%
 1072% @error instantiation error if both =Original= and =Encoded= are uninstantiated.
 1073int64_zigzag_when(Original, Encoded) :-
 1074    when((nonvar(Original) ; nonvar(Encoded)), int64_zigzag(Original, Encoded)).
 1075
 1076%! uint64_int64_when(?Uint64:integer, ?Int64:integer) is det.
 1077% Reinterpret-cast between uint64 and int64. For example,
 1078% =|uint64_int64(0xffffffffffffffff,-1)|=.
 1079%
 1080% This predicate delays until either =Uint64= or =Int64= is
 1081% sufficiently instantiated.
 1082%
 1083% There is also a non-delayed protobufs:uint64_int64/2
 1084%
 1085% @param Uint64 64-bit unsigned integer
 1086% @param Int64 64-bit signed integer
 1087%
 1088% @error Type,Domain if =Value= or =Codes= are of the wrong
 1089%                    type or out of range.
 1090%
 1091% @error instantiation error if both =Value= and =Codes= are uninstantiated.
 1092uint64_int64_when(Uint64, Int64) :-
 1093    when((nonvar(Uint64) ; nonvar(Int64)), uint64_int64(Uint64, Int64)).
 1094
 1095% Reversed argument ordering for maplist/3
 1096int64_uint64_when(Int64, Uint64) :-
 1097    uint64_int64_when(Uint64, Int64).
 1098
 1099%! uint32_int32_when(?Uint32, ?Int32) is det.
 1100% Reinterpret-case between uint32 and int32.
 1101%
 1102% This predicate delays until either =Uint32= or =Int32= is
 1103% sufficiently instantiated.
 1104%
 1105% There is also a non-delayed protobufs:uint32_int32/2
 1106%
 1107% @param Uint32 32-bit unsigned integer (range between 0 and 4294967295).
 1108% @param Int32 32-bit signed integer (range between -2147483648 and 2147483647).
 1109%
 1110% @error Type,Domain if =Int32= or =Uint32= are of the wrong
 1111%                    type or out of range.
 1112%
 1113% @error instantiation error if both =UInt32= and =Int32= are uninstantiated.
 1114uint32_int32_when(Uint32, Int32) :-
 1115    when((nonvar(Uint32) ; nonvar(Int32)), uint32_int32(Uint32, Int32)).
 1116
 1117% Reversed argument ordering for maplist/3
 1118int32_uint32_when(Int32, Uint32) :-
 1119
 1120    uint32_int32_when(Uint32, Int32).
 1121
 1122%! int64_float64_when(?Int64:integer, ?Float64:float) is det.
 1123% Reinterpret-cast between uint64 and float64. For example,
 1124% =|int64_float64(3ff0000000000000,1.0)|=.
 1125%
 1126% This predicate delays until either =Int64= or =Float64= is
 1127% sufficiently instantiated.
 1128%
 1129% There is also a non-delayed protobufs:uint64_int64/2
 1130%
 1131% @param Int64 64-bit unsigned integer
 1132% @param Float64 64-bit float
 1133%
 1134% @error Type,Domain if =Value= or =Codes= are of the wrong
 1135%                    type or out of range.
 1136%
 1137% @error instantiation error if both =Value= and =Codes= are uninstantiated.
 1138int64_float64_when(Int64, Float64) :-
 1139    when((nonvar(Int64) ; nonvar(Float64)), int64_float64(Int64, Float64)).
 1140
 1141%! int32_float32_when(?Int32:integer, ?Float32:float) is det.
 1142% Reinterpret-cast between uint32 and float32. For example,
 1143% =|int32_float32(0x3f800000,1.0)|=.
 1144%
 1145% This predicate delays until either =Int32= or =Float32= is
 1146% sufficiently instantiated.
 1147%
 1148% There is also a non-delayed protobufs:uint32_int32/2
 1149%
 1150% @param Int32 32-bit unsigned integer
 1151% @param Float32 32-bit float
 1152%
 1153% @error Type,Domain if =Value= or =Codes= are of the wrong
 1154%                    type or out of range.
 1155%
 1156% @error instantiation error if both =Value= and =Codes= are uninstantiated.
 1157int32_float32_when(Int32, Float32) :-
 1158    when((nonvar(Int32) ; nonvar(Float32)), int32_float32(Int32, Float32)).
 1159
 1160
 1161%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1162%
 1163% Use protobufs meta-data (see the section on protoc in the "overview" documentation).
 1164
 1165% The protoc plugin generates the following facts (all starting with "proto_meta_").
 1166% The are documented in protoc-gen-swipl and in the overview section.
 1167
 1168:- multifile
 1169     proto_meta_normalize/2,              % (Unnormalized, Normalized)
 1170     proto_meta_package/3,                % (Package, FileName, Options)
 1171     proto_meta_message_type/3,           % (Fqn, Package, Name)
 1172     proto_meta_message_type_map_entry/1, % (Fqn)
 1173     proto_meta_field_name/4,             % (Fqn, FieldNumber, FieldName, FqnName)
 1174     proto_meta_field_json_name/2,        % (FqnName, JsonName)
 1175     proto_meta_field_label/2,            % (FqnName, LabelRepeatOptional) % LABEL_OPTIONAL, LABEL_REQUIRED, LABEL_REPEATED
 1176     proto_meta_field_type/2,             % (FqnName, Type) % TYPE_INT32, TYPE_MESSAGE, etc
 1177     proto_meta_field_type_name/2,        % (FqnName, TypeName)
 1178     proto_meta_field_default_value/2,    % (FqnName, DefaultValue)
 1179     proto_meta_field_option_packed/1,    % (FqnName)
 1180     proto_meta_enum_type/3,              % (FqnName, Fqn, Name)
 1181     proto_meta_enum_value/3,             % (FqnName, Name, Number)
 1182     proto_meta_field_oneof_index/2,      % (FqnName, Index)
 1183     proto_meta_oneof/3.                  % (FqnName, Index, Name)
 1184
 1185proto_meta_enum_value_when(ContextType, EnumValue, IntValue) :-
 1186    when((nonvar(EnumValue) ; nonvar(IntValue)),
 1187         proto_meta_enum_value_(ContextType, EnumValue, IntValue)).
 1188
 1189proto_meta_enum_value_(ContextType, EnumValue, IntValue) :-
 1190    (   proto_meta_enum_value(ContextType, EnumValue, IntValue)
 1191    ->  true
 1192    ;   existence_error(ContextType, EnumValue-IntValue)
 1193    ).
 1194
 1195:- det(segment_to_term/3). 1196%! segment_to_term(+ContextType:atom, +Segment, -FieldAndValue) is det.
 1197% ContextType is the type (name) of the containing message
 1198% Segment is a segment from protobuf_segment_message/2
 1199% TODO: if performance is an issue, this code can be combined with
 1200%       protobuf_segment_message/2 (and thereby avoid the use of protobuf_segment_convert/2)
 1201segment_to_term(ContextType0, Segment, FieldAndValue) =>
 1202    segment_type_tag(Segment, _, Tag),
 1203    field_and_type(ContextType0, Tag, FieldName, _FqnName, ContextType, RepeatOptional, Type),
 1204    (   RepeatOptional = repeat_packed
 1205    ->  convert_segment_packed(Type, ContextType, Tag, Segment, Value)
 1206    ;   convert_segment(Type, ContextType, Tag, Segment, Value)
 1207    ),
 1208    !, % TODO: get rid of this?
 1209    FieldAndValue = field_and_value(FieldName,RepeatOptional,Value).
 1210
 1211% :- det(convert_segment_packed/5). % TODO: "succeeded with a choicepoint"
 1212%! convert_segment_packed(+Type:atom, +ContextType:atom, +Tag:atom, ?Segment, ?Values) is det.
 1213% Reversible on =Segment=, =Values=.
 1214%
 1215% TODO: these are very similar to convert_segment - can they be combined?
 1216
 1217convert_segment_packed('TYPE_DOUBLE', _ContextType, Tag, Segment0, Values) =>
 1218    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, fixed64(Values0)))),
 1219    maplist(int64_float64_when, Values0, Values), !.
 1220convert_segment_packed('TYPE_FLOAT', _ContextType, Tag, Segment0, Values) =>
 1221    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, fixed32(Values0)))),
 1222    maplist(int32_float32_when, Values0, Values), !.
 1223convert_segment_packed('TYPE_INT64', _ContextType, Tag, Segment0, Values) =>
 1224    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, varint(Values0)))),
 1225    maplist(uint64_int64_when, Values0, Values).
 1226convert_segment_packed('TYPE_UINT64', _ContextType, Tag, Segment0, Values) =>
 1227    protobuf_segment_convert(Segment0, packed(Tag, varint(Values))), !.
 1228convert_segment_packed('TYPE_INT32', _ContextType, Tag, Segment0, Values) =>
 1229    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, varint(Values0)))),
 1230    maplist(uint32_int32_when, Values0, Values).
 1231convert_segment_packed('TYPE_FIXED64', _ContextType, Tag, Segment0, Values) =>
 1232    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, fixed64(Values0)))),
 1233    maplist(int64_uint64_when, Values0, Values).
 1234convert_segment_packed('TYPE_FIXED32', _ContextType, Tag, Segment0, Values) =>
 1235    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, fixed32(Values0)))),
 1236    maplist(int32_uint32_when, Values0, Values).
 1237convert_segment_packed('TYPE_BOOL', _ContextType, Tag, Segment0, Values) =>
 1238    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, varint(Values0)))),
 1239    maplist(int_bool_when, Values0, Values).
 1240% TYPE_STRING  isn't allowed TODO: add it anyway?
 1241% TYPE_GROUP   isn't allowed
 1242% TYPE_MESSAGE isn't allowed
 1243% TYPE_BYTES   isn't allowed TODO: add it anyway?
 1244convert_segment_packed('TYPE_UINT32', _ContextType, Tag, Segment0, Values) =>
 1245    protobuf_segment_convert(Segment0, packed(Tag, varint(Values))), !.
 1246convert_segment_packed('TYPE_ENUM', ContextType, Tag, Segment0, Values) =>
 1247    % uint64_int64_when(...), % TODO! https://github.com/SWI-Prolog/contrib-protobufs/issues/9
 1248    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, varint(Values0)))),
 1249    maplist(convert_enum(ContextType), Values, Values0).
 1250convert_segment_packed('TYPE_SFIXED32', _ContextType, Tag, Segment0, Values) =>
 1251    protobuf_segment_convert(Segment0, packed(Tag, fixed32(Values))).
 1252convert_segment_packed('TYPE_SFIXED64', _ContextType, Tag, Segment0, Values) =>
 1253    protobuf_segment_convert(Segment0, packed(Tag, fixed64(Values))).
 1254convert_segment_packed('TYPE_SINT32', _ContextType, Tag, Segment0, Values) =>
 1255    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, varint(Values0)))),
 1256    maplist(int64_zigzag_when, Values, Values0).
 1257convert_segment_packed('TYPE_SINT64', _ContextType, Tag, Segment0, Values) =>
 1258    freeze(Segment0, protobuf_segment_convert(Segment0, packed(Tag, varint(Values0)))),
 1259    maplist(int64_zigzag_when, Values, Values0).
 1260% convert_segment_packed(Type, ContextType, Tag, Segment, Values) => % TODO: delete this clause
 1261%     domain_error(type(type=Type, % TODO: this is a bit funky
 1262%                       context_type=ContextType),
 1263%                  value(segment=Segment,
 1264%                        tag=Tag,
 1265%                        values=Values)).
 1266
 1267:- det(convert_segment/5). 1268%! convert_segment(+Type:atom, +ContextType:atom, Tag:atom, ?Segment, ?Value) is det.
 1269% Compute an appropriate =Value= from the combination of descriptor
 1270% "type" (in =Type=) and a =Segment=.
 1271% Reversible on =Segment=, =Values=.
 1272convert_segment('TYPE_DOUBLE', _ContextType, Tag, Segment0, Value) =>
 1273    Segment = fixed64(Tag,Int64),
 1274    int64_float64_when(Int64, Value),
 1275    protobuf_segment_convert(Segment0, Segment), !.
 1276convert_segment('TYPE_FLOAT', _ContextType, Tag, Segment0, Value) =>
 1277    Segment = fixed32(Tag,Int32),
 1278    int32_float32_when(Int32, Value),
 1279    protobuf_segment_convert(Segment0, Segment), !.
 1280convert_segment('TYPE_INT64', _ContextType, Tag, Segment0, Value) =>
 1281    Segment = varint(Tag,Value0),
 1282    uint64_int64_when(Value0, Value),
 1283    protobuf_segment_convert(Segment0, Segment), !.
 1284convert_segment('TYPE_UINT64', _ContextType, Tag, Segment0, Value) =>
 1285    Segment = varint(Tag,Value),
 1286    protobuf_segment_convert(Segment0, Segment), !.
 1287convert_segment('TYPE_INT32', _ContextType, Tag, Segment0, Value) =>
 1288    Segment = varint(Tag,Value0),
 1289    uint32_int32_when(Value0, Value),
 1290    protobuf_segment_convert(Segment0, Segment), !.
 1291convert_segment('TYPE_FIXED64', _ContextType, Tag, Segment0, Value) =>
 1292    Segment = fixed64(Tag,Value0),
 1293    uint64_int64_when(Value, Value0),
 1294    protobuf_segment_convert(Segment0, Segment), !.
 1295convert_segment('TYPE_FIXED32', _ContextType, Tag, Segment0, Value) =>
 1296    Segment = fixed32(Tag,Value0),
 1297    uint32_int32_when(Value, Value0),
 1298    protobuf_segment_convert(Segment0, Segment), !.
 1299convert_segment('TYPE_BOOL', _ContextType, Tag, Segment0, Value) =>
 1300    Segment = varint(Tag,Value0),
 1301    int_bool_when(Value0, Value),
 1302    protobuf_segment_convert(Segment0, Segment), !.
 1303% convert_segment('TYPE_STRING', _ContextType, Tag, Segment0, Value) =>
 1304%     Segment = string(Tag,ValueStr),
 1305%     protobuf_segment_convert(Segment0, Segment), !,
 1306%     (   false    % TODO: control whether atom or string with an option
 1307%     ->  atom_string(Value, ValueStr)
 1308%     ;   Value = ValueStr
 1309%     ).
 1310convert_segment('TYPE_STRING', _ContextType, Tag, Segment0, Value) =>
 1311    % TODO: option to control whether to use atom_string(Value,ValueStr)
 1312    Segment = string(Tag,Value),
 1313    protobuf_segment_convert(Segment0, Segment), !.
 1314convert_segment('TYPE_GROUP', ContextType, Tag, Segment0, Value) =>
 1315    Segment = group(Tag,MsgSegments),
 1316    % TODO: combine with TYPE_MESSAGE code:
 1317    (   nonvar(Value)
 1318    ->  dict_pairs(Value, _, FieldValues),
 1319        maplist(field_segment(ContextType), FieldValues, MsgSegments),
 1320        protobuf_segment_convert(Segment0, Segment)
 1321    ;   protobuf_segment_convert(Segment0, Segment),
 1322        maplist(segment_to_term(ContextType), MsgSegments, MsgFields),
 1323        combine_fields(MsgFields, ContextType{}, Value)
 1324    ), !.
 1325convert_segment('TYPE_MESSAGE', ContextType, Tag, Segment0, Value) =>
 1326    Segment = message(Tag,MsgSegments),
 1327    (   nonvar(Value)
 1328    ->  dict_pairs(Value, _, FieldValues),
 1329        maplist(field_segment(ContextType), FieldValues, MsgSegments),
 1330        protobuf_segment_convert(Segment0, Segment)
 1331    ;   protobuf_segment_convert(Segment0, Segment),
 1332        maplist(segment_to_term(ContextType), MsgSegments, MsgFields),
 1333        combine_fields(MsgFields, ContextType{}, Value)
 1334    ), !.
 1335convert_segment('TYPE_BYTES', _ContextType, Tag, Segment0, Value) =>
 1336    Segment = length_delimited(Tag,Value),
 1337    protobuf_segment_convert(Segment0, Segment), !.
 1338convert_segment('TYPE_UINT32', _ContextType, Tag, Segment0, Value) =>
 1339    Segment = varint(Tag,Value),
 1340    protobuf_segment_convert(Segment0, Segment), !.
 1341convert_segment('TYPE_ENUM', ContextType, Tag, Segment0, Value) =>
 1342    Segment = varint(Tag,Value0),
 1343    convert_enum(ContextType, Value, Value0), % TODO: negative values: https://github.com/SWI-Prolog/contrib-protobufs/issues/9
 1344    protobuf_segment_convert(Segment0, Segment), !.
 1345convert_segment('TYPE_SFIXED32', _ContextType, Tag, Segment0, Value) =>
 1346    Segment = fixed32(Tag,Value),
 1347    protobuf_segment_convert(Segment0, Segment), !.
 1348convert_segment('TYPE_SFIXED64', _ContextType, Tag, Segment0, Value) =>
 1349    Segment = fixed64(Tag,Value),
 1350    protobuf_segment_convert(Segment0, Segment), !.
 1351convert_segment('TYPE_SINT32', _ContextType, Tag, Segment0, Value) =>
 1352    Segment = varint(Tag,Value0),
 1353    int64_zigzag_when(Value, Value0),
 1354    protobuf_segment_convert(Segment0, Segment), !.
 1355convert_segment('TYPE_SINT64', _ContextType, Tag, Segment0, Value) =>
 1356    Segment = varint(Tag,Value0),
 1357    int64_zigzag_when(Value, Value0),
 1358    protobuf_segment_convert(Segment0, Segment), !.
 1359
 1360convert_enum(ContextType, Enum, Uint) :-
 1361    uint64_int64_when(Uint, Int),
 1362    proto_meta_enum_value_when(ContextType, Enum, Int).
 1363
 1364% TODO: use options to translate to/from false, true (see json_read/3)
 1365int_bool(0, false).
 1366int_bool(1, true).
 1367
 1368int_bool_when(Int, Bool) :-
 1369    when((nonvar(Int) ; nonvar(Bool)), int_bool(Int, Bool)).
 1370
 1371%! add_defaulted_fields(+Value0:dict, ContextType:atom, -Value:dict) is det.
 1372add_defaulted_fields(Value0, ContextType, Value) :-
 1373    % Can use bagof or findall if we know that there aren't any
 1374    % duplicated proto_meta_field_name/4 rules, although this isn't
 1375    % strictly necessary (just avoids processing a field twice).
 1376    ( setof(Name-DefaultValue, message_field_default(ContextType, Name, DefaultValue), DefaultValues)
 1377    ->  true
 1378    ;   DefaultValues = []
 1379    ),
 1380    foldl(add_empty_field_if_missing, DefaultValues, Value0, Value).
 1381
 1382%! message_field_default(+ContextType:atom, Name:atom, -DefaultValue) is semidet.
 1383message_field_default(ContextType, Name, DefaultValue) :-
 1384    proto_meta_field_name(ContextType, _FieldNumber, Name, Fqn),
 1385    proto_meta_field_default_value(Fqn, DefaultValue),
 1386    % If the field is part of a "oneof" group, then there will be a
 1387    % proto_meta_oneof entry for it (using the oneof_index). All
 1388    % fields have a oneof_index, but our code doesn't depend on that.
 1389    \+ (proto_meta_field_oneof_index(Fqn, OneofIndex),
 1390        proto_meta_oneof(ContextType, OneofIndex, _)).
 1391
 1392add_empty_field_if_missing(FieldName-DefaultValue, Dict0, Dict) :-
 1393    (   get_dict(FieldName, Dict0, _)
 1394    ->  Dict = Dict0
 1395    ;   put_dict(FieldName, Dict0, DefaultValue, Dict)
 1396    ).
 1397
 1398:- det(combine_fields/3). 1399%! combine_fields(+Fields:list, +MsgDict0, -MsgDict) is det.
 1400% Combines the fields into a dict and sets missing fields to their default values.
 1401% If the field is marked as 'norepeat' (optional/required), then the last
 1402%    occurrence is kept (as per the protobuf wire spec)
 1403% If the field is marked as 'repeat', then all the occurrences
 1404%    are put into a list, in order.
 1405% This code assumes that fields normally occur all together, but can handle
 1406% (less efficiently) fields not occurring together, as is allowed
 1407% by the protobuf spec.
 1408combine_fields([], MsgDict0, MsgDict) =>
 1409    is_dict(MsgDict0, ContextType),
 1410    add_defaulted_fields(MsgDict0, ContextType, MsgDict).
 1411combine_fields([field_and_value(Field,norepeat,Value)|Fields], MsgDict0, MsgDict) =>
 1412    put_dict(Field, MsgDict0, Value, MsgDict1),
 1413    combine_fields(Fields, MsgDict1, MsgDict).
 1414combine_fields([field_and_value(Field,repeat_packed,Values0)|Fields], MsgDict0, MsgDict) =>
 1415    (   get_dict(Field, MsgDict0, ExistingValues)
 1416    ->  append(ExistingValues, Values0, Values)
 1417    ;   Values = Values0
 1418    ),
 1419    put_dict(Field, MsgDict0, Values, MsgDict1),
 1420    combine_fields(Fields, MsgDict1, MsgDict).
 1421combine_fields([field_and_value(Field,repeat,Value)|Fields], MsgDict0, MsgDict) =>
 1422    combine_fields_repeat(Fields, Field, NewValues, RestFields),
 1423    (   get_dict(Field, MsgDict0, ExistingValues)
 1424    ->  append(ExistingValues, [Value|NewValues], Values)
 1425    ;   Values = [Value|NewValues]
 1426    ),
 1427    put_dict(Field, MsgDict0, Values, MsgDict1),
 1428    combine_fields(RestFields, MsgDict1, MsgDict).
 1429
 1430:- det(combine_fields_repeat/4). 1431%! combine_fields_repeat(+Fields:list, Field:atom, -Values:list, RestFields:list) is det.
 1432% Helper for combine_fields/3
 1433% Stops at the first item that doesn't match =Field= - the assumption
 1434% is that all the items for a field will be together and if they're
 1435% not, they would be combined outside this predicate.
 1436%
 1437% @param Fields a list of fields (Field-Repeat-Value)
 1438% @param Field the name of the field that is being combined
 1439% @param Values gets the Value items that match Field
 1440% @param RestFields gets any left-over fields
 1441combine_fields_repeat([], _Field, Values, RestFields) => Values = [], RestFields = [].
 1442combine_fields_repeat([Field-repeat-Value|Fields], Field, Values, RestFields) =>
 1443    Values = [Value|Values2],
 1444    combine_fields_repeat(Fields, Field, Values2, RestFields).
 1445combine_fields_repeat(Fields, _Field, Values, RestFields) => Values = [], RestFields = Fields.
 1446
 1447:- det(field_and_type/7). 1448%! field_and_type(+ContextType:atom, +Tag:int, -FieldName:atom, -FqnName:atom, -ContextType2:atom, -RepeatOptional:atom, -Type:atom) is det.
 1449% Lookup a =ContextType= and =Tag= to get the field name, type, etc.
 1450field_and_type(ContextType, Tag, FieldName, FqnName, ContextType2, RepeatOptional, Type) =>
 1451    assertion(ground(ContextType)), % TODO: remove
 1452    assertion(ground(Tag)), % TODO: remove
 1453    (   proto_meta_field_name(ContextType, Tag, FieldName, FqnName),
 1454        proto_meta_field_type_name(FqnName, ContextType2),
 1455        fqn_repeat_optional(FqnName, RepeatOptional),
 1456        proto_meta_field_type(FqnName, Type)
 1457    ->  true % Remove choicepoint, if JITI didn't do the right thing.
 1458    ;   existence_error(ContextType, Tag)
 1459    ).
 1460
 1461%! fqn_repeat_optional(+FqnName:atom, -RepeatOptional:atom) is det.
 1462% Lookup up proto_meta_field_label(FqnName, _), proto_meta_field_option_packed(FqnName)
 1463% and set RepeatOptional to one of
 1464% =norepeat=, =repeat=, =repeat_packed=.
 1465fqn_repeat_optional(FqnName, RepeatOptional) =>
 1466    % TODO: existence_error if \+ proto_meta_field_label
 1467    proto_meta_field_label(FqnName, LabelRepeatOptional),
 1468    (   LabelRepeatOptional = 'LABEL_REPEATED',
 1469        proto_meta_field_option_packed(FqnName)
 1470    ->  RepeatOptional = repeat_packed
 1471    ;   \+ proto_meta_field_option_packed(FqnName), % validity check
 1472        fqn_repeat_optional_2(LabelRepeatOptional, RepeatOptional)
 1473    ).
 1474
 1475:- det(fqn_repeat_optional_2/2). 1476%! fqn_repeat_optional_2(+DescriptorLabelEnum:atom, -RepeatOrEmpty:atom) is det.
 1477% Map the descriptor "label" to 'repeat' or 'norepeat'.
 1478% From proto_meta_enum_value('.google.protobuf.FieldDescriptorProto.Label', Label, _).
 1479fqn_repeat_optional_2('LABEL_OPTIONAL', norepeat).
 1480fqn_repeat_optional_2('LABEL_REQUIRED', norepeat).
 1481fqn_repeat_optional_2('LABEL_REPEATED', repeat).
 1482
 1483%! field_descriptor_label_repeated(+Label:atom) is semidet.
 1484% From proto_meta_enum_value('.google.protobuf.FieldDescriptorProto.Label', 'LABEL_REPEATED', _).
 1485% TODO: unused
 1486field_descriptor_label_repeated('LABEL_REPEATED').
 1487
 1488%! field_descriptor_label_single(+Label:atom) is semidet.
 1489% From proto_meta_enum_value('.google.protobuf.FieldDescriptorProto.Label', Label, _).
 1490field_descriptor_label_single('LABEL_OPTIONAL').
 1491field_descriptor_label_single('LABEL_REQUIRED').
 1492
 1493:- det(term_to_segments/3). 1494%! term_to_segments(+Term:dict, +MessageType:atom, Segments) is det.
 1495% Recursively traverse a =Term=, generating message segments
 1496term_to_segments(Term, MessageType, Segments) :-
 1497    dict_pairs(Term, _, FieldValues),
 1498    maplist(field_segment(MessageType), FieldValues, Segments).
 1499
 1500:- det(field_segment/3). 1501% MessageType is the FQN of the field type (e.g., '.test.Scalars1')
 1502% FieldName-Value is from the dict_pairs of the term.
 1503% TODO: Throw an error if proto_meta_field_name/4 fails (need to make
 1504%       sure of all the possible uses of field_segment/3 and that
 1505%       nothing depends on it being able to fail without an error).
 1506field_segment(MessageType, FieldName-Value, Segment) :-
 1507    (   proto_meta_field_name(MessageType, Tag, FieldName, FieldFqn),
 1508        proto_meta_field_type(FieldFqn, FieldType),
 1509        proto_meta_field_type_name(FieldFqn, FieldTypeName),
 1510        proto_meta_field_label(FieldFqn, Label)
 1511    ->  true  % Remove choicepoint, if JITI didn't do the right thing.
 1512    ;   existence_error(MessageType, FieldName-Value)
 1513    ),
 1514    (   proto_meta_field_option_packed(FieldFqn)
 1515    ->  Packed = packed
 1516    ;   Packed = not_packed
 1517    ),
 1518    field_segment_scalar_or_repeated(Label, Packed, FieldType, Tag, FieldTypeName, Value, Segment),
 1519    !. % TODO: remove
 1520
 1521:- det(field_segment_scalar_or_repeated/7). 1522%! field_segment_scalar_or_repeated(+Label, +Packed, +FieldType, +Tag, +FieldTypeName, ?Value, Segment) is det.
 1523% =FieldType= is from the =|.proto|= meta information ('TYPE_SINT32', etc.)
 1524field_segment_scalar_or_repeated('LABEL_OPTIONAL', not_packed, FieldType, Tag, FieldTypeName, Value, Segment) =>
 1525    convert_segment(FieldType, FieldTypeName, Tag, Segment, Value).
 1526field_segment_scalar_or_repeated('LABEL_REQUIRED', not_packed, FieldType, Tag, FieldTypeName, Value, Segment) =>  % same as LABEL_OPTIONAL
 1527    convert_segment(FieldType, FieldTypeName, Tag, Segment, Value).
 1528field_segment_scalar_or_repeated('LABEL_REPEATED', packed, FieldType, Tag, FieldTypeName, Values, Segment) =>
 1529    Segment = packed(Tag,FieldValues),
 1530    maplist(convert_segment_v_s(FieldType, FieldTypeName, Tag), Values, Segments0),
 1531    packed_list(Segments0, FieldValues).
 1532field_segment_scalar_or_repeated('LABEL_REPEATED', not_packed, FieldType, Tag, FieldTypeName, Values, Segment) =>
 1533    Segment = repeated(Segments),
 1534    maplist(convert_segment_v_s(FieldType, FieldTypeName, Tag), Values, Segments).
 1535% field_segment_scalar_or_repeated(Label, Packed, FieldType, Tag, FieldTypeName, Value, Segment) :- % TODO: delete this clause
 1536%     domain_error(type(field_type=FieldType,     % TODO: this is a bit funky
 1537%                       label=Label,
 1538%                       packed=Packed),
 1539%                  value(tag=Tag, field_type_name=FieldTypeName, value=Value, segment=Segment)).
 1540
 1541convert_segment_v_s(FieldType, FieldTypeName, Tag, Value, Segment) :-
 1542    convert_segment(FieldType, FieldTypeName, Tag, Segment, Value).
 1543
 1544% Convert [varint(1,10),varint(1,20)] to varint(1,[10,20]).
 1545packed_list([], []).
 1546packed_list([T1|Ts], PackedList) :-
 1547    detag(T1, Functor, Tag, _V1, List, PackedList),
 1548    packed_list_([T1|Ts], Functor, Tag, List).
 1549
 1550% Functor and Tag are only for verifying that the terms are of the
 1551% expected form.
 1552packed_list_([], _, _, []).
 1553packed_list_([T1|Ts], Functor, Tag, [X1|Xs]) :-
 1554    detag(T1, Functor, Tag, X1, _, _),
 1555    packed_list_(Ts, Functor, Tag, Xs).
 1556
 1557%! protobuf_field_is_map(+MessageType, +FieldName) is semidet.
 1558% Succeeds if =MessageType='s =FieldName= is defined as a map<...> in
 1559% the .proto file.
 1560protobuf_field_is_map(MessageType0, FieldName) :-
 1561    proto_meta_normalize(MessageType0, MessageType),
 1562    proto_meta_field_name(MessageType, _, FieldName, FieldFqn),
 1563    proto_meta_field_type(FieldFqn, 'TYPE_MESSAGE'),
 1564    proto_meta_field_label(FieldFqn, 'LABEL_REPEATED'),
 1565    proto_meta_field_type_name(FieldFqn, FieldTypeName),
 1566    proto_meta_message_type_map_entry(FieldTypeName),
 1567    assertion(proto_meta_field_name(FieldTypeName, 1, key, _)),
 1568    assertion(proto_meta_field_name(FieldTypeName, 2, value, _)),
 1569    !.
 1570
 1571%! protobuf_map_pairs(+ProtobufTermList:list, ?DictTag:atom, ?Pairs) is det.
 1572% Convert between a list of protobuf map entries (in the form
 1573% =|DictTag{key:Key, value:Value}|= and a key-value list as described
 1574% in library(pairs). At least one of =ProtobufTermList= and =Pairs=
 1575% must be instantiated; =DictTag= can be uninstantiated. If
 1576% =ProtobufTermList= is from a term created by
 1577% protobuf_parse_from_codes/3, the ordering of the items is undefined;
 1578% you can order them by using keysort/2 (or by a predicate such as
 1579% dict_pairs/3, list_to_assoc/2, or list_to_rbtree/2.
 1580protobuf_map_pairs(ProtobufTermList, DictTag, Pairs) :-
 1581    maplist(protobuf_dict_map_pairs(DictTag), ProtobufTermList, Pairs).
 1582
 1583protobuf_dict_map_pairs(DictTag, DictTag{key:Key,value:Value}, Key-Value)