View source with raw comments or as raw
    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-2018, 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:- if(current_predicate(is_dict/1)).   38
   39:- module(json,
   40          [ json_read/2,                % +Stream, -JSONTerm
   41            json_read/3,                % +Stream, -JSONTerm, +Options
   42            atom_json_term/3,           % ?Atom, ?JSONTerm, +Options
   43            json_write/2,               % +Stream, +Term
   44            json_write/3,               % +Stream, +Term, +Options
   45            is_json_term/1,             % @Term
   46            is_json_term/2,             % @Term, +Options
   47                                        % Version 7 dict support
   48            json_read_dict/2,           % +Stream, -Dict
   49            json_read_dict/3,           % +Stream, -Dict, +Options
   50            json_write_dict/2,          % +Stream, +Dict
   51            json_write_dict/3,          % +Stream, +Dict, +Options
   52            atom_json_dict/3            % ?Atom, ?JSONDict, +Options
   53          ]).   54
   55:- else.   56
   57:- module(json,
   58          [ json_read/2,                % +Stream, -JSONTerm
   59            json_read/3,                % +Stream, -JSONTerm, +Options
   60            atom_json_term/3,           % ?Atom, ?JSONTerm, +Options
   61            json_write/2,               % +Stream, +Term
   62            json_write/3,               % +Stream, +Term, +Options
   63            is_json_term/1,             % @Term
   64            is_json_term/2
   65          ]).   66
   67:- endif.   68
   69:- use_module(library(record)).   70:- use_module(library(memfile)).   71:- use_module(library(error)).   72:- use_module(library(option)).   73:- use_module(library(debug)).   74
   75:- use_foreign_library(foreign(json)).   76
   77:- predicate_options(json_read/3, 3,
   78                     [ null(ground),
   79                       true(ground),
   80                       false(ground),
   81                       value_string_as(oneof([atom,string]))
   82                     ]).   83:- predicate_options(json_write/3, 3,
   84                     [ indent(nonneg),
   85                       step(positive_integer),
   86                       tab(positive_integer),
   87                       width(nonneg),
   88                       null(ground),
   89                       true(ground),
   90                       false(ground),
   91                       serialize_unknown(boolean)
   92                     ]).   93:- predicate_options(json_read_dict/3, 3,
   94                     [ tag(atom),
   95                       default_tag(atom),
   96                       pass_to(json_read/3, 3)
   97                     ]).   98:- predicate_options(json_write_dict/3, 3,
   99                     [ tag(atom),
  100                       pass_to(json_write/3, 3)
  101                     ]).  102:- predicate_options(is_json_term/2, 2,
  103                     [ null(ground),
  104                       true(ground),
  105                       false(ground)
  106                     ]).  107:- predicate_options(atom_json_term/3, 3,
  108                     [ as(oneof([atom,string,codes])),
  109                       pass_to(json_read/3, 3),
  110                       pass_to(json_write/3, 3)
  111                     ]).

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):

author
- Jan Wielemaker
See also
- http_json.pl links JSON to the HTTP client and server modules.
- json_convert.pl converts JSON Prolog terms to more comfortable terms. */
  135:- record json_options(
  136              null:ground = @(null),
  137              true:ground = @(true),
  138              false:ground = @(false),
  139              end_of_file:ground = error,
  140              value_string_as:oneof([atom,string]) = atom,
  141              tag:atom = '',
  142              default_tag:atom).  143
  144default_json_dict_options(
  145    json_options(null, true, false, error, string, '', _)).
  146
  147
  148                 /*******************************
  149                 *       MAP TO/FROM TEXT       *
  150                 *******************************/
 atom_json_term(?Atom, ?JSONTerm, +Options) is det
