1/*  File:    msgpackc.pl
    2    Author:  Roy Ratcliffe
    3    Created: Jan 19 2022
    4    Purpose: C-Based MessagePack for SWI-Prolog
    5
    6Copyright (c) 2022, Roy Ratcliffe, Northumberland, United Kingdom
    7
    8Permission is hereby granted, free of charge,  to any person obtaining a
    9copy  of  this  software  and    associated   documentation  files  (the
   10"Software"), to deal in  the   Software  without  restriction, including
   11without limitation the rights to  use,   copy,  modify,  merge, publish,
   12distribute, sublicense, and/or sell  copies  of   the  Software,  and to
   13permit persons to whom the Software is   furnished  to do so, subject to
   14the following conditions:
   15
   16    The above copyright notice and this permission notice shall be
   17    included in all copies or substantial portions of the Software.
   18
   19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT  WARRANTY OF ANY KIND, EXPRESS
   20OR  IMPLIED,  INCLUDING  BUT  NOT   LIMITED    TO   THE   WARRANTIES  OF
   21MERCHANTABILITY, FITNESS FOR A PARTICULAR   PURPOSE AND NONINFRINGEMENT.
   22IN NO EVENT SHALL THE AUTHORS  OR   COPYRIGHT  HOLDERS BE LIABLE FOR ANY
   23CLAIM, DAMAGES OR OTHER LIABILITY,  WHETHER   IN  AN ACTION OF CONTRACT,
   24TORT OR OTHERWISE, ARISING FROM,  OUT  OF   OR  IN  CONNECTION  WITH THE
   25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   26
   27*/
   28
   29:- module(msgpackc,
   30          [ msgpack//1,                         % ?Term
   31
   32            msgpack_object//1,                  % ?Object
   33            msgpack_objects//1,                 % ?Objects
   34
   35            msgpack_nil//0,
   36            msgpack_false//0,
   37            msgpack_true//0,
   38
   39            % float format family
   40            msgpack_float//1,                   % ?Float
   41            msgpack_float//2,                   % ?Width,?Float
   42
   43            % int format family
   44            msgpack_int//1,                     % ?Int
   45            msgpack_fixint//2,                  % ?Width,?Int
   46            msgpack_uint//2,                    % ?Width,?Int
   47            msgpack_int//2,                     % ?Width,?Int
   48
   49            % str format family
   50            msgpack_str//1,                     % ?Str
   51            msgpack_fixstr//1,                  % ?Str
   52            msgpack_str//2,                     % ?Width,?Str
   53
   54            % bin format family
   55            msgpack_bin//1,                     % ?Bytes
   56            msgpack_bin//2,                     % ?Width,?Bytes
   57
   58            % array format family
   59            msgpack_array//2,                   % :OnElement,?Array
   60
   61            % map format family
   62            msgpack_map//2,                     % :OnPair,?Map
   63
   64            % ext format family
   65            msgpack_ext//1,                     % ?Term
   66            msgpack_ext//2                      % ?Type,?Ext
   67          ]).   68:- autoload(library(dcg/high_order), [sequence//2, sequence/4]).   69:- autoload(library(utf8), [utf8_codes/3]).   70
   71:- use_foreign_library(foreign(msgpackc)).

C-Based MessagePack for SWI-Prolog

The predicates have three general categories.

  1. High-order recursive for normal use by application software.
  2. Parameterised mid-level grammar components such as msgpack_nil designed for two-way unification between fundamental types and their MessagePack byte encoded representations.
  3. Low-level C predicates and functions interfacing with the machine byte-swapping hardware.

Optimal message packing

Prolog has the uncanny ability to find optimal solutions to seemingly intractible problems. Back-tracking allows the message sender to search for the shortest message possible amongst all available encodings. In most cases, message transmittion latency presents the narrowest bottleneck. Encoding and decoding is just one small part. As message frequency and complexity increases, an optimal encoding might improve overall messaging throughput over channels with limited bandwidth. Optimisation could complete in microseconds whereas transmission improvements might aggregate to milliseconds.

author
- Roy Ratcliffe */
   99:- meta_predicate
  100    msgpack_array(3, ?, ?, ?),
  101    msgpack_map(3, ?, ?, ?),
  102    msgpack_dict(3, ?, ?, ?).  103
  104:- multifile msgpack:type_ext_hook/3.
 msgpack(?Term:compound)// is nondet
Where Term is a compound arity-1 functor, never a list term. The functor carries the format choice.

Packing arrays and maps necessarily recurses. Array elements are themselves objects; arrays are objects hence arrays of arrays nested up to any number of dimensions. Same goes for maps.

  115msgpack(nil) --> msgpack_nil, !.
  116msgpack(bool(false)) --> msgpack_false, !.
  117msgpack(bool(true)) --> msgpack_true, !.
  118msgpack(int(Int)) --> msgpack_int(Int), !.
  119msgpack(float(Float)) --> msgpack_float(Float), !.
  120msgpack(str(Str)) --> msgpack_str(Str), !.
  121msgpack(bin(Bin)) --> msgpack_bin(Bin), !.
  122msgpack(array(Array)) --> msgpack_array(msgpack, Array), !.
  123msgpack(map(Map)) --> msgpack_map(msgpack_pair(msgpack, msgpack), Map), !.
  124msgpack(Term) --> msgpack_ext(Term).
 msgpack_object(?Object)// is semidet
Encodes and decodes a single MessagePack object. Term encodes an object as follows.
  1. The nil object becomes Prolog nil atom rather than [] which Prolog calls "nil," the empty list termination. Prolog [] decodes an empty MessagePack array.
  2. Booleans become Prolog atoms false and true.
  3. Integers become Prolog integers.
  4. Floats become Prolog floats. Distinguishing between 32- and 64-bit float-point occurs by wrapping the Prolog-side in float(Precision, Number) terms where Precision selects 32 or 64 bits. Setting up an epsilon threshold allows for automatic precision adjustment when encoding.
  5. Strings in UTF-8 become Prolog strings, never atoms.
  6. Arrays become Prolog lists.
  7. Maps become Prolog dictionaries.

Unsigned and signed integers share a common pattern. The least-significant two bits, 00 through 11, select eight through 64 bits of width. The ordering of the MessagePack specification arranges the types in order to exploit this feature.

Prolog has no native type for raw binary objects in the vein of R's raw vector.

Notice that integer comes before float. This is important because Prolog integers can render as floats and vice versa provided that the integer is signed; it fails if unsigned.

  159msgpack_object(nil) --> msgpack_nil, !.
  160msgpack_object(false) --> msgpack_false, !.
  161msgpack_object(true) --> msgpack_true, !.
  162msgpack_object(Int) -->
  163    msgpack_int(Int),
  164    { integer(Int)
  165    },
  166    !.
  167msgpack_object(Float) -->
  168    msgpack_float(Float),
  169    { float(Float)
  170    },
  171    !.
  172msgpack_object(Str) --> msgpack_str(Str), !.
  173msgpack_object(bin(Bin)) --> msgpack_bin(Bin), !.
  174msgpack_object(Array) --> msgpack_array(msgpack_object, Array), !.
  175msgpack_object(Map) -->
  176    msgpack_dict(msgpack_pair(msgpack_key, msgpack_object), Map),
  177    !.
  178msgpack_object(ext(Ext)) --> msgpack_ext(Ext).
 msgpack_key(?Key:atomic)// is semidet
SWI Prolog dictionaries require atomic keys. Message packing allows any key types including arrays, sub-map, binaries and extensions. Map keys are only integer or atom under Prolog. Fail therefore for any other types; use msgpack//1 to accept non-atomic maps with keys of any kind.
Arguments:
Key- integer or atom used as map pair key.
  190msgpack_key(Key) --> msgpack_int(Key), !.
  191msgpack_key(Key) -->
  192    { var(Key),
  193      !
  194    },
  195    msgpack_str(Str),
  196    { atom_string(Key, Str)
  197    },
  198    !.
  199msgpack_key(Key) -->
  200    { atom(Key),
  201      atom_string(Key, Str)
  202    },
  203    msgpack_str(Str).
 msgpack_objects(?Objects)// is semidet
Zero or more MessagePack objects.
  209msgpack_objects(Objects) --> sequence(msgpack_object, Objects).
 msgpack_nil// is semidet
 msgpack_false// is semidet
 msgpack_true// is semidet
The simplest packing formats for nil and Booleans.
  217msgpack_nil --> [0xc0].
  218
  219msgpack_false --> [0xc2].
  220
  221msgpack_true --> [0xc3].
  222
  223/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  224
  225    float format family
  226
  227    +--------+--------+--------+--------+--------+
  228    |  0xca  |XXXXXXXX|XXXXXXXX|XXXXXXXX|XXXXXXXX| float 32
  229    +--------+--------+--------+--------+--------+
  230
  231    +--------+--------+--------+-------- / --------+--------+--------+
  232    |  0xcb  |YYYYYYYY|YYYYYYYY|YYYYYYYY / YYYYYYYY|YYYYYYYY|YYYYYYYY| float 64
  233    +--------+--------+--------+-------- / --------+--------+--------+
  234
  235- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_float(?Float)// is semidet
 msgpack_float(?Width, ?Float)// is nondet
Delivers two alternative solutions by design, both valid. Uses the different renderings to select the best compromise between 32- and 64-bit representation for any given number. Prolog lets the implementation explore the alternatives. Chooses 32 bits only when the least-significant 32 bits match zero. In this case, the 64-bit double representation is redundant because the 32-bit representation fully meets the resolution requirements of the float value.

The arity-1 (+) mode version of the predicate duplicates the encoding assumptions. The structure aims to implement precision width selection but without re-rendering. It first unifies a 64-bit float with eight bytes. Parsing from bytes to Float will fail if the bytes run out at the end of the byte stream.

Predicates float32//1 and float64//1 unify with integer-valued floats as well as floating-point values. This provides an alternative representation for many integers.

  258msgpack_float(Float) -->
  259  { float64(Float, Bytes, []),
  260    Bytes \= [_, _, _, _, 0, 0, 0, 0]
  261  },
  262  !,
  263  [0xcb|Bytes].
  264msgpack_float(Float) --> msgpack_float(_, Float), !.
  265
  266msgpack_float(32, Float) --> [0xca], float32(Float).
  267msgpack_float(64, Float) --> [0xcb], float64(Float).
  268
  269/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  270
  271    int format family
  272
  273    +--------+
  274    |0XXXXXXX| fixint, 0 to 127
  275    +--------+
  276
  277    +--------+
  278    |111XXXXX| fixint, -32 to -1
  279    +--------+
  280
  281    +--------+--------+
  282    |  0xcc  |ZZZZZZZZ| uint 8
  283    +--------+--------+
  284
  285    +--------+--------+--------+
  286    |  0xcd  |ZZZZZZZZ|ZZZZZZZZ| uint 16
  287    +--------+--------+--------+
  288
  289    +--------+--------+--------+--------+--------+
  290    |  0xce  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| uint 32
  291    +--------+--------+--------+--------+--------+
  292
  293    +--------+--------+--------+-------- / --------+--------+--------+
  294    |  0xcf  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ / ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| uint 64
  295    +--------+--------+--------+-------- / --------+--------+--------+
  296
  297    +--------+--------+
  298    |  0xd0  |ZZZZZZZZ| int 8
  299    +--------+--------+
  300
  301    +--------+--------+--------+
  302    |  0xd1  |ZZZZZZZZ|ZZZZZZZZ| int 16
  303    +--------+--------+--------+
  304
  305    +--------+--------+--------+--------+--------+
  306    |  0xd2  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| int 32
  307    +--------+--------+--------+--------+--------+
  308
  309    +--------+--------+--------+-------- / --------+--------+--------+
  310    |  0xd3  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ / ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| int 64
  311    +--------+--------+--------+-------- / --------+--------+--------+
  312
  313- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_int(?Int:integer)// is semidet
Finds the optimum integer representation, shortest first. Tries fixed integer at first which works for a small subset of integers between -32 and 127. If that fails because the integer falls outside that small range, the second attempt applies unsigned representation; it only applies signed formats for negatives. This assumes that the difference does not matter. An overlap exists between signed and unsigned integers.
  325msgpack_int(Int) --> msgpack_fixint(_, Int), !.
  326msgpack_int(Int) -->
  327    { integer(Int),
  328      Int < 0,
  329      !
  330    },
  331    msgpack_int(_, Int).
  332msgpack_int(Int) --> msgpack_uint(_, Int), !.
  333msgpack_int(Int) --> msgpack_int(_, Int).
 msgpack_fixint(?Width, ?Int)// is semidet
Width is the integer bit width, only 8 and never 16, 32 or 64.
  339msgpack_fixint(8, Int) --> fixint8(Int).
 fixint8(Int)// is semidet
Very similar to int8//1 except for adding an additional constraint: the Int must not fall below -32. All other constraints also apply for signed 8-bit integers. Rather than falling between -128 and 127 however, the fixed 8-bit integer does not overlap the bit patterns reserved for other MessagePack type codes.
  349fixint8(Int) -->
  350    int8(Int),
  351    { Int >= -32
  352    }.
 msgpack_uint(?Width, ?Int)// is nondet
 msgpack_int(?Width, ?Int)// is nondet
  357msgpack_uint( 8, Int) --> [0xcc],  uint8(Int).
  358msgpack_uint(16, Int) --> [0xcd], uint16(Int).
  359msgpack_uint(32, Int) --> [0xce], uint32(Int).
  360msgpack_uint(64, Int) --> [0xcf], uint64(Int).
  361
  362msgpack_int( 8, Int) --> [0xd0],  int8(Int).
  363msgpack_int(16, Int) --> [0xd1], int16(Int).
  364msgpack_int(32, Int) --> [0xd2], int32(Int).
  365msgpack_int(64, Int) --> [0xd3], int64(Int).
  366
  367/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  368
  369    str format family
  370
  371    +--------+========+
  372    |101XXXXX|  data  | fixstr
  373    +--------+========+
  374
  375    +--------+--------+========+
  376    |  0xd9  |YYYYYYYY|  data  | str 8
  377    +--------+--------+========+
  378
  379    +--------+--------+--------+========+
  380    |  0xda  |ZZZZZZZZ|ZZZZZZZZ|  data  | str 16
  381    +--------+--------+--------+========+
  382
  383    +--------+--------+--------+--------+--------+========+
  384    |  0xdb  |AAAAAAAA|AAAAAAAA|AAAAAAAA|AAAAAAAA|  data  | str 32
  385    +--------+--------+--------+--------+--------+========+
  386
  387- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_str(?Str)// is semidet
Unifies Str with the shortest packed UTF-8 string message.
  393msgpack_str(Str) --> msgpack_fixstr(Str), !.
  394msgpack_str(Str) --> msgpack_str(_, Str), !.
 msgpack_fixstr(?Str)// is semidet
Unifies MessagePack byte codes with fixed Str of length between 0 and 31 inclusive.
  401msgpack_fixstr(Str) -->
  402    { var(Str),
  403      !
  404    },
  405    uint8(Format),
  406    { fixstr_format_length(Format, Length),
  407      length(Bytes, Length)
  408    },
  409    sequence(byte, Bytes),
  410    { phrase(utf8_codes(Codes), Bytes),
  411      string_codes(Str, Codes)
  412    }.
  413msgpack_fixstr(Str) -->
  414    { string(Str),
  415      string_codes(Str, Codes),
  416      phrase(utf8_codes(Codes), Bytes),
  417      length(Bytes, Length),
  418      fixstr_format_length(Format, Length)
  419    },
  420    [Format],
  421    sequence(byte, Bytes).
  422
  423fixstr_format_length(Format, Length), var(Format) =>
  424    Format is 0b101 00000 + Length,
  425    fixstr_format(Format).
  426fixstr_format_length(Format, Length) =>
  427    fixstr_format(Format),
  428    Length is Format - 0b101 00000.
  429
  430fixstr_format(Format) :-
  431    Format >= 0b101 00000,
  432    Format =< 0b101 11111.
 msgpack_str(?Width, ?Str)// is semidet
Refactors common string-byte unification utilised by all string grammars for the MessagePack protocol's 8, 16 and 32 bit lengths. Unifies for Length number of bytes for Str. Length is not the length of Str in Unicodes but the number of bytes in its UTF-8 representation.
  442msgpack_str(Width, Str) -->
  443    { var(Str),
  444      !,
  445      str_width_format(Width, Format)
  446    },
  447    [Format],
  448    uint(Width, Length),
  449    { length(Bytes, Length)
  450    },
  451    sequence(byte, Bytes),
  452    { phrase(utf8_codes(Codes), Bytes),
  453      string_codes(Str, Codes)
  454    }.
  455msgpack_str(Width, Str) -->
  456    { string(Str),
  457      str_width_format(Width, Format),
  458      string_codes(Str, Codes),
  459      phrase(utf8_codes(Codes), Bytes),
  460      length(Bytes, Length)
  461    },
  462    [Format],
  463    uint(Width, Length),
  464    sequence(byte, Bytes).
  465
  466str_width_format( 8, 0xd9).
  467str_width_format(16, 0xda).
  468str_width_format(32, 0xdb).
  469
  470/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  471
  472    bin format family
  473
  474    +--------+--------+========+
  475    |  0xc4  |XXXXXXXX|  data  | bin 8
  476    +--------+--------+========+
  477
  478    +--------+--------+--------+========+
  479    |  0xc5  |YYYYYYYY|YYYYYYYY|  data  | bin 16
  480    +--------+--------+--------+========+
  481
  482    +--------+--------+--------+--------+--------+========+
  483    |  0xc6  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|  data  | bin 32
  484    +--------+--------+--------+--------+--------+========+
  485
  486- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_bin(?Bytes)// is semidet
Succeeds only once when Bytes unifies with the MessagePack byte stream for the first time. Relies on the width ordering: low to high and attempts 8 bits first, 16 bits next and finally 32. Fails if 32 bits is not enough to unify the number of bytes because the byte-list has more than four thousand megabytes.
  496msgpack_bin(Bytes) --> msgpack_bin(_, Bytes), !.
 msgpack_bin(?Width, ?Bytes:list)// is nondet
Works very much like the string grammar except that the Bytes remain as 8-bit byte lists.
  503msgpack_bin(Width, Bytes) -->
  504    { var(Bytes),
  505      !,
  506      bin_width_format(Width, Format)
  507    },
  508    [Format],
  509    uint(Width, Length),
  510    { length(Bytes, Length)
  511    },
  512    sequence(byte, Bytes).
  513msgpack_bin(Width, Bytes) -->
  514    { is_list(Bytes),
  515      bin_width_format(Width, Format),
  516      length(Bytes, Length)
  517    },
  518    [Format],
  519    uint(Width, Length),
  520    sequence(byte, Bytes).
  521
  522bin_width_format( 8, 0xc4).
  523bin_width_format(16, 0xc5).
  524bin_width_format(32, 0xc6).
  525
  526/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  527
  528    array format family
  529
  530    +--------+~~~~~~~~~~~~~~~~~+
  531    |1001XXXX|    X objects    | fixarray
  532    +--------+~~~~~~~~~~~~~~~~~+
  533
  534    +--------+--------+--------+~~~~~~~~~~~~~~~~~+
  535    |  0xdc  |YYYYYYYY|YYYYYYYY|    Y objects    | array 16
  536    +--------+--------+--------+~~~~~~~~~~~~~~~~~+
  537
  538    +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+
  539    |  0xdd  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|    Z objects    | array 32
  540    +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+
  541
  542- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_array(:OnElement, ?Array:list)// is semidet
Unify with Array using OnElement as the per-element grammar predicate.
  549msgpack_array(OnElement, Array) --> msgpack_fixarray(OnElement, Array), !.
  550msgpack_array(OnElement, Array) --> msgpack_array(OnElement, _, Array), !.
 msgpack_fixarray(:OnElement, Array)// is semidet
 msgpack_array(:OnElement, ?Width, ?Array)// is nondet
Non-deterministically unify with Array of MessagePack objects, zero or more msgpack_object(Object) phrases.

Does not prescribe how to extract the elements. OnElement defines the sequence's element.

  561msgpack_fixarray(OnElement, Array) -->
  562    { var(Array),
  563      !
  564    },
  565    uint8(Format),
  566    { fixarray_format_length(Format, Length),
  567      length(Array, Length)
  568    },
  569    sequence(OnElement, Array).
  570msgpack_fixarray(OnElement, Array) -->
  571    { is_list(Array),
  572      length(Array, Length),
  573      fixarray_format_length(Format, Length)
  574    },
  575    [Format],
  576    sequence(OnElement, Array).
  577
  578fixarray_format_length(Format, Length) :-
  579    fix_format_length(shift(0b1001, 4), Format, Length).
  580
  581msgpack_array(OnElement, Width, Array) -->
  582    { var(Array),
  583      !,
  584      array_width_format(Width, Format)
  585    },
  586    [Format],
  587    uint(Width, Length),
  588    { length(Array, Length)
  589    },
  590    sequence(OnElement, Array).
  591msgpack_array(OnElement, Width, Array) -->
  592    { is_list(Array),
  593      array_width_format(Width, Format),
  594      length(Array, Length)
  595    },
  596    [Format],
  597    uint(Width, Length),
  598    sequence(OnElement, Array).
  599
  600array_width_format(16, 0xdc).
  601array_width_format(32, 0xdd).
  602
  603/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  604
  605    map format family
  606
  607    +--------+~~~~~~~~~~~~~~~~~+
  608    |1000XXXX|   X*2 objects   | fixmap
  609    +--------+~~~~~~~~~~~~~~~~~+
  610
  611    +--------+--------+--------+~~~~~~~~~~~~~~~~~+
  612    |  0xde  |YYYYYYYY|YYYYYYYY|   Y*2 objects   | map 16
  613    +--------+--------+--------+~~~~~~~~~~~~~~~~~+
  614
  615    +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+
  616    |  0xdf  |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|   Z*2 objects   | map 32
  617    +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+
  618
  619- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_map(:OnPair, ?Map:list)// is semidet
Unify with Map using OnPair as the pair-wise grammar.
  625msgpack_map(OnPair, Map) --> msgpack_fixmap(OnPair, Map), !.
  626msgpack_map(OnPair, Map) --> msgpack_map(OnPair, _, Map), !.
  627
  628msgpack_fixmap(OnPair, Map) -->
  629    { var(Map),
  630      !
  631    },
  632    [Format],
  633    { fixmap_format_length(Format, Length),
  634      length(Map, Length)
  635    },
  636    sequence(OnPair, Map).
  637msgpack_fixmap(OnPair, Map) -->
  638    { is_list(Map),
  639      length(Map, Length),
  640      fixmap_format_length(Format, Length)
  641    },
  642    [Format],
  643    sequence(OnPair, Map).
  644
  645fixmap_format_length(Format, Length) :-
  646    fix_format_length(shift(0b1000, 4), Format, Length).
  647
  648msgpack_map(OnPair, Width, Map) -->
  649    { var(Map),
  650      !,
  651      map_width_format(Width, Format)
  652    },
  653    [Format],
  654    uint(Width, Length),
  655    { length(Map, Length)
  656    },
  657    sequence(OnPair, Map).
  658msgpack_map(OnPair, Width, Map) -->
  659    { is_list(Map),
  660      map_width_format(Width, Format),
  661      length(Map, Length)
  662    },
  663    [Format],
  664    uint(Width, Length),
  665    sequence(OnPair, Map).
  666
  667map_width_format(16, 0xde).
  668map_width_format(32, 0xdf).
  669
  670msgpack_pair(OnKey, OnValue, Key-Value) -->
  671    call(OnKey, Key),
  672    call(OnValue, Value).
  673
  674msgpack_dict(OnPair, Dict) -->
  675    { var(Dict),
  676      !
  677    },
  678    msgpack_map(OnPair, Pairs),
  679    { dict_create(Dict, _, Pairs)
  680    }.
  681msgpack_dict(OnPair, Dict) -->
  682    { dict_pairs(Dict, _, Pairs)
  683    },
  684    msgpack_map(OnPair, Pairs).
  685
  686/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  687
  688    ext format family
  689
  690- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
 msgpack_ext(?Term)// is semidet
In (++) mode, meaning fully ground with no variables, the ++Term first unifies Term with its Type and Ext bytes using type_ext_hook/3 multi-file predicate.
  698msgpack_ext(Term) -->
  699    { ground(Term),
  700      !,
  701      msgpack:type_ext_hook(Type, Ext, Term)
  702    },
  703    msgpack_ext(Type, Ext).
  704msgpack_ext(Term) -->
  705    msgpack_ext(Type, Ext),
  706    !,
  707    { msgpack:type_ext_hook(Type, Ext, Term)
  708    }.
 msgpack_ext(?Type, ?Ext)// is semidet
Type is a signed integer. Ext is a list of byte codes.
  714msgpack_ext(Type, Ext) --> msgpack_fixext(Type, Ext), !.
  715msgpack_ext(Type, Ext) --> msgpack_ext(_, Type, Ext), !.
  716
  717msgpack_fixext(Type, Ext) -->
  718    { var(Type),
  719      var(Ext),
  720      !,
  721      fixext_length_format(Length, Format)
  722    },
  723    [Format],
  724    int8(Type),
  725    { length(Ext, Length)
  726    },
  727    sequence(byte, Ext).
  728msgpack_fixext(Type, Ext) -->
  729    { integer(Type),
  730      is_list(Ext),
  731      fixext_length_format(Length, Format),
  732      length(Ext, Length)
  733    },
  734    [Format],
  735    int8(Type),
  736    sequence(byte, Ext).
  737
  738fixext_length_format( 1, 0xd4).
  739fixext_length_format( 2, 0xd5).
  740fixext_length_format( 4, 0xd6).
  741fixext_length_format( 8, 0xd7).
  742fixext_length_format(16, 0xd8).
  743
  744msgpack_ext(Width, Type, Ext) -->
  745    { var(Ext),
  746      !,
  747      ext_width_format(Width, Format)
  748    },
  749    [Format],
  750    uint(Width, Length),
  751    int8(Type),
  752    { length(Ext, Length)
  753    },
  754    sequence(byte, Ext).
  755msgpack_ext(Width, Type, Ext) -->
  756    { integer(Type),
  757      is_list(Ext),
  758      ext_width_format(Width, Format),
  759      length(Ext, Length)
  760    },
  761    [Format],
  762    uint(Width, Length),
  763    int8(Type),
  764    sequence(byte, Ext).
  765
  766ext_width_format( 8, 0xc7).
  767ext_width_format(16, 0xc8).
  768ext_width_format(32, 0xc9).
 msgpack:type_ext_hook(Type:integer, Ext:list, Term) is semidet
Parses the extension byte block.

The timestamp extension encodes seconds and nanoseconds since 1970, also called Unix epoch time. Three alternative encodings exist: 4 bytes, 8 bytes and 12 bytes.

  778msgpack:type_ext_hook(-1, Ext, timestamp(Epoch)) :-
  779    once(phrase(timestamp(Epoch), Ext)).
  780
  781timestamp(Epoch) -->
  782    { var(Epoch)
  783    },
  784    epoch(Epoch).
  785timestamp(Epoch) -->
  786    { number(Epoch),
  787      Epoch >= 0,
  788      tv(Epoch, Seconds, NanoSeconds)
  789    },
  790    sec_nsec(Seconds, NanoSeconds).
  791
  792epoch(Epoch) -->
  793    int32(Epoch).
  794epoch(Epoch) -->
  795    uint64(UInt64),
  796    { NanoSeconds is UInt64 >> 34,
  797      NanoSeconds < 1 000 000 000,
  798      Seconds is UInt64 /\ ((1 << 34) - 1),
  799      tv(Epoch, Seconds, NanoSeconds)
  800    }.
  801epoch(Epoch) -->
  802    int32(NanoSeconds),
  803    int64(Seconds),
  804    { tv(Epoch, Seconds, NanoSeconds)
  805    }.
  806
  807sec_nsec(Seconds, 0) -->
  808    { Seconds < (1 << 32)
  809    },
  810    int32(Seconds).
  811sec_nsec(Seconds, NanoSeconds) -->
  812    { Seconds < (1 << 34),
  813      UInt64 is (NanoSeconds << 34) \/ Seconds
  814    },
  815    uint64(UInt64).
  816sec_nsec(Seconds, NanoSeconds) -->
  817    int32(NanoSeconds),
  818    int64(Seconds).
 tv(?Epoch:number, ?Sec:number, ?NSec:number) is det
Uses floor/1 when computing Sec and round/1 for NSec. Time only counts completed seconds and time runs up. Asking for the integer part of a float does not give an integer. It gives the float-point value that matches the integer.

The arguments have number type by design. The predicate supports negatives; Epoch of -1.1 for example gives -1 seconds, -100,000,000 nanoseconds.

  831tv(Epoch, Sec, NSec), var(Epoch) =>
  832    abs(NSec) < 1 000 000 000,
  833    Epoch is Sec + (NSec / 1e9).
  834tv(Epoch, Sec, NSec), number(Epoch) =>
  835    Sec is floor(float_integer_part(Epoch)),
  836    NSec is round(1e9 * float_fractional_part(Epoch)).
 fix_format_length(Fix, Format, Length) is semidet
Useful tool for unifying a Format and Length using a Fix where Fix typically matches a Min-Max pair. The Fix can also have the shift(Bits, Left) form where the amount of Left shift implies the minimum and maximum range.
  845fix_format_length(Fix, Format, Length), var(Format) =>
  846    fix_min_max(Fix, Min, Max),
  847    Format is Min + Length,
  848    Format >= Min,
  849    Format =< Max.
  850fix_format_length(Fix, Format, Length), integer(Format) =>
  851    fix_min_max(Fix, Min, Max),
  852    Format >= Min,
  853    Format =< Max,
  854    Length is Format - Min.
  855
  856fix_min_max(Min-Max, Min, Max) => true.
  857fix_min_max(shift(Bits, Left), Min, Max) =>
  858    Min is Bits << Left,
  859    Max is Min \/ ((1 << Left) - 1).
 float(?Width, ?Float)// is nondet
 uint(?Width, ?Int)// is nondet
 int(?Width, ?Int)// is nondet
Wraps the underlying C big- and little-endian support functions for unifying bytes with floats and integers.
  868float(32, Float) --> float32(Float).
  869float(64, Float) --> float64(Float).
  870
  871uint( 8, Int) -->  uint8(Int).
  872uint(16, Int) --> uint16(Int).
  873uint(32, Int) --> uint32(Int).
  874uint(64, Int) --> uint64(Int).
  875
  876int( 8, Int) -->  int8(Int).
  877int(16, Int) --> int16(Int).
  878int(32, Int) --> int32(Int).
  879int(64, Int) --> int64(Int).
 byte(?Byte)// is semidet
 uint8(?Int)// is semidet
 int8(?Int)// is semidet
Simplifies the MessagePack grammar by asserting Byte constraints. Every Byte is an integer in-between 0 and 255 inclusive; fails semi-deterministically otherwise. Other high-level grammer components can presume these contraints as a baseline and assert any addition limits appropriately.

Predicate uint8//1 is just a synonym for byte//1. The int8//1 grammar accounts for signed integers between -128 through 127 inclusive.

Importantly, phrases such as the following example fail. There is no byte sequence that represents an unsigned integer in 8 bits. Other sub-grammars for MessagePack depend on this type of last-stage back-tracking while exploring the realm of possible matches.

phrase(msgpackc:uint8(256), _)
To be done
- A reasable argument exists for translating byte//1 and all the 8-bit grammar components to C for performance reasons; either that or in its stead some performance benchmarking work that demonstrates negligable difference.
  908byte(Byte) -->
  909    [Byte],
  910    { integer(Byte),
  911      Byte >= 0x00,
  912      Byte =< 0xff
  913    }.
  914
  915uint8(Int) --> byte(Int).
  916
  917int8(Int) -->
  918    byte(Int),
  919    { Int =< 0x7f
  920    },
  921    !.
  922int8(Int) -->
  923    { var(Int)
  924    },
  925    byte(Byte),
  926    { Byte >= 0x80,
  927      Int is Byte - 0x100
  928    },
  929    !.
  930int8(Int) -->
  931    { integer(Int),
  932      % Now that Int is non-variable and an integer, just reverse
  933      % the Int from Byte solution above: swap the sides, add 256 to
  934      % both sides and swap the compute and threshold comparison; at
  935      % this point Int must be negative. Grammar at byte//1 will
  936      % catch Int values greater than -1.
  937      Byte is 0x100 + Int
  938    },
  939    byte(Byte)