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, 2025, 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_key//1, % ?Key 34 msgpack_objects//1, % ?Objects 35 36 msgpack_nil//0, 37 msgpack_false//0, 38 msgpack_true//0, 39 40 % float format family 41 msgpack_float//1, % ?Float 42 msgpack_float//2, % ?Width,?Float 43 44 % int format family 45 msgpack_int//1, % ?Int 46 msgpack_fixint//2, % ?Width,?Int 47 msgpack_uint//2, % ?Width,?Int 48 msgpack_int//2, % ?Width,?Int 49 50 % str format family 51 msgpack_str//1, % ?Str 52 msgpack_fixstr//1, % ?Str 53 msgpack_str//2, % ?Width,?Str 54 55 % bin format family 56 msgpack_bin//1, % ?Bytes 57 msgpack_bin//2, % ?Width,?Bytes 58 59 % array format family 60 msgpack_array//2, % :OnElement,?Array 61 62 % map format family 63 msgpack_map//2, % :OnPair,?Map 64 msgpack_map//1, % ?Map 65 msgpack_pair//3, % :OnKey,:OnValue,KeyValuePair 66 67 % ext format family 68 msgpack_ext//1, % ?Term 69 msgpack_ext//2 % ?Type,?Ext 70 ]). 71:- autoload(library(dcg/high_order), [sequence//2]). 72:- autoload(library(utf8), [utf8_codes/3]). 73 74:- use_foreign_library(foreign(msgpackc)).
102:- meta_predicate 103 msgpack_array( , , , ), 104 msgpack_map( , , , ), 105 msgpack_dict( , , , ). 106 107:- multifile msgpack:type_ext_hook/3.
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.
118msgpack(nil) --> msgpack_nil, !. 119msgpack(bool(false)) --> msgpack_false, !. 120msgpack(bool(true)) --> msgpack_true, !. 121msgpack(int(Int)) --> msgpack_int(Int), !. 122msgpack(float(Float)) --> msgpack_float(Float), !. 123msgpack(str(Str)) --> msgpack_str(Str), !. 124msgpack(bin(Bin)) --> msgpack_bin(Bin), !. 125msgpack(array(Array)) --> msgpack_array(msgpack, Array), !. 126msgpack(map(Map)) --> msgpack_map(Map), !. 127msgpack(Term) --> msgpack_ext(Term).
nil
atom rather than []
which Prolog calls "nil," the empty list termination. Prolog []
decodes an empty MessagePack array.false
and true
.float(Precision, Number)
terms where Precision selects 32 or 64
bits. Setting up an epsilon threshold allows for automatic
precision adjustment when encoding.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.
162msgpack_object(nil) --> msgpack_nil, !. 163msgpack_object(false) --> msgpack_false, !. 164msgpack_object(true) --> msgpack_true, !. 165msgpack_object(Int) --> 166 msgpack_int(Int), 167 { integer(Int) 168 }, 169 !. 170msgpack_object(Float) --> 171 msgpack_float(Float), 172 { float(Float) 173 }, 174 !. 175msgpack_object(Str) --> msgpack_str(Str), !. 176msgpack_object(bin(Bin)) --> msgpack_bin(Bin), !. 177msgpack_object(Array) --> msgpack_array(msgpack_object, Array), !. 178msgpack_object(Map) --> 179 msgpack_dict(msgpack_pair(msgpack_key, msgpack_object), Map), 180 !. 181msgpack_object(ext(Ext)) --> msgpack_ext(Ext).
193msgpack_key(Key) --> msgpack_int(Key), !. 194msgpack_key(Key) --> 195 { var(Key), 196 ! 197 }, 198 msgpack_str(Str), 199 { atom_string(Key, Str) 200 }, 201 !. 202msgpack_key(Key) --> 203 { atom(Key), 204 atom_string(Key, Str) 205 }, 206 msgpack_str(Str).
212msgpack_objects(Objects) --> sequence(msgpack_object, Objects).
220msgpack_nil --> [0xc0]. 221 222msgpack_false --> [0xc2]. 223 224msgpack_true --> [0xc3]. 225 226/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 227 228 float format family 229 230 +--------+--------+--------+--------+--------+ 231 | 0xca |XXXXXXXX|XXXXXXXX|XXXXXXXX|XXXXXXXX| float 32 232 +--------+--------+--------+--------+--------+ 233 234 +--------+--------+--------+-------- / --------+--------+--------+ 235 | 0xcb |YYYYYYYY|YYYYYYYY|YYYYYYYY / YYYYYYYY|YYYYYYYY|YYYYYYYY| float 64 236 +--------+--------+--------+-------- / --------+--------+--------+ 237 238- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
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.
261msgpack_float(Float) --> 262 { float64(Float, Bytes, []), 263 Bytes \= [_, _, _, _, 0, 0, 0, 0] 264 }, 265 !, 266 [0xcb], 267 . 268msgpack_float(Float) --> msgpack_float(_, Float). 269 270msgpack_float(32, Float) --> [0xca], float32(Float). 271msgpack_float(64, Float) --> [0xcb], float64(Float). 272 273/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 274 275 int format family 276 277 +--------+ 278 |0XXXXXXX| fixint, 0 to 127 279 +--------+ 280 281 +--------+ 282 |111XXXXX| fixint, -32 to -1 283 +--------+ 284 285 +--------+--------+ 286 | 0xcc |ZZZZZZZZ| uint 8 287 +--------+--------+ 288 289 +--------+--------+--------+ 290 | 0xcd |ZZZZZZZZ|ZZZZZZZZ| uint 16 291 +--------+--------+--------+ 292 293 +--------+--------+--------+--------+--------+ 294 | 0xce |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| uint 32 295 +--------+--------+--------+--------+--------+ 296 297 +--------+--------+--------+-------- / --------+--------+--------+ 298 | 0xcf |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ / ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| uint 64 299 +--------+--------+--------+-------- / --------+--------+--------+ 300 301 +--------+--------+ 302 | 0xd0 |ZZZZZZZZ| int 8 303 +--------+--------+ 304 305 +--------+--------+--------+ 306 | 0xd1 |ZZZZZZZZ|ZZZZZZZZ| int 16 307 +--------+--------+--------+ 308 309 +--------+--------+--------+--------+--------+ 310 | 0xd2 |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| int 32 311 +--------+--------+--------+--------+--------+ 312 313 +--------+--------+--------+-------- / --------+--------+--------+ 314 | 0xd3 |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ / ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| int 64 315 +--------+--------+--------+-------- / --------+--------+--------+ 316 317- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
329msgpack_int(Int) --> msgpack_fixint(_, Int), !. 330msgpack_int(Int) --> 331 { integer(Int), 332 Int < 0, 333 ! 334 }, 335 msgpack_int(_, Int). 336msgpack_int(Int) --> msgpack_uint(_, Int), !. 337msgpack_int(Int) --> msgpack_int(_, Int).
343msgpack_fixint(8, Int) --> fixint8(Int).
353fixint8(Int) -->
354 int8(Int),
355 { Int >= -32
356 }.
361msgpack_uint( 8, Int) --> [0xcc], uint8(Int). 362msgpack_uint(16, Int) --> [0xcd], uint16(Int). 363msgpack_uint(32, Int) --> [0xce], uint32(Int). 364msgpack_uint(64, Int) --> [0xcf], uint64(Int). 365 366msgpack_int( 8, Int) --> [0xd0], int8(Int). 367msgpack_int(16, Int) --> [0xd1], int16(Int). 368msgpack_int(32, Int) --> [0xd2], int32(Int). 369msgpack_int(64, Int) --> [0xd3], int64(Int). 370 371/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 372 373 str format family 374 375 +--------+========+ 376 |101XXXXX| data | fixstr 377 +--------+========+ 378 379 +--------+--------+========+ 380 | 0xd9 |YYYYYYYY| data | str 8 381 +--------+--------+========+ 382 383 +--------+--------+--------+========+ 384 | 0xda |ZZZZZZZZ|ZZZZZZZZ| data | str 16 385 +--------+--------+--------+========+ 386 387 +--------+--------+--------+--------+--------+========+ 388 | 0xdb |AAAAAAAA|AAAAAAAA|AAAAAAAA|AAAAAAAA| data | str 32 389 +--------+--------+--------+--------+--------+========+ 390 391- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
397msgpack_str(Str) --> msgpack_fixstr(Str), !. 398msgpack_str(Str) --> msgpack_str(_, Str).
405msgpack_fixstr(Str) --> 406 { var(Str), 407 ! 408 }, 409 uint8(Format), 410 { fixstr_format_length(Format, Length), 411 length(Bytes, Length) 412 }, 413 sequence(byte, Bytes), 414 { phrase(utf8_codes(Codes), Bytes), 415 string_codes(Str, Codes) 416 }. 417msgpack_fixstr(Str) --> 418 { string(Str), 419 string_codes(Str, Codes), 420 phrase(utf8_codes(Codes), Bytes), 421 length(Bytes, Length), 422 fixstr_format_length(Format, Length) 423 }, 424 [Format], 425 sequence(byte, Bytes). 426 427fixstr_format_length(Format, Length), var(Format) => 428 Format is 0b101 00000 + Length, 429 fixstr_format(Format). 430fixstr_format_length(Format, Length) => 431 fixstr_format(Format), 432 Length is Format - 0b101 00000. 433 434fixstr_format(Format) :- 435 Format >= 0b101 00000, 436 Format =< 0b101 11111.
446msgpack_str(Width, Str) --> 447 { var(Str), 448 !, 449 str_width_format(Width, Format) 450 }, 451 [Format], 452 uint(Width, Length), 453 { length(Bytes, Length) 454 }, 455 sequence(byte, Bytes), 456 { phrase(utf8_codes(Codes), Bytes), 457 string_codes(Str, Codes) 458 }. 459msgpack_str(Width, Str) --> 460 { string(Str), 461 str_width_format(Width, Format), 462 string_codes(Str, Codes), 463 phrase(utf8_codes(Codes), Bytes), 464 length(Bytes, Length) 465 }, 466 [Format], 467 uint(Width, Length), 468 sequence(byte, Bytes). 469 470str_width_format( 8, 0xd9). 471str_width_format(16, 0xda). 472str_width_format(32, 0xdb). 473 474/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 475 476 bin format family 477 478 +--------+--------+========+ 479 | 0xc4 |XXXXXXXX| data | bin 8 480 +--------+--------+========+ 481 482 +--------+--------+--------+========+ 483 | 0xc5 |YYYYYYYY|YYYYYYYY| data | bin 16 484 +--------+--------+--------+========+ 485 486 +--------+--------+--------+--------+--------+========+ 487 | 0xc6 |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| data | bin 32 488 +--------+--------+--------+--------+--------+========+ 489 490- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
500msgpack_bin(Bytes) --> msgpack_bin(_, Bytes).
507msgpack_bin(Width, Bytes) --> 508 { var(Bytes), 509 !, 510 bin_width_format(Width, Format) 511 }, 512 [Format], 513 uint(Width, Length), 514 { length(Bytes, Length) 515 }, 516 sequence(byte, Bytes). 517msgpack_bin(Width, Bytes) --> 518 { is_list(Bytes), 519 bin_width_format(Width, Format), 520 length(Bytes, Length) 521 }, 522 [Format], 523 uint(Width, Length), 524 sequence(byte, Bytes). 525 526bin_width_format( 8, 0xc4). 527bin_width_format(16, 0xc5). 528bin_width_format(32, 0xc6). 529 530/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 531 532 array format family 533 534 +--------+~~~~~~~~~~~~~~~~~+ 535 |1001XXXX| X objects | fixarray 536 +--------+~~~~~~~~~~~~~~~~~+ 537 538 +--------+--------+--------+~~~~~~~~~~~~~~~~~+ 539 | 0xdc |YYYYYYYY|YYYYYYYY| Y objects | array 16 540 +--------+--------+--------+~~~~~~~~~~~~~~~~~+ 541 542 +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+ 543 | 0xdd |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| Z objects | array 32 544 +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+ 545 546- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
553msgpack_array(OnElement, Array) --> msgpack_fixarray(OnElement, Array), !. 554msgpack_array(OnElement, Array) --> msgpack_array(OnElement, _, Array).
msgpack_object(Object)
phrases.
Does not prescribe how to extract the elements. OnElement defines the sequence's element.
565msgpack_fixarray(OnElement, Array) --> 566 { var(Array), 567 ! 568 }, 569 uint8(Format), 570 { fixarray_format_length(Format, Length), 571 length(Array, Length) 572 }, 573 sequence(OnElement, Array). 574msgpack_fixarray(OnElement, Array) --> 575 { is_list(Array), 576 length(Array, Length), 577 fixarray_format_length(Format, Length) 578 }, 579 [Format], 580 sequence(OnElement, Array). 581 582fixarray_format_length(Format, Length) :- 583 fix_format_length(shift(0b1001, 4), Format, Length). 584 585msgpack_array(OnElement, Width, Array) --> 586 { var(Array), 587 !, 588 array_width_format(Width, Format) 589 }, 590 [Format], 591 uint(Width, Length), 592 { length(Array, Length) 593 }, 594 sequence(OnElement, Array). 595msgpack_array(OnElement, Width, Array) --> 596 { is_list(Array), 597 array_width_format(Width, Format), 598 length(Array, Length) 599 }, 600 [Format], 601 uint(Width, Length), 602 sequence(OnElement, Array). 603 604array_width_format(16, 0xdc). 605array_width_format(32, 0xdd). 606 607/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 608 609 map format family 610 611 +--------+~~~~~~~~~~~~~~~~~+ 612 |1000XXXX| X*2 objects | fixmap 613 +--------+~~~~~~~~~~~~~~~~~+ 614 615 +--------+--------+--------+~~~~~~~~~~~~~~~~~+ 616 | 0xde |YYYYYYYY|YYYYYYYY| Y*2 objects | map 16 617 +--------+--------+--------+~~~~~~~~~~~~~~~~~+ 618 619 +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+ 620 | 0xdf |ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ|ZZZZZZZZ| Z*2 objects | map 32 621 +--------+--------+--------+--------+--------+~~~~~~~~~~~~~~~~~+ 622 623- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
630msgpack_map(OnPair, Map) --> msgpack_fixmap(OnPair, Map), !. 631msgpack_map(OnPair, Map) --> msgpack_map(OnPair, _, Map). 632 633msgpack_map(Map) --> msgpack_map(msgpack_pair(msgpack, msgpack), Map). 634 635msgpack_fixmap(OnPair, Map) --> 636 { var(Map), 637 ! 638 }, 639 [Format], 640 { fixmap_format_length(Format, Length), 641 length(Map, Length) 642 }, 643 sequence(OnPair, Map). 644msgpack_fixmap(OnPair, Map) --> 645 { is_list(Map), 646 length(Map, Length), 647 fixmap_format_length(Format, Length) 648 }, 649 [Format], 650 sequence(OnPair, Map). 651 652fixmap_format_length(Format, Length) :- 653 fix_format_length(shift(0b1000, 4), Format, Length). 654 655msgpack_map(OnPair, Width, Map) --> 656 { var(Map), 657 !, 658 map_width_format(Width, Format) 659 }, 660 [Format], 661 uint(Width, Length), 662 { length(Map, Length) 663 }, 664 sequence(OnPair, Map). 665msgpack_map(OnPair, Width, Map) --> 666 { is_list(Map), 667 map_width_format(Width, Format), 668 length(Map, Length) 669 }, 670 [Format], 671 uint(Width, Length), 672 sequence(OnPair, Map). 673 674map_width_format(16, 0xde). 675map_width_format(32, 0xdf).
679msgpack_pair(OnKey, OnValue, Key-Value) --> 680 call(OnKey, Key), 681 call(OnValue, Value). 682 683msgpack_dict(OnPair, Dict) --> 684 { var(Dict), 685 ! 686 }, 687 msgpack_map(OnPair, Pairs), 688 { dict_create(Dict, _, Pairs) 689 }. 690msgpack_dict(OnPair, Dict) --> 691 { is_dict(Dict), 692 dict_pairs(Dict, _, Pairs) 693 }, 694 msgpack_map(OnPair, Pairs). 695 696/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 697 698 ext format family 699 700- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
708msgpack_ext(Term) --> 709 { ground(Term), 710 !, 711 msgpack:type_ext_hook(Type, Ext, Term) 712 }, 713 msgpack_ext(Type, Ext). 714msgpack_ext(Term) --> 715 msgpack_ext(Type, Ext), 716 !, 717 { msgpack:type_ext_hook(Type, Ext, Term) 718 }.
724msgpack_ext(Type, Ext) --> msgpack_fixext(Type, Ext), !. 725msgpack_ext(Type, Ext) --> msgpack_ext(_, Type, Ext). 726 727msgpack_fixext(Type, Ext) --> 728 { var(Type), 729 var(Ext), 730 !, 731 fixext_length_format(Length, Format) 732 }, 733 [Format], 734 int8(Type), 735 { length(Ext, Length) 736 }, 737 sequence(byte, Ext). 738msgpack_fixext(Type, Ext) --> 739 { integer(Type), 740 is_list(Ext), 741 fixext_length_format(Length, Format), 742 length(Ext, Length) 743 }, 744 [Format], 745 int8(Type), 746 sequence(byte, Ext). 747 748fixext_length_format( 1, 0xd4). 749fixext_length_format( 2, 0xd5). 750fixext_length_format( 4, 0xd6). 751fixext_length_format( 8, 0xd7). 752fixext_length_format(16, 0xd8). 753 754msgpack_ext(Width, Type, Ext) --> 755 { var(Ext), 756 !, 757 ext_width_format(Width, Format) 758 }, 759 [Format], 760 uint(Width, Length), 761 int8(Type), 762 { length(Ext, Length) 763 }, 764 sequence(byte, Ext). 765msgpack_ext(Width, Type, Ext) --> 766 { integer(Type), 767 is_list(Ext), 768 ext_width_format(Width, Format), 769 length(Ext, Length) 770 }, 771 [Format], 772 uint(Width, Length), 773 int8(Type), 774 sequence(byte, Ext). 775 776ext_width_format( 8, 0xc7). 777ext_width_format(16, 0xc8). 778ext_width_format(32, 0xc9).
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.
788msgpacktype_ext_hook(-1, Ext, timestamp(Epoch)) :- 789 once(phrase(timestamp(Epoch), Ext)). 790 791timestamp(Epoch) --> 792 { var(Epoch) 793 }, 794 epoch(Epoch). 795timestamp(Epoch) --> 796 { number(Epoch), 797 Epoch >= 0, 798 tv(Epoch, Seconds, NanoSeconds) 799 }, 800 sec_nsec(Seconds, NanoSeconds). 801 802epoch(Epoch) --> 803 int32(Epoch). 804epoch(Epoch) --> 805 uint64(UInt64), 806 { NanoSeconds is UInt64 >> 34, 807 NanoSeconds < 1 000 000 000, 808 Seconds is UInt64 /\ ((1 << 34) - 1), 809 tv(Epoch, Seconds, NanoSeconds) 810 }. 811epoch(Epoch) --> 812 int32(NanoSeconds), 813 int64(Seconds), 814 { tv(Epoch, Seconds, NanoSeconds) 815 }. 816 817sec_nsec(Seconds, 0) --> 818 { Seconds < (1 << 32) 819 }, 820 int32(Seconds). 821sec_nsec(Seconds, NanoSeconds) --> 822 { Seconds < (1 << 34), 823 UInt64 is (NanoSeconds << 34) \/ Seconds 824 }, 825 uint64(UInt64). 826sec_nsec(Seconds, NanoSeconds) --> 827 int32(NanoSeconds), 828 int64(Seconds).
The arguments have number type by design. The predicate supports negatives; Epoch of -1.1 for example gives -1 seconds, -100,000,000 nanoseconds.
841tv(Epoch, Sec, NSec), var(Epoch) => 842 abs(NSec) < 1 000 000 000, 843 Epoch is Sec + (NSec / 1e9). 844tv(Epoch, Sec, NSec), number(Epoch) => 845 Sec is floor(float_integer_part(Epoch)), 846 NSec is round(1e9 * float_fractional_part(Epoch)).
shift(Bits, Left)
form where the amount of Left shift implies the
minimum and maximum range.855fix_format_length(Fix, Format, Length), var(Format) => 856 fix_min_max(Fix, Min, Max), 857 Format is Min + Length, 858 Format >= Min, 859 Format =< Max. 860fix_format_length(Fix, Format, Length), integer(Format) => 861 fix_min_max(Fix, Min, Max), 862 Format >= Min, 863 Format =< Max, 864 Length is Format - Min. 865 866fix_min_max(Min-Max, Min, Max) => true. 867fix_min_max(shift(Bits, Left), Min, Max) => 868 Min is Bits << Left, 869 Max is Min \/ ((1 << Left) - 1).
878float(32, Float) --> float32(Float). 879float(64, Float) --> float64(Float). 880 881uint( 8, Int) --> uint8(Int). 882uint(16, Int) --> uint16(Int). 883uint(32, Int) --> uint32(Int). 884uint(64, Int) --> uint64(Int). 885 886int( 8, Int) --> int8(Int). 887int(16, Int) --> int16(Int). 888int(32, Int) --> int32(Int). 889int(64, Int) --> int64(Int).
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), _)
918byte(Byte) --> 919 [Byte], 920 { integer(Byte), 921 Byte >= 0x00, 922 Byte =< 0xff 923 }. 924 925uint8(Int) --> byte(Int). 926 927int8(Int) --> 928 byte(Int), 929 { Int =< 0x7f 930 }, 931 !. 932int8(Int) --> 933 { var(Int) 934 }, 935 byte(Byte), 936 { Byte >= 0x80, 937 Int is Byte - 0x100 938 }, 939 !. 940int8(Int) --> 941 { integer(Int), 942 % Now that Int is non-variable and an integer, just reverse 943 % the Int from Byte solution above: swap the sides, add 256 to 944 % both sides and swap the compute and threshold comparison; at 945 % this point Int must be negative. Grammar at byte//1 will 946 % catch Int values greater than -1. 947 Byte is 0x100 + Int 948 }, 949 byte(Byte)
C-Based MessagePack for SWI-Prolog
The predicates have three general categories.
msgpack_nil
designed for two-way unification between fundamental types and their MessagePack byte encoded representations.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.