Convert between textual representation and a JSON term. In write mode (JSONTerm to Atom), the option
as(Type)
defines the output type, which is one of atom (default), string, codes or chars.
  161atom_json_term(Atom, Term, Options) :-
  162    ground(Atom),
  163    !,
  164    setup_call_cleanup(
  165        ( atom_to_memory_file(Atom, MF),
  166          open_memory_file(MF, read, In, [free_on_close(true)])
  167        ),
  168        json_read(In, Term, Options),
  169        close(In)).
  170atom_json_term(Result, Term, Options) :-
  171    select_option(as(Type), Options, Options1, atom),
  172    (   type_term(Type, Result, Out)
  173    ->  true
  174    ;   must_be(oneof([atom,string,codes,chars]), Type)
  175    ),
  176    with_output_to(Out,
  177                   json_write(current_output, Term, Options1)).
  178
  179type_term(atom,   Result, atom(Result)).
  180type_term(string, Result, string(Result)).
  181type_term(codes,  Result, codes(Result)).
  182type_term(chars,  Result, chars(Result)).
  183
  184
  185                 /*******************************
  186                 *           READING            *
  187                 *******************************/
 json_read(+Stream, -Term) is det
 json_read(+Stream, -Term, +Options) is det
Read next JSON value from Stream into a Prolog term. The canonical representation for Term is:

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(+NullTerm)
Term used to represent JSON null. Default @(null)
true(+TrueTerm)
Term used to represent JSON true. Default @(true)
false +FalseTerm
Term used to represent JSON false. Default @(false)
end_of_file(+ErrorOrTerm)
If end of file is reached after skipping white space but before any input is processed take the following action (default error):
  • If ErrorOrTerm == error, throw an unexpected end of file syntax error
  • Otherwise return ErrorOrTerm.

Returning an status term is required to process Concatenated JSON. Suggested values are @(eof) or end_of_file.

