1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2007-2020, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(json, 38 [ json_read/2, % +Stream, -JSONTerm 39 json_read/3, % +Stream, -JSONTerm, +Options 40 atom_json_term/3, % ?Atom, ?JSONTerm, +Options 41 json_write/2, % +Stream, +Term 42 json_write/3, % +Stream, +Term, +Options 43 is_json_term/1, % @Term 44 is_json_term/2, % @Term, +Options 45 % Version 7 dict support 46 json_read_dict/2, % +Stream, -Dict 47 json_read_dict/3, % +Stream, -Dict, +Options 48 json_write_dict/2, % +Stream, +Dict 49 json_write_dict/3, % +Stream, +Dict, +Options 50 atom_json_dict/3 % ?Atom, ?JSONDict, +Options 51 ]). 52:- use_module(library(record)). 53:- use_module(library(memfile)). 54:- use_module(library(error)). 55:- use_module(library(option)). 56:- use_module(library(lists)). 57 58:- use_foreign_library(foreign(json)). 59 60:- multifile 61 json_write_hook/4. % +Term, +Stream, +State, +Options 62 63:- predicate_options(json_read/3, 3, 64 [ null(ground), 65 true(ground), 66 false(ground), 67 value_string_as(oneof([atom,string])) 68 ]). 69:- predicate_options(json_write/3, 3, 70 [ indent(nonneg), 71 step(positive_integer), 72 tab(positive_integer), 73 width(nonneg), 74 null(ground), 75 true(ground), 76 false(ground), 77 serialize_unknown(boolean) 78 ]). 79:- predicate_options(json_read_dict/3, 3, 80 [ tag(atom), 81 default_tag(atom), 82 pass_to(json_read/3, 3) 83 ]). 84:- predicate_options(json_write_dict/3, 3, 85 [ tag(atom), 86 pass_to(json_write/3, 3) 87 ]). 88:- predicate_options(is_json_term/2, 2, 89 [ null(ground), 90 true(ground), 91 false(ground) 92 ]). 93:- predicate_options(atom_json_term/3, 3, 94 [ as(oneof([atom,string,codes])), 95 pass_to(json_read/3, 3), 96 pass_to(json_write/3, 3) 97 ]).
121:- record json_options( 122 null:ground = @(null), 123 true:ground = @(true), 124 false:ground = @(false), 125 end_of_file:ground = error, 126 value_string_as:oneof([atom,string]) = atom, 127 tag:atom = '', 128 default_tag:atom). 129 130default_json_dict_options( 131 json_options(null, true, false, error, string, '', _)). 132 133 134 /******************************* 135 * MAP TO/FROM TEXT * 136 *******************************/
atom
(default),
string
, codes
or chars
.147atom_json_term(Atom, Term, Options) :- 148 ground(Atom), 149 !, 150 setup_call_cleanup( 151 ( atom_to_memory_file(Atom, MF), 152 open_memory_file(MF, read, In, [free_on_close(true)]) 153 ), 154 json_read(In, Term, Options), 155 close(In)). 156atom_json_term(Result, Term, Options) :- 157 select_option(as(Type), Options, Options1, atom), 158 ( type_term(Type, Result, Out) 159 -> true 160 ; must_be(oneof([atom,string,codes,chars]), Type) 161 ), 162 with_output_to(Out, 163 json_write(current_output, Term, Options1)). 164 165type_term(atom, Result, atom(Result)). 166type_term(string, Result, string(Result)). 167type_term(codes, Result, codes(Result)). 168type_term(chars, Result, chars(Result)). 169 170 171 /******************************* 172 * READING * 173 *******************************/
json(NameValueList)
, where
NameValueList is a list of Name=Value. Name is an atom
created from the JSON string.true
and false
are mapped -like JPL-
to @(true) and @(false).null
is mapped to the Prolog term
@(null)Here is a complete example in JSON and its corresponding Prolog term.
{ "name":"Demo term", "created": { "day":null, "month":"December", "year":2007 }, "confirmed":true, "members":[1,2,3] }
json([ name='Demo term', created=json([day= @null, month='December', year=2007]), confirmed= @true, members=[1, 2, 3] ])
The following options are processed:
null
. Default @(null)true
. Default @(true)false
. Default @(false)error
):
error
, throw an unexpected
end of file syntax error
Returning an status term is required to process
Concatenated
JSON.
Suggested values are @(eof)
or end_of_file
.
atom
.
The alternative is string
, producing a packed string object.
Please note that codes
or chars
would produce ambiguous
output and are therefore not supported.248json_read(Stream, Term) :- 249 default_json_options(Options), 250 ( json_value_top(Stream, Term, Options) 251 -> true 252 ; syntax_error(illegal_json, Stream) 253 ). 254json_read(Stream, Term, Options) :- 255 make_json_options(Options, OptionTerm, _RestOptions), 256 ( json_value_top(Stream, Term, OptionTerm) 257 -> true 258 ; syntax_error(illegal_json, Stream) 259 ). 260 261json_value_top(Stream, Term, Options) :- 262 stream_property(Stream, type(binary)), 263 !, 264 setup_call_cleanup( 265 set_stream(Stream, encoding(utf8)), 266 json_value_top_(Stream, Term, Options), 267 set_stream(Stream, type(binary))). 268json_value_top(Stream, Term, Options) :- 269 json_value_top_(Stream, Term, Options). 270 271json_value_top_(Stream, Term, Options) :- 272 get_code(Stream, C0), 273 ws(C0, Stream, C1), 274 ( C1 == -1 275 -> json_options_end_of_file(Options, Action), 276 ( Action == error 277 -> syntax_error(unexpected_end_of_file, Stream) 278 ; Term = Action 279 ) 280 ; json_term_top(C1, Stream, Term, Options) 281 ). 282 283json_value(Stream, Term, Next, Options) :- 284 get_code(Stream, C0), 285 ws(C0, Stream, C1), 286 ( C1 == -1 287 -> syntax_error(unexpected_end_of_file, Stream) 288 ; json_term(C1, Stream, Term, Next, Options) 289 ). 290 291json_term(C0, Stream, JSON, Next, Options) :- 292 json_term_top(C0, Stream, JSON, Options), 293 get_code(Stream, Next). 294 295json_term_top(0'{, Stream, json(Pairs), Options) :- 296 !, 297 ws(Stream, C), 298 json_pairs(C, Stream, Pairs, Options). 299json_term_top(0'[, Stream, Array, Options) :- 300 !, 301 ws(Stream, C), 302 json_array(C, Stream, Array, Options). 303json_term_top(0'", Stream, String, Options) :- 304 !, 305 get_code(Stream, C1), 306 json_string_codes(C1, Stream, Codes), 307 json_options_value_string_as(Options, Type), 308 codes_to_type(Type, Codes, String). 309json_term_top(0'-, Stream, Number, _Options) :- 310 !, 311 json_read_number(Stream, 0'-, Number). 312json_term_top(D, Stream, Number, _Options) :- 313 between(0'0, 0'9, D), 314 !, 315 json_read_number(Stream, D, Number). 316json_term_top(C, Stream, Constant, Options) :- 317 json_read_constant(C, Stream, ID), 318 json_constant(ID, Constant, Options). 319 320json_pairs(0'}, _, [], _) :- !. 321json_pairs(C0, Stream, [Pair|Tail], Options) :- 322 json_pair(C0, Stream, Pair, C, Options), 323 ws(C, Stream, Next), 324 ( Next == 0', 325 -> ws(Stream, C2), 326 json_pairs(C2, Stream, Tail, Options) 327 ; Next == 0'} 328 -> Tail = [] 329 ; syntax_error(illegal_object, Stream) 330 ). 331 332json_pair(C0, Stream, Name=Value, Next, Options) :- 333 json_string_as_atom(C0, Stream, Name), 334 ws(Stream, C), 335 C == 0':, 336 json_value(Stream, Value, Next, Options). 337 338 339json_array(0'], _, [], _) :- !. 340json_array(C0, Stream, [Value|Tail], Options) :- 341 json_term(C0, Stream, Value, C, Options), 342 ws(C, Stream, Next), 343 ( Next == 0', 344 -> ws(Stream, C1), 345 json_array(C1, Stream, Tail, Options) 346 ; Next == 0'] 347 -> Tail = [] 348 ; syntax_error(illegal_array, Stream) 349 ). 350 351codes_to_type(atom, Codes, Atom) :- 352 atom_codes(Atom, Codes). 353codes_to_type(string, Codes, Atom) :- 354 string_codes(Atom, Codes). 355codes_to_type(codes, Codes, Codes). 356 357json_string_as_atom(0'", Stream, Atom) :- 358 get_code(Stream, C1), 359 json_string_codes(C1, Stream, Codes), 360 atom_codes(Atom, Codes). 361 362json_string_codes(0'", _, []) :- !. 363json_string_codes(0'\\, Stream, [H|T]) :- 364 !, 365 get_code(Stream, C0), 366 ( escape(C0, Stream, H) 367 -> true 368 ; syntax_error(illegal_string_escape, Stream) 369 ), 370 get_code(Stream, C1), 371 json_string_codes(C1, Stream, T). 372json_string_codes(-1, Stream, _) :- 373 !, 374 syntax_error(eof_in_string, Stream). 375json_string_codes(C, Stream, [C|T]) :- 376 get_code(Stream, C1), 377 json_string_codes(C1, Stream, T). 378 379escape(0'", _, 0'") :- !. 380escape(0'\\, _, 0'\\) :- !. 381escape(0'/, _, 0'/) :- !. 382escape(0'b, _, 0'\b) :- !. 383escape(0'f, _, 0'\f) :- !. 384escape(0'n, _, 0'\n) :- !. 385escape(0'r, _, 0'\r) :- !. 386escape(0't, _, 0'\t) :- !. 387escape(0'u, Stream, C) :- 388 !, 389 get_code(Stream, C1), 390 get_code(Stream, C2), 391 get_code(Stream, C3), 392 get_code(Stream, C4), 393 code_type(C1, xdigit(D1)), 394 code_type(C2, xdigit(D2)), 395 code_type(C3, xdigit(D3)), 396 code_type(C4, xdigit(D4)), 397 C is D1<<12+D2<<8+D3<<4+D4. 398 399json_read_constant(0't, Stream, true) :- 400 !, 401 must_see(`rue`, Stream, true). 402json_read_constant(0'f, Stream, false) :- 403 !, 404 must_see(`alse`, Stream, false). 405json_read_constant(0'n, Stream, null) :- 406 !, 407 must_see(`ull`, Stream, null). 408 409must_see([], _Stream, _). 410must_see([H|T], Stream, Name) :- 411 get_code(Stream, C), 412 ( C == H 413 -> true 414 ; syntax_error(json_expected(Name), Stream) 415 ), 416 must_see(T, Stream, Name). 417 418json_constant(true, Constant, Options) :- 419 !, 420 json_options_true(Options, Constant). 421json_constant(false, Constant, Options) :- 422 !, 423 json_options_false(Options, Constant). 424json_constant(null, Constant, Options) :- 425 !, 426 json_options_null(Options, Constant).
//
... comments.434ws(Stream, Next) :- 435 get_code(Stream, C0), 436 json_skip_ws(Stream, C0, Next). 437 438ws(C0, Stream, Next) :- 439 json_skip_ws(Stream, C0, Next). 440 441syntax_error(Message, Stream) :- 442 stream_error_context(Stream, Context), 443 throw(error(syntax_error(json(Message)), Context)). 444 445stream_error_context(Stream, stream(Stream, Line, LinePos, CharNo)) :- 446 stream_pair(Stream, Read, _), 447 character_count(Read, CharNo), 448 line_position(Read, LinePos), 449 line_count(Read, Line). 450 451 452 /******************************* 453 * JSON OUTPUT * 454 *******************************/
461% foreign json_write_string/2.
line_position(Stream, Pos)
is not 0. Then it writes Indent //
TabDistance tab characters and Indent mode TabDistance spaces.
469% foreign json_write_indent/3.
Values can be of the form #(Term), which causes Term to be stringified if it is not an atom or string. Stringification is based on term_string/2.
Rational numbers are emitted as floating point numbers. The hook json_write_hook/4 can be used to realize domain specific alternatives.
The version 7 dict type is supported as well. Optionally, if the
dict has a tag, a property "type":"tag" can be added to the
object. This behaviour can be controlled using the tag
option (see
below). For example:
?- json_write(current_output, point{x:1,y:2}). { "x":1, "y":2 }
?- json_write(current_output, point{x:1,y:2}, [tag(type)]). { "type":"point", "x":1, "y":2 }
In addition to the options recognised by json_read/3, we process the following options are recognised:
true
(default false
), serialize unknown terms and
print them as a JSON string. The default raises a type
error. Note that this option only makes sense if you can
guarantee that the passed value is not an otherwise valid
Prolog reporesentation of a Prolog term.
If a string is emitted, the sequence </
is emitted as
<\/
. This is valid JSON syntax which ensures that JSON
objects can be safely embedded into an HTML <script>
element.
Note that this hook is shared by all users of this library. It is generally adviced to map a unique compound term to avoid interference with normal output.
557:- record json_write_state(indent:nonneg = 0, 558 step:positive_integer = 2, 559 tab:positive_integer = 8, 560 width:nonneg = 72, 561 serialize_unknown:boolean = false 562 ). 563 564json_write(Stream, Term) :- 565 json_write(Stream, Term, []). 566json_write(Stream, Term, Options) :- 567 make_json_write_state(Options, State, Options1), 568 make_json_options(Options1, OptionTerm, _RestOptions), 569 json_write_term(Term, Stream, State, OptionTerm). 570 571json_write_term(Var, _, _, _) :- 572 var(Var), 573 !, 574 instantiation_error(Var). 575json_write_term(json(Pairs), Stream, State, Options) :- 576 !, 577 json_write_object(Pairs, Stream, State, Options). 578json_write_term(Dict, Stream, State, Options) :- 579 is_dict(Dict), 580 !, 581 dict_pairs(Dict, Tag, Pairs0), 582 ( nonvar(Tag), 583 json_options_tag(Options, Name), 584 Name \== '' 585 -> Pairs = [Name-Tag|Pairs0] 586 ; Pairs = Pairs0 587 ), 588 json_write_object(Pairs, Stream, State, Options). 589json_write_term(List, Stream, State, Options) :- 590 is_list(List), 591 !, 592 space_if_not_at_left_margin(Stream, State), 593 write(Stream, '['), 594 ( json_write_state_width(State, Width), 595 ( Width == 0 596 -> true 597 ; json_write_state_indent(State, Indent), 598 json_print_length(List, Options, Width, Indent, _) 599 ) 600 -> set_width_of_json_write_state(0, State, State2), 601 write_array_hor(List, Stream, State2, Options), 602 write(Stream, ']') 603 ; step_indent(State, State2), 604 write_array_ver(List, Stream, State2, Options), 605 indent(Stream, State), 606 write(Stream, ']') 607 ). 608 609json_write_term(Term, Stream, State, Options) :- 610 json_write_hook(Term, Stream, State, Options), 611 !. 612json_write_term(Number, Stream, _State, _Options) :- 613 number(Number), 614 !, 615 ( float(Number) 616 -> write(Stream, Number) 617 ; integer(Number) 618 -> write(Stream, Number) 619 ; Float is float(Number) % rational number 620 -> write(Stream, Float) 621 ). 622json_write_term(True, Stream, _State, Options) :- 623 json_options_true(Options, True), 624 !, 625 write(Stream, true). 626json_write_term(False, Stream, _State, Options) :- 627 json_options_false(Options, False), 628 !, 629 write(Stream, false). 630json_write_term(Null, Stream, _State, Options) :- 631 json_options_null(Options, Null), 632 !, 633 write(Stream, null). 634json_write_term(#(Text), Stream, _State, _Options) :- 635 !, 636 ( ( atom(Text) 637 ; string(Text) 638 ) 639 -> json_write_string(Stream, Text) 640 ; term_string(Text, String), 641 json_write_string(Stream, String) 642 ). 643json_write_term(String, Stream, _State, _Options) :- 644 atom(String), 645 !, 646 json_write_string(Stream, String). 647json_write_term(String, Stream, _State, _Options) :- 648 string(String), 649 !, 650 json_write_string(Stream, String). 651json_write_term(AnyTerm, Stream, State, _Options) :- 652 ( json_write_state_serialize_unknown(State, true) 653 -> term_string(AnyTerm, String), 654 json_write_string(Stream, String) 655 ; type_error(json_term, AnyTerm) 656 ). 657 658json_write_object(Pairs, Stream, State, Options) :- 659 space_if_not_at_left_margin(Stream, State), 660 write(Stream, '{'), 661 ( json_write_state_width(State, Width), 662 ( Width == 0 663 -> true 664 ; json_write_state_indent(State, Indent), 665 json_print_length(json(Pairs), Options, Width, Indent, _) 666 ) 667 -> set_width_of_json_write_state(0, State, State2), 668 write_pairs_hor(Pairs, Stream, State2, Options), 669 write(Stream, '}') 670 ; step_indent(State, State2), 671 write_pairs_ver(Pairs, Stream, State2, Options), 672 indent(Stream, State), 673 write(Stream, '}') 674 ). 675 676 677write_pairs_hor([], _, _, _). 678write_pairs_hor([H|T], Stream, State, Options) :- 679 json_pair(H, Name, Value), 680 json_write_string(Stream, Name), 681 write(Stream, ':'), 682 json_write_term(Value, Stream, State, Options), 683 ( T == [] 684 -> true 685 ; write(Stream, ', '), 686 write_pairs_hor(T, Stream, State, Options) 687 ). 688 689write_pairs_ver([], _, _, _). 690write_pairs_ver([H|T], Stream, State, Options) :- 691 indent(Stream, State), 692 json_pair(H, Name, Value), 693 json_write_string(Stream, Name), 694 write(Stream, ':'), 695 json_write_term(Value, Stream, State, Options), 696 ( T == [] 697 -> true 698 ; write(Stream, ','), 699 write_pairs_ver(T, Stream, State, Options) 700 ). 701 702 703json_pair(Var, _, _) :- 704 var(Var), 705 !, 706 instantiation_error(Var). 707json_pair(Name=Value, Name, Value) :- !. 708json_pair(Name-Value, Name, Value) :- !. 709json_pair(NameValue, Name, Value) :- 710 compound(NameValue), 711 NameValue =.. [Name, Value], 712 !. 713json_pair(Pair, _, _) :- 714 type_error(json_pair, Pair). 715 716 717write_array_hor([], _, _, _). 718write_array_hor([H|T], Stream, State, Options) :- 719 json_write_term(H, Stream, State, Options), 720 ( T == [] 721 -> write(Stream, ' ') 722 ; write(Stream, ', '), 723 write_array_hor(T, Stream, State, Options) 724 ). 725 726write_array_ver([], _, _, _). 727write_array_ver([H|T], Stream, State, Options) :- 728 indent(Stream, State), 729 json_write_term(H, Stream, State, Options), 730 ( T == [] 731 -> true 732 ; write(Stream, ','), 733 write_array_ver(T, Stream, State, Options) 734 ). 735 736 737indent(Stream, State) :- 738 json_write_state_indent(State, Indent), 739 json_write_state_tab(State, Tab), 740 json_write_indent(Stream, Indent, Tab). 741 742step_indent(State0, State) :- 743 json_write_state_indent(State0, Indent), 744 json_write_state_step(State0, Step), 745 NewIndent is Indent+Step, 746 set_indent_of_json_write_state(NewIndent, State0, State). 747 748space_if_not_at_left_margin(Stream, State) :- 749 stream_pair(Stream, _, Write), 750 line_position(Write, LinePos), 751 ( LinePos == 0 752 ; json_write_state_indent(State, LinePos) 753 ), 754 !. 755space_if_not_at_left_margin(Stream, _) :- 756 put_char(Stream, ' ').
766json_print_length(Var, _, _, _, _) :- 767 var(Var), 768 !, 769 instantiation_error(Var). 770json_print_length(json(Pairs), Options, Max, Len0, Len) :- 771 !, 772 Len1 is Len0 + 2, 773 Len1 =< Max, 774 must_be(list, Pairs), 775 pairs_print_length(Pairs, Options, Max, Len1, Len). 776json_print_length(Dict, Options, Max, Len0, Len) :- 777 is_dict(Dict), 778 !, 779 dict_pairs(Dict, _Tag, Pairs), 780 Len1 is Len0 + 2, 781 Len1 =< Max, 782 pairs_print_length(Pairs, Options, Max, Len1, Len). 783json_print_length(Array, Options, Max, Len0, Len) :- 784 is_list(Array), 785 !, 786 Len1 is Len0 + 2, 787 Len1 =< Max, 788 array_print_length(Array, Options, Max, Len1, Len). 789json_print_length(Null, Options, Max, Len0, Len) :- 790 json_options_null(Options, Null), 791 !, 792 Len is Len0 + 4, 793 Len =< Max. 794json_print_length(False, Options, Max, Len0, Len) :- 795 json_options_false(Options, False), 796 !, 797 Len is Len0 + 5, 798 Len =< Max. 799json_print_length(True, Options, Max, Len0, Len) :- 800 json_options_true(Options, True), 801 !, 802 Len is Len0 + 4, 803 Len =< Max. 804json_print_length(Number, _Options, Max, Len0, Len) :- 805 number(Number), 806 !, 807 write_length(Number, AL, []), 808 Len is Len0 + AL, 809 Len =< Max. 810json_print_length(@(Id), _Options, Max, Len0, Len) :- 811 atom(Id), 812 !, 813 atom_length(Id, IdLen), 814 Len is Len0+IdLen, 815 Len =< Max. 816json_print_length(String, _Options, Max, Len0, Len) :- 817 string_len(String, Len0, Len), 818 !, 819 Len =< Max. 820json_print_length(AnyTerm, _Options, Max, Len0, Len) :- 821 write_length(AnyTerm, AL, []), % will be serialized 822 Len is Len0 + AL+2, 823 Len =< Max. 824 825pairs_print_length([], _, _, Len, Len). 826pairs_print_length([H|T], Options, Max, Len0, Len) :- 827 pair_len(H, Options, Max, Len0, Len1), 828 ( T == [] 829 -> Len = Len1 830 ; Len2 is Len1 + 2, 831 Len2 =< Max, 832 pairs_print_length(T, Options, Max, Len2, Len) 833 ). 834 835pair_len(Pair, Options, Max, Len0, Len) :- 836 compound(Pair), 837 pair_nv(Pair, Name, Value), 838 !, 839 string_len(Name, Len0, Len1), 840 Len2 is Len1+2, 841 Len2 =< Max, 842 json_print_length(Value, Options, Max, Len2, Len). 843pair_len(Pair, _Options, _Max, _Len0, _Len) :- 844 type_error(pair, Pair). 845 846pair_nv(Name=Value, Name, Value) :- !. 847pair_nv(Name-Value, Name, Value) :- !. 848pair_nv(Term, Name, Value) :- 849 compound_name_arguments(Term, Name, [Value]). 850 851array_print_length([], _, _, Len, Len). 852array_print_length([H|T], Options, Max, Len0, Len) :- 853 json_print_length(H, Options, Max, Len0, Len1), 854 ( T == [] 855 -> Len = Len1 856 ; Len2 is Len1+2, 857 Len2 =< Max, 858 array_print_length(T, Options, Max, Len2, Len) 859 ). 860 861string_len(String, Len0, Len) :- 862 atom(String), 863 !, 864 atom_length(String, AL), 865 Len is Len0 + AL + 2. 866string_len(String, Len0, Len) :- 867 string(String), 868 !, 869 string_length(String, AL), 870 Len is Len0 + AL + 2. 871 872 873 /******************************* 874 * TEST * 875 *******************************/
true
, false
and null
constants.884is_json_term(Term) :- 885 default_json_options(Options), 886 is_json_term2(Options, Term). 887 888is_json_term(Term, Options) :- 889 make_json_options(Options, OptionTerm, _RestOptions), 890 is_json_term2(OptionTerm, Term). 891 892is_json_term2(_, Var) :- 893 var(Var), !, fail. 894is_json_term2(Options, json(Pairs)) :- 895 !, 896 is_list(Pairs), 897 maplist(is_json_pair(Options), Pairs). 898is_json_term2(Options, List) :- 899 is_list(List), 900 !, 901 maplist(is_json_term2(Options), List). 902is_json_term2(_, Primitive) :- 903 atomic(Primitive), 904 !. % atom, string or number 905is_json_term2(Options, True) :- 906 json_options_true(Options, True). 907is_json_term2(Options, False) :- 908 json_options_false(Options, False). 909is_json_term2(Options, Null) :- 910 json_options_null(Options, Null). 911 912is_json_pair(_, Var) :- 913 var(Var), !, fail. 914is_json_pair(Options, Name=Value) :- 915 atom(Name), 916 is_json_term2(Options, Value). 917 918 /******************************* 919 * DICT SUPPORT * 920 *******************************/
true
, false
and null
are represented using these
Prolog atoms.type
field in an object assigns a tag for
the dict.
The predicate json_read_dict/3 processes the same options as
json_read/3, but with different defaults. In addition, it
processes the tag
option. See json_read/3 for details about
the shared options.
tag
option does not
apply.null
.true
.false
string
. The alternative is atom
, producing a
packed string object.961json_read_dict(Stream, Dict) :- 962 json_read_dict(Stream, Dict, []). 963 964json_read_dict(Stream, Dict, Options) :- 965 make_json_dict_options(Options, OptionTerm, _RestOptions), 966 ( json_value_top(Stream, Term, OptionTerm) 967 -> true 968 ; syntax_error(illegal_json, Stream) 969 ), 970 term_to_dict(Term, Dict, OptionTerm). 971 972term_to_dict(json(Pairs), Dict, Options) :- 973 !, 974 ( json_options_tag(Options, TagName), 975 Tag \== '', 976 select(TagName = Tag0, Pairs, NVPairs), 977 to_atom(Tag0, Tag) 978 -> json_dict_pairs(NVPairs, DictPairs, Options) 979 ; json_options_default_tag(Options, DefTag), 980 ( var(DefTag) 981 -> true 982 ; Tag = DefTag 983 ), 984 json_dict_pairs(Pairs, DictPairs, Options) 985 ), 986 dict_create(Dict, Tag, DictPairs). 987term_to_dict(Value0, Value, _Options) :- 988 atomic(Value0), Value0 \== [], 989 !, 990 Value = Value0. 991term_to_dict(List0, List, Options) :- 992 is_list(List0), 993 !, 994 terms_to_dicts(List0, List, Options). 995term_to_dict(Special, Special, Options) :- 996 ( json_options_true(Options, Special) 997 ; json_options_false(Options, Special) 998 ; json_options_null(Options, Special) 999 ; json_options_end_of_file(Options, Special) 1000 ), 1001 !. 1002 1003json_dict_pairs([], [], _). 1004json_dict_pairs([Name=Value0|T0], [Name=Value|T], Options) :- 1005 term_to_dict(Value0, Value, Options), 1006 json_dict_pairs(T0, T, Options). 1007 1008terms_to_dicts([], [], _). 1009terms_to_dicts([Value0|T0], [Value|T], Options) :- 1010 term_to_dict(Value0, Value, Options), 1011 terms_to_dicts(T0, T, Options). 1012 1013to_atom(Tag, Atom) :- 1014 string(Tag), 1015 !, 1016 atom_string(Atom, Tag). 1017to_atom(Atom, Atom) :- 1018 atom(Atom).
1027json_write_dict(Stream, Dict) :- 1028 json_write_dict(Stream, Dict, []). 1029 1030json_write_dict(Stream, Dict, Options) :- 1031 make_json_write_state(Options, State, Options1), 1032 make_json_dict_options(Options1, OptionTerm, _RestOptions), 1033 json_write_term(Dict, Stream, State, OptionTerm). 1034 1035 1036make_json_dict_options(Options, Record, RestOptions) :- 1037 default_json_dict_options(Record0), 1038 set_json_options_fields(Options, Record0, Record, RestOptions).
atom
,
string
or codes
.1051atom_json_dict(Atom, Term, Options) :- 1052 ground(Atom), 1053 !, 1054 setup_call_cleanup( 1055 open_string(Atom, In), 1056 json_read_dict(In, Term, Options), 1057 close(In)). 1058atom_json_dict(Result, Term, Options) :- 1059 select_option(as(Type), Options, Options1, atom), 1060 ( type_term(Type, Result, Out) 1061 -> true 1062 ; must_be(oneof([atom,string,codes]), Type) 1063 ), 1064 with_output_to(Out, 1065 json_write_dict(current_output, Term, Options1)). 1066 1067 1068 /******************************* 1069 * MESSAGES * 1070 *******************************/ 1071 1072:- multifile 1073 prolog:error_message/3. 1074 1075prologerror_message(syntax_error(json(Id))) --> 1076 [ 'JSON syntax error: ' ], 1077 json_syntax_error(Id). 1078 1079json_syntax_error(illegal_comment) --> 1080 [ 'Illegal comment' ]. 1081json_syntax_error(illegal_string_escape) --> 1082 [ 'Illegal escape sequence in string' ]
Reading and writing JSON serialization
This module supports reading and writing JSON objects. This library supports two Prolog representations (the new representation is only supported in SWI-Prolog version 7 and later):
json(NameValueList)
, a JSON string as an atom and the JSON constantsnull
,true
andfalse
as @(null), @(true) and @false.null
,true
andfalse
.http_json.pl
links JSON to the HTTP client and server modules.json_convert.pl
converts JSON Prolog terms to more comfortable terms. */