View source with formatted 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-2016, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- if(current_predicate(is_dict/1)).   37
   38:- module(json,
   39          [ json_read/2,                % +Stream, -JSONTerm
   40            json_read/3,                % +Stream, -JSONTerm, +Options
   41            atom_json_term/3,           % ?Atom, ?JSONTerm, +Options
   42            json_write/2,               % +Stream, +Term
   43            json_write/3,               % +Stream, +Term, +Options
   44            is_json_term/1,             % @Term
   45            is_json_term/2,             % @Term, +Options
   46                                        % Version 7 dict support
   47            json_read_dict/2,           % +Stream, -Dict
   48            json_read_dict/3,           % +Stream, -Dict, +Options
   49            json_write_dict/2,          % +Stream, +Dict
   50            json_write_dict/3,          % +Stream, +Dict, +Options
   51            atom_json_dict/3            % ?Atom, ?JSONDict, +Options
   52          ]).   53
   54:- else.   55
   56:- module(json,
   57          [ json_read/2,                % +Stream, -JSONTerm
   58            json_read/3,                % +Stream, -JSONTerm, +Options
   59            atom_json_term/3,           % ?Atom, ?JSONTerm, +Options
   60            json_write/2,               % +Stream, +Term
   61            json_write/3,               % +Stream, +Term, +Options
   62            is_json_term/1,             % @Term
   63            is_json_term/2
   64          ]).   65
   66:- endif.   67
   68:- use_module(library(record)).   69:- use_module(library(memfile)).   70:- use_module(library(error)).   71:- use_module(library(option)).   72
   73:- use_foreign_library(foreign(json)).   74
   75:- predicate_options(json_read/3, 3,
   76                     [ null(ground),
   77                       true(ground),
   78                       false(ground),
   79                       value_string_as(oneof([atom,string]))
   80                     ]).   81:- predicate_options(json_write/3, 3,
   82                     [ indent(nonneg),
   83                       step(positive_integer),
   84                       tab(positive_integer),
   85                       width(nonneg),
   86                       null(ground),
   87                       true(ground),
   88                       false(ground),
   89                       serialize_unknown(boolean)
   90                     ]).   91:- predicate_options(json_read_dict/3, 3,
   92                     [ tag(atom),
   93                       pass_to(json_read/3, 3)
   94                     ]).   95:- predicate_options(json_write_dict/3, 3,
   96                     [ tag(atom),
   97                       pass_to(json_write/3, 3)
   98                     ]).   99:- predicate_options(is_json_term/2, 2,
  100                     [ null(ground),
  101                       true(ground),
  102                       false(ground)
  103                     ]).  104:- predicate_options(atom_json_term/3, 3,
  105                     [ as(oneof([atom,string,codes])),
  106                       pass_to(json_read/3, 3),
  107                       pass_to(json_write/3, 3)
  108                     ]).  109
  110/** <module> Reading and writing JSON serialization
  111
  112This module supports reading and  writing   JSON  objects.  This library
  113supports two Prolog representations (the   _new_  representation is only
  114supported in SWI-Prolog version 7 and later):
  115
  116  - The *classical* representation is provided by json_read/3 and
  117    json_write/3.  This represents a JSON object as json(NameValueList),
  118    a JSON string as an atom and the JSON constants =null=, =true= and
  119    =false= as @(null), @(true) and @false.
  120
  121  - The *new* representation is provided by json_read_dict/3 and
  122    json_write_dict/3. This represents a JSON object as a dict, a JSON
  123    string as a Prolog string and the JSON constants using the Prolog
  124    atoms =null=, =true= and =false=.
  125
  126@author Jan Wielemaker
  127@see    http_json.pl links JSON to the HTTP client and server modules.
  128@see    json_convert.pl converts JSON Prolog terms to more comfortable
  129terms.
  130*/
  131
  132:- record json_options(null:ground = @(null),
  133                   true:ground = @(true),
  134                   false:ground = @(false),
  135                   value_string_as:oneof([atom,string]) = atom,
  136                   tag:atom = '').  137
  138default_json_dict_options(
  139    json_options(null, true, false, string, '')).
  140
  141
  142                 /*******************************
  143                 *       MAP TO/FROM TEXT       *
  144                 *******************************/
  145
  146%!  atom_json_term(?Atom, ?JSONTerm, +Options) is det.
  147%
  148%   Convert between textual  representation  and   a  JSON  term. In
  149%   _write_ mode (JSONTerm to Atom), the option
  150%
  151%       * as(Type)
  152%       defines the output type, which is one of =atom= (default),
  153%       =string=, =codes= or =chars=.
  154
  155atom_json_term(Atom, Term, Options) :-
  156    ground(Atom),
  157    !,
  158    setup_call_cleanup(
  159        ( atom_to_memory_file(Atom, MF),
  160          open_memory_file(MF, read, In, [free_on_close(true)])
  161        ),
  162        json_read(In, Term, Options),
  163        close(In)).
  164atom_json_term(Result, Term, Options) :-
  165    select_option(as(Type), Options, Options1, atom),
  166    (   type_term(Type, Result, Out)
  167    ->  true
  168    ;   must_be(oneof([atom,string,codes,chars]), Type)
  169    ),
  170    with_output_to(Out,
  171                   json_write(current_output, Term, Options1)).
  172
  173type_term(atom,   Result, atom(Result)).
  174type_term(string, Result, string(Result)).
  175type_term(codes,  Result, codes(Result)).
  176type_term(chars,  Result, chars(Result)).
  177
  178
  179                 /*******************************
  180                 *           READING            *
  181                 *******************************/
  182
  183%!  json_read(+Stream, -Term) is det.
  184%!  json_read(+Stream, -Term, +Options) is det.
  185%
  186%   Read next JSON value from Stream into a Prolog term. The
  187%   canonical representation for Term is:
  188%
  189%     * A JSON object is mapped to a term json(NameValueList), where
  190%       NameValueList is a list of Name=Value. Name is an atom
  191%       created from the JSON string.
  192%
  193%     * A JSON array is mapped to a Prolog list of JSON values.
  194%
  195%     * A JSON string is mapped to a Prolog atom
  196%
  197%     * A JSON number is mapped to a Prolog number
  198%
  199%     * The JSON constants =true= and =false= are mapped -like JPL-
  200%       to @(true) and @(false).
  201%
  202%     * The JSON constant =null= is mapped to the Prolog term
  203%       @(null)
  204%
  205%   Here is a complete example in  JSON and its corresponding Prolog
  206%   term.
  207%
  208%     ==
  209%     { "name":"Demo term",
  210%       "created": {
  211%         "day":null,
  212%         "month":"December",
  213%         "year":2007
  214%       },
  215%       "confirmed":true,
  216%       "members":[1,2,3]
  217%     }
  218%     ==
  219%
  220%     ==
  221%     json([ name='Demo term',
  222%            created=json([day= @null, month='December', year=2007]),
  223%            confirmed= @true,
  224%            members=[1, 2, 3]
  225%          ])
  226%     ==
  227%
  228%   The following options are processed:
  229%
  230%           * null(+NullTerm)
  231%           Term used to represent JSON =null=.  Default @(null)
  232%           * true(+TrueTerm)
  233%           Term used to represent JSON =true=.  Default @(true)
  234%           * false(+FalseTerm)
  235%           Term used to represent JSON =false=.  Default @(false)
  236%           * value_string_as(+Type)
  237%           Prolog type used for strings used as value.  Default
  238%           is =atom=.  The alternative is =string=, producing a
  239%           packed string object.  Please note that =codes= or
  240%           =chars= would produce ambiguous output and is therefore
  241%           not supported.
  242%
  243%   @see    json_read_dict/3 to read a JSON term using the version 7
  244%           extended data types.
  245
  246json_read(Stream, Term) :-
  247    default_json_options(Options),
  248    (   json_value(Stream, Term, _, Options)
  249    ->  true
  250    ;   syntax_error(illegal_json, Stream)
  251    ).
  252json_read(Stream, Term, Options) :-
  253    make_json_options(Options, OptionTerm, _RestOptions),
  254    (   json_value(Stream, Term, _, OptionTerm)
  255    ->  true
  256    ;   syntax_error(illegal_json, Stream)
  257    ).
  258
  259json_value(Stream, Term, Next, Options) :-
  260    get_code(Stream, C0),
  261    ws(C0, Stream, C1),
  262    (   C1 == -1
  263    ->  syntax_error(unexpected_end_of_file, Stream)
  264    ;   json_term(C1, Stream, Term, Next, Options)
  265    ).
  266
  267json_term(0'{, Stream, json(Pairs), Next, Options) :-
  268    !,
  269    ws(Stream, C),
  270    json_pairs(C, Stream, Pairs, Options),
  271    get_code(Stream, Next).
  272json_term(0'[, Stream, Array, Next, Options) :-
  273    !,
  274    ws(Stream, C),
  275    json_array(C, Stream, Array, Options),
  276    get_code(Stream, Next).
  277json_term(0'", Stream, String, Next, Options) :-
  278    !,
  279    get_code(Stream, C1),
  280    json_string_codes(C1, Stream, Codes),
  281    json_options_value_string_as(Options, Type),
  282    codes_to_type(Type, Codes, String),
  283    get_code(Stream, Next).
  284json_term(0'-, Stream, Number, Next, _Options) :-
  285    !,
  286    json_number_codes(Stream, Codes, Next),
  287    number_codes(Number, [0'-|Codes]).
  288json_term(D, Stream, Number, Next, _Options) :-
  289    between(0'0, 0'9, D),
  290    !,
  291    json_number_codes(Stream, Codes, Next),
  292    number_codes(Number, [D|Codes]).
  293json_term(C, Stream, Constant, Next, Options) :-
  294    get_code(Stream, C1),
  295    json_identifier_codes(C1, Stream, Codes, Next),
  296    atom_codes(ID, [C|Codes]),
  297    json_constant(ID, Constant, Options).
  298
  299json_pairs(0'}, _, [], _) :- !.
  300json_pairs(C0, Stream, [Pair|Tail], Options) :-
  301    json_pair(C0, Stream, Pair, C, Options),
  302    ws(C, Stream, Next),
  303    (   Next == 0',
  304    ->  ws(Stream, C2),
  305        json_pairs(C2, Stream, Tail, Options)
  306    ;   Next == 0'}
  307    ->  Tail = []
  308    ;   syntax_error(illegal_object, Stream)
  309    ).
  310
  311json_pair(C0, Stream, Name=Value, Next, Options) :-
  312    json_string_as_atom(C0, Stream, Name),
  313    ws(Stream, C),
  314    C == 0':,
  315    json_value(Stream, Value, Next, Options).
  316
  317
  318json_array(0'], _, [], _) :- !.
  319json_array(C0, Stream, [Value|Tail], Options) :-
  320    json_term(C0, Stream, Value, C, Options),
  321    ws(C, Stream, Next),
  322    (   Next == 0',
  323    ->  ws(Stream, C1),
  324        json_array(C1, Stream, Tail, Options)
  325    ;   Next == 0']
  326    ->  Tail = []
  327    ;   syntax_error(illegal_array, Stream)
  328    ).
  329
  330codes_to_type(atom, Codes, Atom) :-
  331    atom_codes(Atom, Codes).
  332codes_to_type(string, Codes, Atom) :-
  333    string_codes(Atom, Codes).
  334codes_to_type(codes, Codes, Codes).
  335
  336json_string_as_atom(0'", Stream, Atom) :-
  337    get_code(Stream, C1),
  338    json_string_codes(C1, Stream, Codes),
  339    atom_codes(Atom, Codes).
  340
  341json_string_codes(0'", _, []) :- !.
  342json_string_codes(0'\\, Stream, [H|T]) :-
  343    !,
  344    get_code(Stream, C0),
  345    (   escape(C0, Stream, H)
  346    ->  true
  347    ;   syntax_error(illegal_string_escape, Stream)
  348    ),
  349    get_code(Stream, C1),
  350    json_string_codes(C1, Stream, T).
  351json_string_codes(-1, Stream, _) :-
  352    !,
  353    syntax_error(eof_in_string, Stream).
  354json_string_codes(C, Stream, [C|T]) :-
  355    get_code(Stream, C1),
  356    json_string_codes(C1, Stream, T).
  357
  358escape(0'", _, 0'") :- !.
  359escape(0'\\, _, 0'\\) :- !.
  360escape(0'/, _, 0'/) :- !.
  361escape(0'b, _, 0'\b) :- !.
  362escape(0'f, _, 0'\f) :- !.
  363escape(0'n, _, 0'\n) :- !.
  364escape(0'r, _, 0'\r) :- !.
  365escape(0't, _, 0'\t) :- !.
  366escape(0'u, Stream, C) :-
  367    !,
  368    get_code(Stream, C1),
  369    get_code(Stream, C2),
  370    get_code(Stream, C3),
  371    get_code(Stream, C4),
  372    code_type(C1, xdigit(D1)),
  373    code_type(C2, xdigit(D2)),
  374    code_type(C3, xdigit(D3)),
  375    code_type(C4, xdigit(D4)),
  376    C is D1<<12+D2<<8+D3<<4+D4.
  377
  378json_number_codes(Stream, Codes, Next) :-
  379    get_code(Stream, C1),
  380    json_number_codes(C1, Stream, Codes, Next).
  381
  382json_number_codes(C1, Stream, [C1|Codes], Next) :-
  383    number_code(C1),
  384    !,
  385    get_code(Stream, C2),
  386    json_number_codes(C2, Stream, Codes, Next).
  387json_number_codes(C, _, [], C).
  388
  389number_code(C) :-
  390    between(0'0, 0'9, C),
  391    !.
  392number_code(0'.).
  393number_code(0'-).
  394number_code(0'+).
  395number_code(0'e).
  396number_code(0'E).
  397
  398json_identifier_codes(C1, Stream, [C1|T], Next) :-
  399    between(0'a, 0'z, C1),
  400    !,
  401    get_code(Stream, C2),
  402    json_identifier_codes(C2, Stream, T, Next).
  403json_identifier_codes(C, _, [], C).
  404
  405
  406json_constant(true, Constant, Options) :-
  407    !,
  408    json_options_true(Options, Constant).
  409json_constant(false, Constant, Options) :-
  410    !,
  411    json_options_false(Options, Constant).
  412json_constant(null, Constant, Options) :-
  413    !,
  414    json_options_null(Options, Constant).
  415
  416%!  ws(+Stream, -Next) is det.
  417%!  ws(+C0, +Stream, -Next)
  418%
  419%   Skip white space on the Stream, returning the first non-ws
  420%   character.  Also skips =|//|= ... comments.
  421
  422ws(Stream, Next) :-
  423    get_code(Stream, C0),
  424    ws(C0, Stream, Next).
  425
  426ws(C0, Stream, C) :-
  427    ws(C0),
  428    !,
  429    get_code(Stream, C1),
  430    ws(C1, Stream, C).
  431ws(0'/, Stream, C) :-
  432    !,
  433    get_code(Stream, Cmt1),
  434    !,
  435    expect(Cmt1, 0'/, Stream),
  436    skip(Stream, 0'\n),
  437    get_code(Stream, C0),
  438    ws(C0, Stream, C).
  439ws(C, _, C).
  440
  441ws(0' ).
  442ws(0'\t).
  443ws(0'\n).
  444ws(0'\r).
  445
  446expect(C, C, _) :- !.
  447expect(_, 0'/, Stream) :-
  448    !,
  449    syntax_error(illegal_comment, Stream).
  450
  451syntax_error(Message, Stream) :-
  452    stream_error_context(Stream, Context),
  453    throw(error(syntax_error(json(Message)), Context)).
  454
  455stream_error_context(Stream, stream(Stream, Line, LinePos, CharNo)) :-
  456    stream_pair(Stream, Read, _),
  457    character_count(Read, CharNo),
  458    line_position(Read, LinePos),
  459    line_count(Read, Line).
  460
  461
  462                 /*******************************
  463                 *          JSON OUTPUT         *
  464                 *******************************/
  465
  466%!  json_write_string(+Stream, +Text) is det.
  467%
  468%   Write a JSON string to  Stream.  Stream   must  be  opened  in a
  469%   Unicode capable encoding, typically UTF-8.
  470
  471% foreign json_write_string/2.
  472
  473%!  json_write_indent(+Stream, +Indent, +TabDistance) is det.
  474%
  475%   Newline and indent to  Indent.  A   Newline  is  only written if
  476%   line_position(Stream, Pos) is not 0. Then   it  writes Indent //
  477%   TabDistance tab characters and Indent mode TabDistance spaces.
  478
  479% foreign json_write_indent/3.
  480
  481%!  json_write(+Stream, +Term) is det.
  482%!  json_write(+Stream, +Term, +Options) is det.
  483%
  484%   Write a JSON term to Stream.  The   JSON  object  is of the same
  485%   format as produced by json_read/2, though we allow for some more
  486%   flexibility with regard to pairs in  objects. All of Name=Value,
  487%   Name-Value and Name(Value) produce the  same output.
  488%
  489%   Values can be of the form  #(Term),   which  causes `Term` to be
  490%   _stringified_ if it is not an atom or string. Stringification is
  491%   based on term_string/2.
  492%
  493%   The version 7 _dict_ type is supported as well. If the dicts has
  494%   a _tag_, a property "type":"tag" is   added  to the object. This
  495%   behaviour can be changed using the =tag= option (see below). For
  496%   example:
  497%
  498%     ==
  499%     ?- json_write(current_output, point{x:1,y:2}).
  500%     {
  501%       "type":"point",
  502%       "x":1,
  503%       "y":2
  504%     }
  505%     ==
  506%
  507%   In addition to the options recognised by json_read/3, we process
  508%   the following options are recognised:
  509%
  510%       * width(+Width)
  511%       Width in which we try to format the result.  Too long lines
  512%       switch from _horizontal_ to _vertical_ layout for better
  513%       readability. If performance is critical and human
  514%       readability is not an issue use Width = 0, which causes a
  515%       single-line output.
  516%
  517%       * step(+Step)
  518%       Indentation increnment for next level.  Default is 2.
  519%
  520%       * tab(+TabDistance)
  521%       Distance between tab-stops.  If equal to Step, layout
  522%       is generated with one tab per level.
  523%
  524%       * serialize_unknown(+Boolean)
  525%       If =true= (default =false=), serialize unknown terms and
  526%       print them as a JSON string.  The default raises a type
  527%       error.  Note that this option only makes sense if you can
  528%       guarantee that the passed value is not an otherwise valid
  529%       Prolog reporesentation of a Prolog term.
  530%
  531%   If a string is  emitted,  the   sequence  =|</|=  is  emitted as
  532%   =|<\/|=. This is valid  JSON  syntax   which  ensures  that JSON
  533%   objects  can  be  safely  embedded  into  an  HTML  =|<script>|=
  534%   element.
  535
  536:- record json_write_state(indent:nonneg = 0,
  537                       step:positive_integer = 2,
  538                       tab:positive_integer = 8,
  539                       width:nonneg = 72,
  540                       serialize_unknown:boolean = false
  541                      ).  542
  543json_write(Stream, Term) :-
  544    json_write(Stream, Term, []).
  545json_write(Stream, Term, Options) :-
  546    make_json_write_state(Options, State, Options1),
  547    make_json_options(Options1, OptionTerm, _RestOptions),
  548    json_write_term(Term, Stream, State, OptionTerm).
  549
  550json_write_term(Var, _, _, _) :-
  551    var(Var),
  552    !,
  553    instantiation_error(Var).
  554json_write_term(json(Pairs), Stream, State, Options) :-
  555    !,
  556    json_write_object(Pairs, Stream, State, Options).
  557:- if(current_predicate(is_dict/1)).  558json_write_term(Dict, Stream, State, Options) :-
  559    is_dict(Dict),
  560    !,
  561    dict_pairs(Dict, Tag, Pairs0),
  562    (   nonvar(Tag),
  563        json_options_tag(Options, Name),
  564        Name \== ''
  565    ->  Pairs = [Name-Tag|Pairs0]
  566    ;   Pairs = Pairs0
  567    ),
  568    json_write_object(Pairs, Stream, State, Options).
  569:- endif.  570json_write_term(List, Stream, State, Options) :-
  571    is_list(List),
  572    !,
  573    space_if_not_at_left_margin(Stream, State),
  574    write(Stream, '['),
  575    (   json_write_state_width(State, Width),
  576        (   Width == 0
  577        ->  true
  578        ;   json_write_state_indent(State, Indent),
  579            json_print_length(List, Options, Width, Indent, _)
  580        )
  581    ->  set_width_of_json_write_state(0, State, State2),
  582        write_array_hor(List, Stream, State2, Options),
  583        write(Stream, ']')
  584    ;   step_indent(State, State2),
  585        write_array_ver(List, Stream, State2, Options),
  586        indent(Stream, State),
  587        write(Stream, ']')
  588    ).
  589json_write_term(Number, Stream, _State, _Options) :-
  590    number(Number),
  591    !,
  592    write(Stream, Number).
  593json_write_term(True, Stream, _State, Options) :-
  594    json_options_true(Options, True),
  595    !,
  596    write(Stream, true).
  597json_write_term(False, Stream, _State, Options) :-
  598    json_options_false(Options, False),
  599    !,
  600    write(Stream, false).
  601json_write_term(Null, Stream, _State, Options) :-
  602    json_options_null(Options, Null),
  603    !,
  604    write(Stream, null).
  605json_write_term(#(Text), Stream, _State, _Options) :-
  606    !,
  607    (   (   atom(Text)
  608        ;   string(Text)
  609        )
  610    ->  json_write_string(Stream, Text)
  611    ;   term_string(Text, String),
  612        json_write_string(Stream, String)
  613    ).
  614json_write_term(String, Stream, _State, _Options) :-
  615    atom(String),
  616    !,
  617    json_write_string(Stream, String).
  618json_write_term(String, Stream, _State, _Options) :-
  619    string(String),
  620    !,
  621    json_write_string(Stream, String).
  622json_write_term(AnyTerm, Stream, State, _Options) :-
  623    (   json_write_state_serialize_unknown(State, true)
  624    ->  term_string(AnyTerm, String),
  625        json_write_string(Stream, String)
  626    ;   type_error(json_term, AnyTerm)
  627    ).
  628
  629json_write_object(Pairs, Stream, State, Options) :-
  630    space_if_not_at_left_margin(Stream, State),
  631    write(Stream, '{'),
  632    (   json_write_state_width(State, Width),
  633        (   Width == 0
  634        ->  true
  635        ;   json_write_state_indent(State, Indent),
  636            json_print_length(json(Pairs), Options, Width, Indent, _)
  637        )
  638    ->  set_width_of_json_write_state(0, State, State2),
  639        write_pairs_hor(Pairs, Stream, State2, Options),
  640        write(Stream, '}')
  641    ;   step_indent(State, State2),
  642        write_pairs_ver(Pairs, Stream, State2, Options),
  643        indent(Stream, State),
  644        write(Stream, '}')
  645    ).
  646
  647
  648write_pairs_hor([], _, _, _).
  649write_pairs_hor([H|T], Stream, State, Options) :-
  650    json_pair(H, Name, Value),
  651    json_write_string(Stream, Name),
  652    write(Stream, ':'),
  653    json_write_term(Value, Stream, State, Options),
  654    (   T == []
  655    ->  true
  656    ;   write(Stream, ', '),
  657        write_pairs_hor(T, Stream, State, Options)
  658    ).
  659
  660write_pairs_ver([], _, _, _).
  661write_pairs_ver([H|T], Stream, State, Options) :-
  662    indent(Stream, State),
  663    json_pair(H, Name, Value),
  664    json_write_string(Stream, Name),
  665    write(Stream, ':'),
  666    json_write_term(Value, Stream, State, Options),
  667    (   T == []
  668    ->  true
  669    ;   write(Stream, ','),
  670        write_pairs_ver(T, Stream, State, Options)
  671    ).
  672
  673
  674json_pair(Var, _, _) :-
  675    var(Var),
  676    !,
  677    instantiation_error(Var).
  678json_pair(Name=Value, Name, Value) :- !.
  679json_pair(Name-Value, Name, Value) :- !.
  680json_pair(NameValue, Name, Value) :-
  681    compound(NameValue),
  682    NameValue =.. [Name, Value],
  683    !.
  684json_pair(Pair, _, _) :-
  685    type_error(json_pair, Pair).
  686
  687
  688write_array_hor([], _, _, _).
  689write_array_hor([H|T], Stream, State, Options) :-
  690    json_write_term(H, Stream, State, Options),
  691    (   T == []
  692    ->  write(Stream, ' ')
  693    ;   write(Stream, ', '),
  694        write_array_hor(T, Stream, State, Options)
  695    ).
  696
  697write_array_ver([], _, _, _).
  698write_array_ver([H|T], Stream, State, Options) :-
  699    indent(Stream, State),
  700    json_write_term(H, Stream, State, Options),
  701    (   T == []
  702    ->  true
  703    ;   write(Stream, ','),
  704        write_array_ver(T, Stream, State, Options)
  705    ).
  706
  707
  708indent(Stream, State) :-
  709    json_write_state_indent(State, Indent),
  710    json_write_state_tab(State, Tab),
  711    json_write_indent(Stream, Indent, Tab).
  712
  713step_indent(State0, State) :-
  714    json_write_state_indent(State0, Indent),
  715    json_write_state_step(State0, Step),
  716    NewIndent is Indent+Step,
  717    set_indent_of_json_write_state(NewIndent, State0, State).
  718
  719space_if_not_at_left_margin(Stream, State) :-
  720    stream_pair(Stream, _, Write),
  721    line_position(Write, LinePos),
  722    (   LinePos == 0
  723    ;   json_write_state_indent(State, LinePos)
  724    ),
  725    !.
  726space_if_not_at_left_margin(Stream, _) :-
  727    put_char(Stream, ' ').
  728
  729
  730%!  json_print_length(+Value, +Options, +Max, +Len0, +Len) is semidet.
  731%
  732%   True if Len-Len0 is the print-length of Value on a single line
  733%   and Len-Len0 =< Max.
  734%
  735%   @tbd    Escape sequences in strings are not considered.
  736
  737json_print_length(Var, _, _, _, _) :-
  738    var(Var),
  739    !,
  740    instantiation_error(Var).
  741json_print_length(json(Pairs), Options, Max, Len0, Len) :-
  742    !,
  743    Len1 is Len0 + 2,
  744    Len1 =< Max,
  745    must_be(list, Pairs),
  746    pairs_print_length(Pairs, Options, Max, Len1, Len).
  747:- if(current_predicate(is_dict/1)).  748json_print_length(Dict, Options, Max, Len0, Len) :-
  749    is_dict(Dict),
  750    !,
  751    dict_pairs(Dict, _Tag, Pairs),
  752    Len1 is Len0 + 2,
  753    Len1 =< Max,
  754    pairs_print_length(Pairs, Options, Max, Len1, Len).
  755:- endif.  756json_print_length(Array, Options, Max, Len0, Len) :-
  757    is_list(Array),
  758    !,
  759    Len1 is Len0 + 2,
  760    Len1 =< Max,
  761    array_print_length(Array, Options, Max, Len1, Len).
  762json_print_length(Null, Options, Max, Len0, Len) :-
  763    json_options_null(Options, Null),
  764    !,
  765    Len is Len0 + 4,
  766    Len =< Max.
  767json_print_length(False, Options, Max, Len0, Len) :-
  768    json_options_false(Options, False),
  769    !,
  770    Len is Len0 + 5,
  771    Len =< Max.
  772json_print_length(True, Options, Max, Len0, Len) :-
  773    json_options_true(Options, True),
  774    !,
  775    Len is Len0 + 4,
  776    Len =< Max.
  777json_print_length(Number, _Options, Max, Len0, Len) :-
  778    number(Number),
  779    !,
  780    write_length(Number, AL, []),
  781    Len is Len0 + AL,
  782    Len =< Max.
  783json_print_length(@(Id), _Options, Max, Len0, Len) :-
  784    atom(Id),
  785    !,
  786    atom_length(Id, IdLen),
  787    Len is Len0+IdLen,
  788    Len =< Max.
  789json_print_length(String, _Options, Max, Len0, Len) :-
  790    string_len(String, Len0, Len),
  791    !,
  792    Len =< Max.
  793json_print_length(AnyTerm, _Options, Max, Len0, Len) :-
  794    write_length(AnyTerm, AL, []),          % will be serialized
  795    Len is Len0 + AL+2,
  796    Len =< Max.
  797
  798pairs_print_length([], _, _, Len, Len).
  799pairs_print_length([H|T], Options, Max, Len0, Len) :-
  800    pair_len(H, Options, Max, Len0, Len1),
  801    (   T == []
  802    ->  Len = Len1
  803    ;   Len2 is Len1 + 2,
  804        Len2 =< Max,
  805        pairs_print_length(T, Options, Max, Len2, Len)
  806    ).
  807
  808pair_len(Pair, Options, Max, Len0, Len) :-
  809    compound(Pair),
  810    pair_nv(Pair, Name, Value),
  811    !,
  812    string_len(Name, Len0, Len1),
  813    Len2 is Len1+2,
  814    Len2 =< Max,
  815    json_print_length(Value, Options, Max, Len2, Len).
  816pair_len(Pair, _Options, _Max, _Len0, _Len) :-
  817    type_error(pair, Pair).
  818
  819pair_nv(Name=Value, Name, Value) :- !.
  820pair_nv(Name-Value, Name, Value) :- !.
  821pair_nv(Term, Name, Value) :-
  822    compound_name_arguments(Term, Name, [Value]).
  823
  824array_print_length([], _, _, Len, Len).
  825array_print_length([H|T], Options, Max, Len0, Len) :-
  826    json_print_length(H, Options, Max, Len0, Len1),
  827    (   T == []
  828    ->  Len = Len1
  829    ;   Len2 is Len1+2,
  830        Len2 =< Max,
  831        array_print_length(T, Options, Max, Len2, Len)
  832    ).
  833
  834string_len(String, Len0, Len) :-
  835    atom(String),
  836    !,
  837    atom_length(String, AL),
  838    Len is Len0 + AL + 2.
  839string_len(String, Len0, Len) :-
  840    string(String),
  841    !,
  842    string_length(String, AL),
  843    Len is Len0 + AL + 2.
  844
  845
  846                 /*******************************
  847                 *             TEST             *
  848                 *******************************/
  849
  850%!  is_json_term(@Term) is semidet.
  851%!  is_json_term(@Term, +Options) is semidet.
  852%
  853%   True if Term is  a  json  term.   Options  are  the  same as for
  854%   json_read/2, defining the Prolog  representation   for  the JSON
  855%   =true=, =false= and =null= constants.
  856
  857is_json_term(Term) :-
  858    default_json_options(Options),
  859    is_json_term2(Options, Term).
  860
  861is_json_term(Term, Options) :-
  862    make_json_options(Options, OptionTerm, _RestOptions),
  863    is_json_term2(OptionTerm, Term).
  864
  865is_json_term2(_, Var) :-
  866    var(Var), !, fail.
  867is_json_term2(Options, json(Pairs)) :-
  868    !,
  869    is_list(Pairs),
  870    maplist(is_json_pair(Options), Pairs).
  871is_json_term2(Options, List) :-
  872    is_list(List),
  873    !,
  874    maplist(is_json_term2(Options), List).
  875is_json_term2(_, Primitive) :-
  876    atomic(Primitive),
  877    !.           % atom, string or number
  878is_json_term2(Options, True) :-
  879    json_options_true(Options, True).
  880is_json_term2(Options, False) :-
  881    json_options_false(Options, False).
  882is_json_term2(Options, Null) :-
  883    json_options_null(Options, Null).
  884
  885is_json_pair(_, Var) :-
  886    var(Var), !, fail.
  887is_json_pair(Options, Name=Value) :-
  888    atom(Name),
  889    is_json_term2(Options, Value).
  890
  891:- if(current_predicate(is_dict/1)).  892
  893                 /*******************************
  894                 *         DICT SUPPORT         *
  895                 *******************************/
  896
  897%!  json_read_dict(+Stream, -Dict) is det.
  898%!  json_read_dict(+Stream, -Dict, +Options) is det.
  899%
  900%   Read  a  JSON  object,  returning  objects    as  a  dicts.  The
  901%   representation depends on the options, where the default is:
  902%
  903%     * String values are mapped to Prolog strings
  904%     * JSON =true=, =false= and =null= are represented using these
  905%       Prolog atoms.
  906%     * JSON objects are mapped to dicts.
  907%     * By default, a =type= field in an object assigns a tag for
  908%       the dict.
  909%
  910%   The predicate json_read_dict/3 processes  the   same  options as
  911%   json_read/3,  but  with  different  defaults.  In  addition,  it
  912%   processes the `tag` option. See   json_read/3  for details about
  913%   the shared options.
  914%
  915%     * tag(+Name)
  916%       When converting to/from a dict, map the indicated JSON
  917%       attribute to the dict _tag_. No mapping is performed if Name
  918%       is the empty atom ('', default). See json_read_dict/2 and
  919%       json_write_dict/2.
  920%     * null(+NullTerm)
  921%     Default the atom `null`.
  922%     * true(+TrueTerm)
  923%     Default the atom `true`.
  924%     * false(+FalseTerm)
  925%     Default the atom `false`
  926%     * value_string_as(+Type)
  927%     Prolog type used for strings used as value.  Default
  928%     is =string=.  The alternative is =atom=, producing a
  929%     packed string object.
  930
  931json_read_dict(Stream, Dict) :-
  932    json_read_dict(Stream, Dict, []).
  933
  934json_read_dict(Stream, Dict, Options) :-
  935    make_json_dict_options(Options, OptionTerm, _RestOptions),
  936    (   json_value(Stream, Term, _, OptionTerm)
  937    ->  true
  938    ;   syntax_error(illegal_json, Stream)
  939    ),
  940    term_to_dict(Term, Dict, OptionTerm).
  941
  942term_to_dict(json(Pairs), Dict, Options) :-
  943    !,
  944    (   json_options_tag(Options, TagName),
  945        Tag \== '',
  946        select(TagName = Tag0, Pairs, NVPairs),
  947        to_atom(Tag0, Tag)
  948    ->  json_dict_pairs(NVPairs, DictPairs, Options)
  949    ;   json_dict_pairs(Pairs, DictPairs, Options)
  950    ),
  951    dict_create(Dict, Tag, DictPairs).
  952term_to_dict(Value0, Value, _Options) :-
  953    atomic(Value0), Value0 \== [],
  954    !,
  955    Value = Value0.
  956term_to_dict(List0, List, Options) :-
  957    assertion(is_list(List0)),
  958    terms_to_dicts(List0, List, Options).
  959
  960json_dict_pairs([], [], _).
  961json_dict_pairs([Name=Value0|T0], [Name=Value|T], Options) :-
  962    term_to_dict(Value0, Value, Options),
  963    json_dict_pairs(T0, T, Options).
  964
  965terms_to_dicts([], [], _).
  966terms_to_dicts([Value0|T0], [Value|T], Options) :-
  967    term_to_dict(Value0, Value, Options),
  968    terms_to_dicts(T0, T, Options).
  969
  970to_atom(Tag, Atom) :-
  971    string(Tag),
  972    !,
  973    atom_string(Atom, Tag).
  974to_atom(Atom, Atom) :-
  975    atom(Atom).
  976
  977%!  json_write_dict(+Stream, +Dict) is det.
  978%!  json_write_dict(+Stream, +Dict, +Options) is det.
  979%
  980%   Write a JSON term, represented using dicts.  This is the same as
  981%   json_write/3, but assuming the default   representation  of JSON
  982%   objects as dicts.
  983
  984json_write_dict(Stream, Dict) :-
  985    json_write_dict(Stream, Dict, []).
  986
  987json_write_dict(Stream, Dict, Options) :-
  988    make_json_write_state(Options, State, Options1),
  989    make_json_dict_options(Options1, OptionTerm, _RestOptions),
  990    json_write_term(Dict, Stream, State, OptionTerm).
  991
  992
  993make_json_dict_options(Options, Record, RestOptions) :-
  994    default_json_dict_options(Record0),
  995    set_json_options_fields(Options, Record0, Record, RestOptions).
  996
  997%!  atom_json_dict(+Atom, -JSONDict, +Options) is det.
  998%!  atom_json_dict(-Text, +JSONDict, +Options) is det.
  999%
 1000%   Convert  between  textual  representation  and    a   JSON  term
 1001%   represented as a dict. Options are as for json_read/3.
 1002%   In _write_ mode, the addtional option
 1003%
 1004%       * as(Type)
 1005%       defines the output type, which is one of =atom=,
 1006%       =string= or =codes=.
 1007
 1008atom_json_dict(Atom, Term, Options) :-
 1009    ground(Atom),
 1010    !,
 1011    setup_call_cleanup(
 1012        ( text_memfile(Atom, MF),
 1013          open_memory_file(MF, read, In, [free_on_close(true)])
 1014        ),
 1015        json_read_dict(In, Term, Options),
 1016        close(In)).
 1017atom_json_dict(Result, Term, Options) :-
 1018    select_option(as(Type), Options, Options1, atom),
 1019    (   type_term(Type, Result, Out)
 1020    ->  true
 1021    ;   must_be(oneof([atom,string,codes]), Type)
 1022    ),
 1023    with_output_to(Out,
 1024                   json_write_dict(current_output, Term, Options1)).
 1025
 1026text_memfile(Atom, MF) :-
 1027    atom(Atom),
 1028    !,
 1029    atom_to_memory_file(Atom, MF).
 1030text_memfile(String, MF) :-
 1031    string(String),
 1032    !,
 1033    new_memory_file(MF),
 1034    insert_memory_file(MF, 0, String).
 1035
 1036:- endif. 1037
 1038                 /*******************************
 1039                 *           MESSAGES           *
 1040                 *******************************/
 1041
 1042:- multifile
 1043    prolog:error_message/3. 1044
 1045prolog:error_message(syntax_error(json(Id))) -->
 1046    [ 'JSON syntax error: ' ],
 1047    json_syntax_error(Id).
 1048
 1049json_syntax_error(illegal_comment) -->
 1050    [ 'Illegal comment' ].
 1051json_syntax_error(illegal_string_escape) -->
 1052    [ 'Illegal escape sequence in string' ]