value_string_as(+Type)
Prolog type used for strings used as value. Default is 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.
See also
- json_read_dict/3 to read a JSON term using the version 7 extended data types.
  262json_read(Stream, Term) :-
  263    default_json_options(Options),
  264    (   json_value_top(Stream, Term, Options)
  265    ->  true
  266    ;   syntax_error(illegal_json, Stream)
  267    ).
  268json_read(Stream, Term, Options) :-
  269    make_json_options(Options, OptionTerm, _RestOptions),
  270    (   json_value_top(Stream, Term, OptionTerm)
  271    ->  true
  272    ;   syntax_error(illegal_json, Stream)
  273    ).
  274
  275json_value_top(Stream, Term, Options) :-
  276    get_code(Stream, C0),
  277    ws(C0, Stream, C1),
  278    (   C1 == -1
  279    ->  json_options_end_of_file(Options, Action),
  280        (   Action == error
  281        ->  syntax_error(unexpected_end_of_file, Stream)
  282        ;   Term = Action
  283        )
  284    ;   json_term_top(C1, Stream, Term, Options)
  285    ).
  286
  287json_value(Stream, Term, Next, Options) :-
  288    get_code(Stream, C0),
  289    ws(C0, Stream, C1),
  290    (   C1 == -1
  291    ->  syntax_error(unexpected_end_of_file, Stream)
  292    ;   json_term(C1, Stream, Term, Next, Options)
  293    ).
  294
  295json_term(C0, Stream, JSON, Next, Options) :-
  296    json_term_top(C0, Stream, JSON, Options),
  297    get_code(Stream, Next).
  298
  299json_term_top(0'{, Stream, json(Pairs), Options) :-
  300    !,
  301    ws(Stream, C),
  302    json_pairs(C, Stream, Pairs, Options).
  303json_term_top(0'[, Stream, Array, Options) :-
  304    !,
  305    ws(Stream, C),
  306    json_array(C, Stream, Array, Options).
  307json_term_top(0'", Stream, String, Options) :-
  308    !,
  309    get_code(Stream, C1),
  310    json_string_codes(C1, Stream, Codes),
  311    json_options_value_string_as(Options, Type),
  312    codes_to_type(Type, Codes, String).
  313json_term_top(0'-, Stream, Number, _Options) :-
  314    !,
  315    json_read_number(Stream, 0'-, Number).
  316json_term_top(D, Stream, Number, _Options) :-
  317    between(0'0, 0'9, D),
  318    !,
  319    json_read_number(Stream, D, Number).
  320json_term_top(C, Stream, Constant, Options) :-
  321    json_read_constant(C, Stream, ID),
  322    json_constant(ID, Constant, Options).
  323
  324json_pairs(0'}, _, [], _) :- !.
  325json_pairs(C0, Stream, [Pair|Tail], Options) :-
  326    json_pair(C0, Stream, Pair, C, Options),
  327    ws(C, Stream, Next),
  328    (   Next == 0',
  329    ->  ws(Stream, C2),
  330        json_pairs(C2, Stream, Tail, Options)
  331    ;   Next == 0'}
  332    ->  Tail = []
  333    ;   syntax_error(illegal_object, Stream)
  334    ).
  335
  336json_pair(C0, Stream, Name=Value, Next, Options) :-
  337    json_string_as_atom(C0, Stream, Name),
  338    ws(Stream, C),
  339    C == 0':,
  340    json_value(Stream, Value, Next, Options).
  341
  342
  343json_array(0'], _, [], _) :- !.
  344json_array(C0, Stream, [Value|Tail], Options) :-
  345    json_term(C0, Stream, Value, C, Options),
  346    ws(C, Stream, Next),
  347    (   Next == 0',
  348    ->  ws(Stream, C1),
  349        json_array(C1, Stream, Tail, Options)
  350    ;   Next == 0']
  351    ->  Tail = []
  352    ;   syntax_error(illegal_array, Stream)
  353    ).
  354
  355codes_to_type(atom, Codes, Atom) :-
  356    atom_codes(Atom, Codes).
  357codes_to_type(string, Codes, Atom) :-
  358    string_codes(Atom, Codes).
  359codes_to_type(codes, Codes, Codes).
  360
  361json_string_as_atom(0'", Stream, Atom) :-
  362    get_code(Stream, C1),
  363    json_string_codes(C1, Stream, Codes),
  364    atom_codes(Atom, Codes).
  365
  366json_string_codes(0'", _, []) :- !.
  367json_string_codes(0'\\, Stream, [H|T]) :-
  368    !,
  369    get_code(Stream, C0),
  370    (   escape(C0, Stream, H)
  371    ->  true
  372    ;   syntax_error(illegal_string_escape, Stream)
  373    ),
  374    get_code(Stream, C1),
  375    json_string_codes(C1, Stream, T).
  376json_string_codes(-1, Stream, _) :-
  377    !,
  378    syntax_error(eof_in_string, Stream).
  379json_string_codes(C, Stream, [C|T]) :-
  380    get_code(Stream, C1),
  381    json_string_codes(C1, Stream, T).
  382
  383escape(0'", _, 0'") :- !.
  384escape(0'\\, _, 0'\\) :- !.
  385escape(0'/, _, 0'/) :- !.
  386escape(0'b, _, 0'\b) :- !.
  387escape(0'f, _, 0'\f) :- !.
  388escape(0'n, _, 0'\n) :- !.
  389escape(0'r, _, 0'\r) :- !.
  390escape(0't, _, 0'\t) :- !.
  391escape(0'u, Stream, C) :-
  392    !,
  393    get_code(Stream, C1),
  394    get_code(Stream, C2),
  395    get_code(Stream, C3),
  396    get_code(Stream, C4),
  397    code_type(C1, xdigit(D1)),
  398    code_type(C2, xdigit(D2)),
  399    code_type(C3, xdigit(D3)),
  400    code_type(C4, xdigit(D4)),
  401    C is D1<<12+D2<<8+D3<<4+D4.
  402
  403json_read_constant(0't, Stream, true) :-
  404    !,
  405    must_see(`rue`, Stream, true).
  406json_read_constant(0'f, Stream, false) :-
  407    !,
  408    must_see(`alse`, Stream, false).
  409json_read_constant(0'n, Stream, null) :-
  410    !,
  411    must_see(`ull`, Stream, null).
  412
  413must_see([], _Stream, _).
  414must_see([H|T], Stream, Name) :-
  415    get_code(Stream, C),
  416    (   C == H
  417    ->  true
  418    ;   syntax_error(json_expected(Name), Stream)
  419    ),
  420    must_see(T, Stream, Name).
  421
  422json_constant(true, Constant, Options) :-
  423    !,
  424    json_options_true(Options, Constant).
  425json_constant(false, Constant, Options) :-
  426    !,
  427    json_options_false(Options, Constant).
  428json_constant(null, Constant, Options) :-
  429    !,
  430    json_options_null(Options, Constant).
 ws(+Stream, -Next) is det
 ws(+C0, +Stream, -Next)
Skip white space on the Stream, returning the first non-ws character. Also skips // ... comments.
  438ws(Stream, Next) :-
  439    get_code(Stream, C0),
  440    json_skip_ws(Stream, C0, Next).
  441
  442ws(C0, Stream, Next) :-
  443    json_skip_ws(Stream, C0, Next).
  444
  445syntax_error(Message, Stream) :-
  446    stream_error_context(Stream, Context),
  447    throw(error(syntax_error(json(Message)), Context)).
  448
  449stream_error_context(Stream, stream(Stream, Line, LinePos, CharNo)) :-
  450    stream_pair(Stream, Read, _),
  451    character_count(Read, CharNo),
  452    line_position(Read, LinePos),
  453    line_count(Read, Line).
  454
  455
  456                 /*******************************
  457                 *          JSON OUTPUT         *
  458                 *******************************/
 json_write_string(+Stream, +Text) is det
Write a JSON string to Stream. Stream must be opened in a Unicode capable encoding, typically UTF-8.
  465% foreign json_write_string/2.
 json_write_indent(+Stream, +Indent, +TabDistance) is det
Newline and indent to Indent. A Newline is only written if line_position(Stream, Pos) is not 0. Then it writes Indent // TabDistance tab characters and Indent mode TabDistance spaces.
  473% foreign json_write_indent/3.
 json_write(+Stream, +Term) is det
 json_write(+Stream, +Term, +Options) is det
Write a JSON term to Stream. The JSON object is of the same format as produced by json_read/2, though we allow for some more flexibility with regard to pairs in objects. All of Name=Value, Name-Value and Name(Value) produce the same output.

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.

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:

width(+Width)
Width in which we try to format the result. Too long lines switch from horizontal to vertical layout for better readability. If performance is critical and human readability is not an issue use Width = 0, which causes a single-line output.
step(+Step)
Indentation increnment for next level. Default is 2.
tab(+TabDistance)
Distance between tab-stops. If equal to Step, layout is generated with one tab per level.
serialize_unknown(+Boolean)
If 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.

  538:- record json_write_state(indent:nonneg = 0,
  539                       step:positive_integer = 2,
  540                       tab:positive_integer = 8,
  541                       width:nonneg = 72,
  542                       serialize_unknown:boolean = false
  543                      ).  544
  545json_write(Stream, Term) :-
  546    json_write(Stream, Term, []).
  547json_write(Stream, Term, Options) :-
  548    make_json_write_state(Options, State, Options1),
  549    make_json_options(Options1, OptionTerm, _RestOptions),
  550    json_write_term(Term, Stream, State, OptionTerm).
  551
  552json_write_term(Var, _, _, _) :-
  553    var(Var),
  554    !,
  555    instantiation_error(Var).
  556json_write_term(json(Pairs), Stream, State, Options) :-
  557    !,
  558    json_write_object(Pairs, Stream, State, Options).
  559:- if(current_predicate(is_dict/1)).  560json_write_term(Dict, Stream, State, Options) :-
  561    is_dict(Dict),
  562    !,
  563    dict_pairs(Dict, Tag, Pairs0),
  564    (   nonvar(Tag),
  565        json_options_tag(Options, Name),
  566        Name \== ''
  567    ->  Pairs = [Name-Tag|Pairs0]
  568    ;   Pairs = Pairs0
  569    ),
  570    json_write_object(Pairs, Stream, State, Options).
  571:- endif.  572json_write_term(List, Stream, State, Options) :-
  573    is_list(List),
  574    !,
  575    space_if_not_at_left_margin(Stream, State),
  576    write(Stream, '['),
  577    (   json_write_state_width(State, Width),
  578        (   Width == 0
  579        ->  true
  580        ;   json_write_state_indent(State, Indent),
  581            json_print_length(List, Options, Width, Indent, _)
  582        )
  583    ->  set_width_of_json_write_state(0, State, State2),
  584        write_array_hor(List, Stream, State2, Options),
  585        write(Stream, ']')
  586    ;   step_indent(State, State2),
  587        write_array_ver(List, Stream, State2, Options),
  588        indent(Stream, State),
  589        write(Stream, ']')
  590    ).
  591json_write_term(Number, Stream, _State, _Options) :-
  592    number(Number),
  593    !,
  594    write(Stream, Number).
  595json_write_term(True, Stream, _State, Options) :-
  596    json_options_true(Options, True),
  597    !,
  598    write(Stream, true).
  599json_write_term(False, Stream, _State, Options) :-
  600    json_options_false(Options, False),
  601    !,
  602    write(Stream, false).
  603json_write_term(Null, Stream, _State, Options) :-
  604    json_options_null(Options, Null),
  605    !,
  606    write(Stream, null).
  607json_write_term(#(Text), Stream, _State, _Options) :-
  608    !,
  609    (   (   atom(Text)
  610        ;   string(Text)
  611        )
  612    ->  json_write_string(Stream, Text)
  613    ;   term_string(Text, String),
  614        json_write_string(Stream, String)
  615    ).
  616json_write_term(String, Stream, _State, _Options) :-
  617    atom(String),
  618    !,
  619    json_write_string(Stream, String).
  620json_write_term(String, Stream, _State, _Options) :-
  621    string(String),
  622    !,
  623    json_write_string(Stream, String).
  624json_write_term(AnyTerm, Stream, State, _Options) :-
  625    (   json_write_state_serialize_unknown(State, true)
  626    ->  term_string(AnyTerm, String),
  627        json_write_string(Stream, String)
  628    ;   type_error(json_term, AnyTerm)
  629    ).
  630
  631json_write_object(Pairs, Stream, State, Options) :-
  632    space_if_not_at_left_margin(Stream, State),
  633    write(Stream, '{'),
  634    (   json_write_state_width(State, Width),
  635        (   Width == 0
  636        ->  true
  637        ;   json_write_state_indent(State, Indent),
  638            json_print_length(json(Pairs), Options, Width, Indent, _)
  639        )
  640    ->  set_width_of_json_write_state(0, State, State2),
  641        write_pairs_hor(Pairs, Stream, State2, Options),
  642        write(Stream, '}')
  643    ;   step_indent(State, State2),
  644        write_pairs_ver(Pairs, Stream, State2, Options),
  645        indent(Stream, State),
  646        write(Stream, '}')
  647    ).
  648
  649
  650write_pairs_hor([], _, _, _).
  651write_pairs_hor([H|T], Stream, State, Options) :-
  652    json_pair(H, Name, Value),
  653    json_write_string(Stream, Name),
  654    write(Stream, ':'),
  655    json_write_term(Value, Stream, State, Options),
  656    (   T == []
  657    ->  true
  658    ;   write(Stream, ', '),
  659        write_pairs_hor(T, Stream, State, Options)
  660    ).
  661
  662write_pairs_ver([], _, _, _).
  663write_pairs_ver([H|T], Stream, State, Options) :-
  664    indent(Stream, State),
  665    json_pair(H, Name, Value),
  666    json_write_string(Stream, Name),
  667    write(Stream, ':'),
  668    json_write_term(Value, Stream, State, Options),
  669    (   T == []
  670    ->  true
  671    ;   write(Stream, ','),
  672        write_pairs_ver(T, Stream, State, Options)
  673    ).
  674
  675
  676json_pair(Var, _, _) :-
  677    var(Var),
  678    !,
  679    instantiation_error(Var).
  680json_pair(Name=Value, Name, Value) :- !.
  681json_pair(Name-Value, Name, Value) :- !.
  682json_pair(NameValue, Name, Value) :-
  683    compound(NameValue),
  684    NameValue =.. [Name, Value],
  685    !.
  686json_pair(Pair, _, _) :-
  687    type_error(json_pair, Pair).
  688
  689
  690write_array_hor([], _, _, _).
  691write_array_hor([H|T], Stream, State, Options) :-
  692    json_write_term(H, Stream, State, Options),
  693    (   T == []
  694    ->  write(Stream, ' ')
  695    ;   write(Stream, ', '),
  696        write_array_hor(T, Stream, State, Options)
  697    ).
  698
  699write_array_ver([], _, _, _).
  700write_array_ver([H|T], Stream, State, Options) :-
  701    indent(Stream, State),
  702    json_write_term(H, Stream, State, Options),
  703    (   T == []
  704    ->  true
  705    ;   write(Stream, ','),
  706        write_array_ver(T, Stream, State, Options)
  707    ).
  708
  709
  710indent(Stream, State) :-
  711    json_write_state_indent(State, Indent),
  712    json_write_state_tab(State, Tab),
  713    json_write_indent(Stream, Indent, Tab).
  714
  715step_indent(State0, State) :-
  716    json_write_state_indent(State0, Indent),
  717    json_write_state_step(State0, Step),
  718    NewIndent is Indent+Step,
  719    set_indent_of_json_write_state(NewIndent, State0, State).
  720
  721space_if_not_at_left_margin(Stream, State) :-
  722    stream_pair(Stream, _, Write),
  723    line_position(Write, LinePos),
  724    (   LinePos == 0
  725    ;   json_write_state_indent(State, LinePos)
  726    ),
  727    !.
  728space_if_not_at_left_margin(Stream, _) :-
  729    put_char(Stream, ' ').
 json_print_length(+Value, +Options, +Max, +Len0, +Len) is semidet
True if Len-Len0 is the print-length of Value on a single line and Len-Len0 =< Max.
To be done
- Escape sequences in strings are not considered.
  739json_print_length(Var, _, _, _, _) :-
  740    var(Var),
  741    !,
  742    instantiation_error(Var).
  743json_print_length(json(Pairs), Options, Max, Len0, Len) :-
  744    !,
  745    Len1 is Len0 + 2,
  746    Len1 =< Max,
  747    must_be(list, Pairs),
  748    pairs_print_length(Pairs, Options, Max, Len1, Len).
  749:- if(current_predicate(is_dict/1)).  750json_print_length(Dict, Options, Max, Len0, Len) :-
  751    is_dict(Dict),
  752    !,
  753    dict_pairs(Dict, _Tag, Pairs),
  754    Len1 is Len0 + 2,
  755    Len1 =< Max,
  756    pairs_print_length(Pairs, Options, Max, Len1, Len).
  757:- endif.  758json_print_length(Array, Options, Max, Len0, Len) :-
  759    is_list(Array),
  760    !,
  761    Len1 is Len0 + 2,
  762    Len1 =< Max,
  763    array_print_length(Array, Options, Max, Len1, Len).
  764json_print_length(Null, Options, Max, Len0, Len) :-
  765    json_options_null(Options, Null),
  766    !,
  767    Len is Len0 + 4,
  768    Len =< Max.
  769json_print_length(False, Options, Max, Len0, Len) :-
  770    json_options_false(Options, False),
  771    !,
  772    Len is Len0 + 5,
  773    Len =< Max.
  774json_print_length(True, Options, Max, Len0, Len) :-
  775    json_options_true(Options, True),
  776    !,
  777    Len is Len0 + 4,
  778    Len =< Max.
  779json_print_length(Number, _Options, Max, Len0, Len) :-
  780    number(Number),
  781    !,
  782    write_length(Number, AL, []),
  783    Len is Len0 + AL,
  784    Len =< Max.
  785json_print_length(@(Id), _Options, Max, Len0, Len) :-
  786    atom(Id),
  787    !,
  788    atom_length(Id, IdLen),
  789    Len is Len0+IdLen,
  790    Len =< Max.
  791json_print_length(String, _Options, Max, Len0, Len) :-
  792    string_len(String, Len0, Len),
  793    !,
  794    Len =< Max.
  795json_print_length(AnyTerm, _Options, Max, Len0, Len) :-
  796    write_length(AnyTerm, AL, []),          % will be serialized
  797    Len is Len0 + AL+2,
  798    Len =< Max.
  799
  800pairs_print_length([], _, _, Len, Len).
  801pairs_print_length([H|T], Options, Max, Len0, Len) :-
  802    pair_len(H, Options, Max, Len0, Len1),
  803    (   T == []
  804    ->  Len = Len1
  805    ;   Len2 is Len1 + 2,
  806        Len2 =< Max,
  807        pairs_print_length(T, Options, Max, Len2, Len)
  808    ).
  809
  810pair_len(Pair, Options, Max, Len0, Len) :-
  811    compound(Pair),
  812    pair_nv(Pair, Name, Value),
  813    !,
  814    string_len(Name, Len0, Len1),
  815    Len2 is Len1+2,
  816    Len2 =< Max,
  817    json_print_length(Value, Options, Max, Len2, Len).
  818pair_len(Pair, _Options, _Max, _Len0, _Len) :-
  819    type_error(pair, Pair).
  820
  821pair_nv(Name=Value, Name, Value) :- !.
  822pair_nv(Name-Value, Name, Value) :- !.
  823pair_nv(Term, Name, Value) :-
  824    compound_name_arguments(Term, Name, [Value]).
  825
  826array_print_length([], _, _, Len, Len).
  827array_print_length([H|T], Options, Max, Len0, Len) :-
  828    json_print_length(H, Options, Max, Len0, Len1),
  829    (   T == []
  830    ->  Len = Len1
  831    ;   Len2 is Len1+2,
  832        Len2 =< Max,
  833        array_print_length(T, Options, Max, Len2, Len)
  834    ).
  835
  836string_len(String, Len0, Len) :-
  837    atom(String),
  838    !,
  839    atom_length(String, AL),
  840    Len is Len0 + AL + 2.
  841string_len(String, Len0, Len) :-
  842    string(String),
  843    !,
  844    string_length(String, AL),
  845    Len is Len0 + AL + 2.
  846
  847
  848                 /*******************************
  849                 *             TEST             *
  850                 *******************************/
 is_json_term(@Term) is semidet
 is_json_term(@Term, +Options) is semidet
True if Term is a json term. Options are the same as for json_read/2, defining the Prolog representation for the JSON true, false and null constants.
  859is_json_term(Term) :-
  860    default_json_options(Options),
  861    is_json_term2(Options, Term).
  862
  863is_json_term(Term, Options) :-
  864    make_json_options(Options, OptionTerm, _RestOptions),
  865    is_json_term2(OptionTerm, Term).
  866
  867is_json_term2(_, Var) :-
  868    var(Var), !, fail.
  869is_json_term2(Options, json(Pairs)) :-
  870    !,
  871    is_list(Pairs),
  872    maplist(is_json_pair(Options), Pairs).
  873is_json_term2(Options, List) :-
  874    is_list(List),
  875    !,
  876    maplist(is_json_term2(Options), List).
  877is_json_term2(_, Primitive) :-
  878    atomic(Primitive),
  879    !.           % atom, string or number
  880is_json_term2(Options, True) :-
  881    json_options_true(Options, True).
  882is_json_term2(Options, False) :-
  883    json_options_false(Options, False).
  884is_json_term2(Options, Null) :-
  885    json_options_null(Options, Null).
  886
  887is_json_pair(_, Var) :-
  888    var(Var), !, fail.
  889is_json_pair(Options, Name=Value) :-
  890    atom(Name),
  891    is_json_term2(Options, Value).
  892
  893:- if(current_predicate(is_dict/1)).  894
  895                 /*******************************
  896                 *         DICT SUPPORT         *
  897                 *******************************/
 json_read_dict(+Stream, -Dict) is det
 json_read_dict(+Stream, -Dict, +Options) is det
Read a JSON object, returning objects as a dicts. The representation depends on the options, where the default is:

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(+Name)
When converting to/from a dict, map the indicated JSON attribute to the dict tag. No mapping is performed if Name is the empty atom ('', default). See json_read_dict/2 and json_write_dict/2.
default_tag(+Tag)
Provide the default tag if the above tag option does not apply.
null(+NullTerm)
Default the atom null.
true(+TrueTerm)
Default the atom true.
false +FalseTerm
Default the atom false
value_string_as(+Type)
Prolog type used for strings used as value. Default is string. The alternative is atom, producing a packed string object.
  936json_read_dict(Stream, Dict) :-
  937    json_read_dict(Stream, Dict, []).
  938
  939json_read_dict(Stream, Dict, Options) :-
  940    make_json_dict_options(Options, OptionTerm, _RestOptions),
  941    (   json_value_top(Stream, Term, OptionTerm)
  942    ->  true
  943    ;   syntax_error(illegal_json, Stream)
  944    ),
  945    term_to_dict(Term, Dict, OptionTerm).
  946
  947term_to_dict(json(Pairs), Dict, Options) :-
  948    !,
  949    (   json_options_tag(Options, TagName),
  950        Tag \== '',
  951        select(TagName = Tag0, Pairs, NVPairs),
  952        to_atom(Tag0, Tag)
  953    ->  json_dict_pairs(NVPairs, DictPairs, Options)
  954    ;   json_options_default_tag(Options, DefTag),
  955        (   var(DefTag)
  956        ->  true
  957        ;   Tag = DefTag
  958        ),
  959        json_dict_pairs(Pairs, DictPairs, Options)
  960    ),
  961    dict_create(Dict, Tag, DictPairs).
  962term_to_dict(Value0, Value, _Options) :-
  963    atomic(Value0), Value0 \== [],
  964    !,
  965    Value = Value0.
  966term_to_dict(List0, List, Options) :-
  967    is_list(List0),
  968    !,
  969    terms_to_dicts(List0, List, Options).
  970term_to_dict(Special, Special, Options) :-
  971    (   json_options_true(Options, Special)
  972    ;   json_options_false(Options, Special)
  973    ;   json_options_null(Options, Special)
  974    ;   json_options_end_of_file(Options, Special)
  975    ),
  976    !.
  977
  978json_dict_pairs([], [], _).
  979json_dict_pairs([Name=Value0|T0], [Name=Value|T], Options) :-
  980    term_to_dict(Value0, Value, Options),
  981    json_dict_pairs(T0, T, Options).
  982
  983terms_to_dicts([], [], _).
  984terms_to_dicts([Value0|T0], [Value|T], Options) :-
  985    term_to_dict(Value0, Value, Options),
  986    terms_to_dicts(T0, T, Options).
  987
  988to_atom(Tag, Atom) :-
  989    string(Tag),
  990    !,
  991    atom_string(Atom, Tag).
  992to_atom(Atom, Atom) :-
  993    atom(Atom).
 json_write_dict(+Stream, +Dict) is det
 json_write_dict(+Stream, +Dict, +Options) is det
Write a JSON term, represented using dicts. This is the same as json_write/3, but assuming the default representation of JSON objects as dicts.
 1002json_write_dict(Stream, Dict) :-
 1003    json_write_dict(Stream, Dict, []).
 1004
 1005json_write_dict(Stream, Dict, Options) :-
 1006    make_json_write_state(Options, State, Options1),
 1007    make_json_dict_options(Options1, OptionTerm, _RestOptions),
 1008    json_write_term(Dict, Stream, State, OptionTerm).
 1009
 1010
 1011make_json_dict_options(Options, Record, RestOptions) :-
 1012    default_json_dict_options(Record0),
 1013    set_json_options_fields(Options, Record0, Record, RestOptions).
 atom_json_dict(+Atom, -JSONDict, +Options) is det
atom_json_dict(-Text, +JSONDict, +Options) is det
Convert between textual representation and a JSON term represented as a dict. Options are as for json_read/3. In write mode, the addtional option
as(Type)
defines the output type, which is one of atom, string or codes.
 1026atom_json_dict(Atom, Term, Options) :-
 1027    ground(Atom),
 1028    !,
 1029    setup_call_cleanup(
 1030        ( text_memfile(Atom, MF),
 1031          open_memory_file(MF, read, In, [free_on_close(true)])
 1032        ),
 1033        json_read_dict(In, Term, Options),
 1034        close(In)).
 1035atom_json_dict(Result, Term, Options) :-
 1036    select_option(as(Type), Options, Options1, atom),
 1037    (   type_term(Type, Result, Out)
 1038    ->  true
 1039    ;   must_be(oneof([atom,string,codes]), Type)
 1040    ),
 1041    with_output_to(Out,
 1042                   json_write_dict(current_output, Term, Options1)).
 1043
 1044text_memfile(Atom, MF) :-
 1045    atom(Atom),
 1046    !,
 1047    atom_to_memory_file(Atom, MF).
 1048text_memfile(String, MF) :-
 1049    string(String),
 1050    !,
 1051    new_memory_file(MF),
 1052    insert_memory_file(MF, 0, String).
 1053
 1054:- endif. 1055
 1056                 /*******************************
 1057                 *           MESSAGES           *
 1058                 *******************************/
 1059
 1060:- multifile
 1061    prolog:error_message/3. 1062
 1063prolog:error_message(syntax_error(json(Id))) -->
 1064    [ 'JSON syntax error: ' ],
 1065    json_syntax_error(Id).
 1066
 1067json_syntax_error(illegal_comment) -->
 1068    [ 'Illegal comment' ].
 1069json_syntax_error(illegal_string_escape) -->
 1070    [ 'Illegal escape sequence in string' ]