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