36
   37:- if(current_predicate(is_dict/1)).   38
   39:- module(json,
   40          [ json_read/2,                   41            json_read/3,                   42            atom_json_term/3,              43            json_write/2,                  44            json_write/3,                  45            is_json_term/1,                46            is_json_term/2,                47                                           48            json_read_dict/2,              49            json_read_dict/3,              50            json_write_dict/2,             51            json_write_dict/3,             52            atom_json_dict/3               53          ]).   54
   55:- else.   56
   57:- module(json,
   58          [ json_read/2,                   59            json_read/3,                   60            atom_json_term/3,              61            json_write/2,                  62            json_write/3,                  63            is_json_term/1,                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                     ]).  112
  134
  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                   151
  160
  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                   188
  261
  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).
  431
  437
  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                   459
  464
  466
  472
  474
  537
  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, ' ').
  730
  731
  738
  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, []),            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                   851
  858
  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    !.             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                   898
  935
  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).
  994
 1001
 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).
 1014
 1025
 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                  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' ]