37
38:- module(json,
39 [ json_read/2, 40 json_read/3, 41 atom_json_term/3, 42 json_write/2, 43 json_write/3, 44 is_json_term/1, 45 is_json_term/2, 46 47 json_read_dict/2, 48 json_read_dict/3, 49 json_write_dict/2, 50 json_write_dict/3, 51 atom_json_dict/3 52 ]). 53:- use_module(library(record)). 54:- use_module(library(error)). 55:- use_module(library(option)). 56:- use_module(library(lists)). 57
58:- use_foreign_library(foreign(json)). 59
60:- multifile
61 json_write_hook/4, 62 json_dict_pairs/2. 63
64:- predicate_options(json_read/3, 3,
65 [ null(ground),
66 true(ground),
67 false(ground),
68 value_string_as(oneof([atom,string]))
69 ]). 70:- predicate_options(json_write/3, 3,
71 [ indent(nonneg),
72 step(positive_integer),
73 tab(positive_integer),
74 width(nonneg),
75 null(ground),
76 true(ground),
77 false(ground),
78 serialize_unknown(boolean)
79 ]). 80:- predicate_options(json_read_dict/3, 3,
81 [ tag(atom),
82 default_tag(atom),
83 pass_to(json_read/3, 3)
84 ]). 85:- predicate_options(json_write_dict/3, 3,
86 [ tag(atom),
87 pass_to(json_write/3, 3)
88 ]). 89:- predicate_options(is_json_term/2, 2,
90 [ null(ground),
91 true(ground),
92 false(ground)
93 ]). 94:- predicate_options(atom_json_term/3, 3,
95 [ as(oneof([atom,string,codes])),
96 pass_to(json_read/3, 3),
97 pass_to(json_write/3, 3)
98 ]). 99
121
122:- record json_options(
123 null:ground = @(null),
124 true:ground = @(true),
125 false:ground = @(false),
126 end_of_file:ground = error,
127 value_string_as:oneof([atom,string]) = atom,
128 tag:atom = '',
129 default_tag:atom). 130
131default_json_dict_options(
132 json_options(null, true, false, error, string, '', _)).
133
134
135 138
147
148atom_json_term(Atom, Term, Options) :-
149 ground(Atom),
150 !,
151 setup_call_cleanup(
152 open_string(Atom, In),
153 json_read(In, Term, Options),
154 close(In)).
155atom_json_term(Result, Term, Options) :-
156 select_option(as(Type), Options, Options1, atom),
157 ( type_term(Type, Result, Out)
158 -> true
159 ; must_be(oneof([atom,string,codes,chars]), Type)
160 ),
161 with_output_to(Out,
162 json_write(current_output, Term, Options1)).
163
164type_term(atom, Result, atom(Result)).
165type_term(string, Result, string(Result)).
166type_term(codes, Result, codes(Result)).
167type_term(chars, Result, chars(Result)).
168
169
170 173
246
247json_read(Stream, Term) :-
248 default_json_options(Options),
249 ( json_value_top(Stream, Term, Options)
250 -> true
251 ; syntax_error(illegal_json, Stream)
252 ).
253json_read(Stream, Term, Options) :-
254 make_json_options(Options, OptionTerm, _RestOptions),
255 ( json_value_top(Stream, Term, OptionTerm)
256 -> true
257 ; syntax_error(illegal_json, Stream)
258 ).
259
260json_value_top(Stream, Term, Options) :-
261 stream_property(Stream, type(binary)),
262 !,
263 setup_call_cleanup(
264 set_stream(Stream, encoding(utf8)),
265 json_value_top_(Stream, Term, Options),
266 set_stream(Stream, type(binary))).
267json_value_top(Stream, Term, Options) :-
268 json_value_top_(Stream, Term, Options).
269
270json_value_top_(Stream, Term, Options) :-
271 get_code(Stream, C0),
272 ws(C0, Stream, C1),
273 ( C1 == -1
274 -> json_options_end_of_file(Options, Action),
275 ( Action == error
276 -> syntax_error(unexpected_end_of_file, Stream)
277 ; Term = Action
278 )
279 ; json_term_top(C1, Stream, Term, Options)
280 ).
281
282json_value(Stream, Term, Next, Options) :-
283 get_code(Stream, C0),
284 ws(C0, Stream, C1),
285 ( C1 == -1
286 -> syntax_error(unexpected_end_of_file, Stream)
287 ; json_term(C1, Stream, Term, Next, Options)
288 ).
289
290json_term(C0, Stream, JSON, Next, Options) :-
291 json_term_top(C0, Stream, JSON, Options),
292 get_code(Stream, Next).
293
294json_term_top(0'{, Stream, json(Pairs), Options) :-
295 !,
296 ws(Stream, C),
297 json_pairs(C, Stream, Pairs, Options).
298json_term_top(0'[, Stream, Array, Options) :-
299 !,
300 ws(Stream, C),
301 json_array(C, Stream, Array, Options).
302json_term_top(0'", Stream, String, Options) :-
303 !,
304 get_code(Stream, C1),
305 json_string_codes(C1, Stream, Codes),
306 json_options_value_string_as(Options, Type),
307 codes_to_type(Type, Codes, String).
308json_term_top(0'-, Stream, Number, _Options) :-
309 !,
310 json_read_number(Stream, 0'-, Number).
311json_term_top(D, Stream, Number, _Options) :-
312 between(0'0, 0'9, D),
313 !,
314 json_read_number(Stream, D, Number).
315json_term_top(C, Stream, Constant, Options) :-
316 json_read_constant(C, Stream, ID),
317 json_constant(ID, Constant, Options).
318
319json_pairs(0'}, _, [], _) :- !.
320json_pairs(C0, Stream, [Pair|Tail], Options) :-
321 json_pair(C0, Stream, Pair, C, Options),
322 ws(C, Stream, Next),
323 ( Next == 0',
324 -> ws(Stream, C2),
325 json_pairs(C2, Stream, Tail, Options)
326 ; Next == 0'}
327 -> Tail = []
328 ; syntax_error(illegal_object, Stream)
329 ).
330
331json_pair(C0, Stream, Name=Value, Next, Options) :-
332 json_string_as_atom(C0, Stream, Name),
333 ws(Stream, C),
334 C == 0':,
335 json_value(Stream, Value, Next, Options).
336
337
338json_array(0'], _, [], _) :- !.
339json_array(C0, Stream, [Value|Tail], Options) :-
340 json_term(C0, Stream, Value, C, Options),
341 ws(C, Stream, Next),
342 ( Next == 0',
343 -> ws(Stream, C1),
344 json_array(C1, Stream, Tail, Options)
345 ; Next == 0']
346 -> Tail = []
347 ; syntax_error(illegal_array, Stream)
348 ).
349
350codes_to_type(atom, Codes, Atom) :-
351 atom_codes(Atom, Codes).
352codes_to_type(string, Codes, Atom) :-
353 string_codes(Atom, Codes).
354codes_to_type(codes, Codes, Codes).
355
356json_string_as_atom(0'", Stream, Atom) :-
357 get_code(Stream, C1),
358 json_string_codes(C1, Stream, Codes),
359 atom_codes(Atom, Codes).
360
361json_string_codes(0'", _, []) :- !.
362json_string_codes(0'\\, Stream, [H|T]) :-
363 !,
364 get_code(Stream, C0),
365 ( escape(C0, Stream, H)
366 -> true
367 ; syntax_error(illegal_string_escape, Stream)
368 ),
369 get_code(Stream, C1),
370 json_string_codes(C1, Stream, T).
371json_string_codes(-1, Stream, _) :-
372 !,
373 syntax_error(eof_in_string, Stream).
374json_string_codes(C, Stream, [C|T]) :-
375 get_code(Stream, C1),
376 json_string_codes(C1, Stream, T).
377
378escape(0'", _, 0'") :- !.
379escape(0'\\, _, 0'\\) :- !.
380escape(0'/, _, 0'/) :- !.
381escape(0'b, _, 0'\b) :- !.
382escape(0'f, _, 0'\f) :- !.
383escape(0'n, _, 0'\n) :- !.
384escape(0'r, _, 0'\r) :- !.
385escape(0't, _, 0'\t) :- !.
386escape(0'u, Stream, C) :-
387 get_XXXX(Stream, H),
388 ( hi_surrogate(H)
389 -> get_surrogate_tail(Stream, H, C)
390 ; C = H
391 ).
392
393get_XXXX(Stream, C) :-
394 get_xdigit(Stream, D1),
395 get_xdigit(Stream, D2),
396 get_xdigit(Stream, D3),
397 get_xdigit(Stream, D4),
398 C is D1<<12+D2<<8+D3<<4+D4.
399
400get_xdigit(Stream, D) :-
401 get_code(Stream, C),
402 code_type(C, xdigit(D)),
403 !.
404get_xdigit(Stream, _) :-
405 syntax_error(hexdigit_expected, Stream).
406
407get_surrogate_tail(Stream, Hi, Codepoint) :-
408 ( get_code(Stream, 0'\\),
409 get_code(Stream, 0'u),
410 get_XXXX(Stream, Lo),
411 surrogate([Hi, Lo], Codepoint)
412 -> true
413 ; syntax_error(illegal_surrogate_pair, Stream)
414 ).
415
416
417hi_surrogate(C) :-
418 C >= 0xD800, C < 0xDC00.
419
420lo_surrogate(C) :-
421 C >= 0xDC00, C < 0xE000.
422
423surrogate([Hi, Lo], Codepoint) :-
424 hi_surrogate(Hi),
425 lo_surrogate(Lo),
426 Codepoint is (Hi - 0xD800) * 0x400 + (Lo - 0xDC00) + 0x10000.
427
428json_read_constant(0't, Stream, true) :-
429 !,
430 must_see(`rue`, Stream, true).
431json_read_constant(0'f, Stream, false) :-
432 !,
433 must_see(`alse`, Stream, false).
434json_read_constant(0'n, Stream, null) :-
435 !,
436 must_see(`ull`, Stream, null).
437
438must_see([], _Stream, _).
439must_see([H|T], Stream, Name) :-
440 get_code(Stream, C),
441 ( C == H
442 -> true
443 ; syntax_error(json_expected(Name), Stream)
444 ),
445 must_see(T, Stream, Name).
446
447json_constant(true, Constant, Options) :-
448 !,
449 json_options_true(Options, Constant).
450json_constant(false, Constant, Options) :-
451 !,
452 json_options_false(Options, Constant).
453json_constant(null, Constant, Options) :-
454 !,
455 json_options_null(Options, Constant).
456
462
463ws(Stream, Next) :-
464 get_code(Stream, C0),
465 json_skip_ws(Stream, C0, Next).
466
467ws(C0, Stream, Next) :-
468 json_skip_ws(Stream, C0, Next).
469
470syntax_error(Message, Stream) :-
471 stream_error_context(Stream, Context),
472 throw(error(syntax_error(json(Message)), Context)).
473
474stream_error_context(Stream, stream(Stream, Line, LinePos, CharNo)) :-
475 stream_pair(Stream, Read, _),
476 character_count(Read, CharNo),
477 line_position(Read, LinePos),
478 line_count(Read, Line).
479
480
481 484
489
491
497
499
566
583
588
589:- record json_write_state(indent:nonneg = 0,
590 step:positive_integer = 2,
591 tab:positive_integer = 8,
592 width:nonneg = 72,
593 serialize_unknown:boolean = false
594 ). 595
596json_write(Stream, Term) :-
597 json_write(Stream, Term, []).
598json_write(Stream, Term, Options) :-
599 make_json_write_state(Options, State, Options1),
600 make_json_options(Options1, OptionTerm, _RestOptions),
601 json_write_term(Term, Stream, State, OptionTerm).
602
603json_write_term(Var, _, _, _) :-
604 var(Var),
605 !,
606 instantiation_error(Var).
607json_write_term(json(Pairs), Stream, State, Options) :-
608 !,
609 json_write_object(Pairs, Stream, State, Options).
610json_write_term(Dict, Stream, State, Options) :-
611 is_dict(Dict, Tag),
612 !,
613 json_pairs(Dict, Pairs0),
614 ( nonvar(Tag),
615 json_options_tag(Options, Name),
616 Name \== ''
617 -> Pairs = [Name-Tag|Pairs0]
618 ; Pairs = Pairs0
619 ),
620 json_write_object(Pairs, Stream, State, Options).
621json_write_term(List, Stream, State, Options) :-
622 is_list(List),
623 !,
624 space_if_not_at_left_margin(Stream, State),
625 write(Stream, '['),
626 ( json_write_state_width(State, Width),
627 ( Width == 0
628 -> true
629 ; json_write_state_indent(State, Indent),
630 json_print_length(List, Options, Width, Indent, _)
631 )
632 -> set_width_of_json_write_state(0, State, State2),
633 write_array_hor(List, Stream, State2, Options),
634 write(Stream, ']')
635 ; step_indent(State, State2),
636 write_array_ver(List, Stream, State2, Options),
637 indent(Stream, State),
638 write(Stream, ']')
639 ).
640
641json_write_term(Term, Stream, State, Options) :-
642 json_write_hook(Term, Stream, State, Options),
643 !.
644json_write_term(Number, Stream, _State, _Options) :-
645 number(Number),
646 !,
647 ( float(Number)
648 -> write(Stream, Number)
649 ; integer(Number)
650 -> write(Stream, Number)
651 ; Float is float(Number) 652 -> write(Stream, Float)
653 ).
654json_write_term(True, Stream, _State, Options) :-
655 json_options_true(Options, True),
656 !,
657 write(Stream, true).
658json_write_term(False, Stream, _State, Options) :-
659 json_options_false(Options, False),
660 !,
661 write(Stream, false).
662json_write_term(Null, Stream, _State, Options) :-
663 json_options_null(Options, Null),
664 !,
665 write(Stream, null).
666json_write_term(#(Text), Stream, _State, _Options) :-
667 !,
668 ( ( atom(Text)
669 ; string(Text)
670 )
671 -> json_write_string(Stream, Text)
672 ; term_string(Text, String),
673 json_write_string(Stream, String)
674 ).
675json_write_term(String, Stream, _State, _Options) :-
676 atom(String),
677 !,
678 json_write_string(Stream, String).
679json_write_term(String, Stream, _State, _Options) :-
680 string(String),
681 !,
682 json_write_string(Stream, String).
683json_write_term(AnyTerm, Stream, State, _Options) :-
684 ( json_write_state_serialize_unknown(State, true)
685 -> term_string(AnyTerm, String),
686 json_write_string(Stream, String)
687 ; type_error(json_term, AnyTerm)
688 ).
689
690json_pairs(Dict, Pairs) :-
691 json_dict_pairs(Dict, Pairs),
692 !.
693json_pairs(Dict, Pairs) :-
694 dict_pairs(Dict, _, Pairs).
695
696json_write_object(Pairs, Stream, State, Options) :-
697 space_if_not_at_left_margin(Stream, State),
698 write(Stream, '{'),
699 ( json_write_state_width(State, Width),
700 ( Width == 0
701 -> true
702 ; json_write_state_indent(State, Indent),
703 json_print_length(json(Pairs), Options, Width, Indent, _)
704 )
705 -> set_width_of_json_write_state(0, State, State2),
706 write_pairs_hor(Pairs, Stream, State2, Options),
707 write(Stream, '}')
708 ; step_indent(State, State2),
709 write_pairs_ver(Pairs, Stream, State2, Options),
710 indent(Stream, State),
711 write(Stream, '}')
712 ).
713
714
715write_pairs_hor([], _, _, _).
716write_pairs_hor([H|T], Stream, State, Options) :-
717 json_pair(H, Name, Value),
718 json_write_string(Stream, Name),
719 write(Stream, ':'),
720 json_write_term(Value, Stream, State, Options),
721 ( T == []
722 -> true
723 ; write(Stream, ', '),
724 write_pairs_hor(T, Stream, State, Options)
725 ).
726
727write_pairs_ver([], _, _, _).
728write_pairs_ver([H|T], Stream, State, Options) :-
729 indent(Stream, State),
730 json_pair(H, Name, Value),
731 json_write_string(Stream, Name),
732 write(Stream, ':'),
733 json_write_term(Value, Stream, State, Options),
734 ( T == []
735 -> true
736 ; write(Stream, ','),
737 write_pairs_ver(T, Stream, State, Options)
738 ).
739
740
741json_pair(Var, _, _) :-
742 var(Var),
743 !,
744 instantiation_error(Var).
745json_pair(Name=Value, Name, Value) :- !.
746json_pair(Name-Value, Name, Value) :- !.
747json_pair(NameValue, Name, Value) :-
748 compound(NameValue),
749 NameValue =.. [Name, Value],
750 !.
751json_pair(Pair, _, _) :-
752 type_error(json_pair, Pair).
753
754
755write_array_hor([], _, _, _).
756write_array_hor([H|T], Stream, State, Options) :-
757 json_write_term(H, Stream, State, Options),
758 ( T == []
759 -> write(Stream, ' ')
760 ; write(Stream, ', '),
761 write_array_hor(T, Stream, State, Options)
762 ).
763
764write_array_ver([], _, _, _).
765write_array_ver([H|T], Stream, State, Options) :-
766 indent(Stream, State),
767 json_write_term(H, Stream, State, Options),
768 ( T == []
769 -> true
770 ; write(Stream, ','),
771 write_array_ver(T, Stream, State, Options)
772 ).
773
774
775indent(Stream, State) :-
776 json_write_state_indent(State, Indent),
777 json_write_state_tab(State, Tab),
778 json_write_indent(Stream, Indent, Tab).
779
780step_indent(State0, State) :-
781 json_write_state_indent(State0, Indent),
782 json_write_state_step(State0, Step),
783 NewIndent is Indent+Step,
784 set_indent_of_json_write_state(NewIndent, State0, State).
785
786space_if_not_at_left_margin(Stream, State) :-
787 stream_pair(Stream, _, Write),
788 line_position(Write, LinePos),
789 ( LinePos == 0
790 ; json_write_state_indent(State, LinePos)
791 ),
792 !.
793space_if_not_at_left_margin(Stream, _) :-
794 put_char(Stream, ' ').
795
796
803
804json_print_length(Var, _, _, _, _) :-
805 var(Var),
806 !,
807 instantiation_error(Var).
808json_print_length(json(Pairs), Options, Max, Len0, Len) :-
809 !,
810 Len1 is Len0 + 2,
811 Len1 =< Max,
812 must_be(list, Pairs),
813 pairs_print_length(Pairs, Options, Max, Len1, Len).
814json_print_length(Dict, Options, Max, Len0, Len) :-
815 is_dict(Dict),
816 !,
817 dict_pairs(Dict, _Tag, Pairs),
818 Len1 is Len0 + 2,
819 Len1 =< Max,
820 pairs_print_length(Pairs, Options, Max, Len1, Len).
821json_print_length(Array, Options, Max, Len0, Len) :-
822 is_list(Array),
823 !,
824 Len1 is Len0 + 2,
825 Len1 =< Max,
826 array_print_length(Array, Options, Max, Len1, Len).
827json_print_length(Null, Options, Max, Len0, Len) :-
828 json_options_null(Options, Null),
829 !,
830 Len is Len0 + 4,
831 Len =< Max.
832json_print_length(False, Options, Max, Len0, Len) :-
833 json_options_false(Options, False),
834 !,
835 Len is Len0 + 5,
836 Len =< Max.
837json_print_length(True, Options, Max, Len0, Len) :-
838 json_options_true(Options, True),
839 !,
840 Len is Len0 + 4,
841 Len =< Max.
842json_print_length(Number, _Options, Max, Len0, Len) :-
843 number(Number),
844 !,
845 write_length(Number, AL, []),
846 Len is Len0 + AL,
847 Len =< Max.
848json_print_length(@(Id), _Options, Max, Len0, Len) :-
849 atom(Id),
850 !,
851 atom_length(Id, IdLen),
852 Len is Len0+IdLen,
853 Len =< Max.
854json_print_length(String, _Options, Max, Len0, Len) :-
855 string_len(String, Len0, Len),
856 !,
857 Len =< Max.
858json_print_length(AnyTerm, _Options, Max, Len0, Len) :-
859 write_length(AnyTerm, AL, []), 860 Len is Len0 + AL+2,
861 Len =< Max.
862
863pairs_print_length([], _, _, Len, Len).
864pairs_print_length([H|T], Options, Max, Len0, Len) :-
865 pair_len(H, Options, Max, Len0, Len1),
866 ( T == []
867 -> Len = Len1
868 ; Len2 is Len1 + 2,
869 Len2 =< Max,
870 pairs_print_length(T, Options, Max, Len2, Len)
871 ).
872
873pair_len(Pair, Options, Max, Len0, Len) :-
874 compound(Pair),
875 pair_nv(Pair, Name, Value),
876 !,
877 string_len(Name, Len0, Len1),
878 Len2 is Len1+2,
879 Len2 =< Max,
880 json_print_length(Value, Options, Max, Len2, Len).
881pair_len(Pair, _Options, _Max, _Len0, _Len) :-
882 type_error(pair, Pair).
883
884pair_nv(Name=Value, Name, Value) :- !.
885pair_nv(Name-Value, Name, Value) :- !.
886pair_nv(Term, Name, Value) :-
887 compound_name_arguments(Term, Name, [Value]).
888
889array_print_length([], _, _, Len, Len).
890array_print_length([H|T], Options, Max, Len0, Len) :-
891 json_print_length(H, Options, Max, Len0, Len1),
892 ( T == []
893 -> Len = Len1
894 ; Len2 is Len1+2,
895 Len2 =< Max,
896 array_print_length(T, Options, Max, Len2, Len)
897 ).
898
899string_len(String, Len0, Len) :-
900 atom(String),
901 !,
902 atom_length(String, AL),
903 Len is Len0 + AL + 2.
904string_len(String, Len0, Len) :-
905 string(String),
906 !,
907 string_length(String, AL),
908 Len is Len0 + AL + 2.
909
910
911 914
921
922is_json_term(Term) :-
923 default_json_options(Options),
924 is_json_term2(Options, Term).
925
926is_json_term(Term, Options) :-
927 make_json_options(Options, OptionTerm, _RestOptions),
928 is_json_term2(OptionTerm, Term).
929
930is_json_term2(_, Var) :-
931 var(Var), !, fail.
932is_json_term2(Options, json(Pairs)) :-
933 !,
934 is_list(Pairs),
935 maplist(is_json_pair(Options), Pairs).
936is_json_term2(Options, List) :-
937 is_list(List),
938 !,
939 maplist(is_json_term2(Options), List).
940is_json_term2(_, Primitive) :-
941 atomic(Primitive),
942 !. 943is_json_term2(Options, True) :-
944 json_options_true(Options, True).
945is_json_term2(Options, False) :-
946 json_options_false(Options, False).
947is_json_term2(Options, Null) :-
948 json_options_null(Options, Null).
949
950is_json_pair(_, Var) :-
951 var(Var), !, fail.
952is_json_pair(Options, Name=Value) :-
953 atom(Name),
954 is_json_term2(Options, Value).
955
956 959
998
999json_read_dict(Stream, Dict) :-
1000 json_read_dict(Stream, Dict, []).
1001
1002json_read_dict(Stream, Dict, Options) :-
1003 make_json_dict_options(Options, OptionTerm, _RestOptions),
1004 ( json_value_top(Stream, Term, OptionTerm)
1005 -> true
1006 ; syntax_error(illegal_json, Stream)
1007 ),
1008 term_to_dict(Term, Dict, OptionTerm).
1009
1010term_to_dict(json(Pairs), Dict, Options) :-
1011 !,
1012 ( json_options_tag(Options, TagName),
1013 Tag \== '',
1014 select(TagName = Tag0, Pairs, NVPairs),
1015 to_atom(Tag0, Tag)
1016 -> json_dict_pairs(NVPairs, DictPairs, Options)
1017 ; json_options_default_tag(Options, DefTag),
1018 ( var(DefTag)
1019 -> true
1020 ; Tag = DefTag
1021 ),
1022 json_dict_pairs(Pairs, DictPairs, Options)
1023 ),
1024 dict_create(Dict, Tag, DictPairs).
1025term_to_dict(Value0, Value, _Options) :-
1026 atomic(Value0), Value0 \== [],
1027 !,
1028 Value = Value0.
1029term_to_dict(List0, List, Options) :-
1030 is_list(List0),
1031 !,
1032 terms_to_dicts(List0, List, Options).
1033term_to_dict(Special, Special, Options) :-
1034 ( json_options_true(Options, Special)
1035 ; json_options_false(Options, Special)
1036 ; json_options_null(Options, Special)
1037 ; json_options_end_of_file(Options, Special)
1038 ),
1039 !.
1040
1041json_dict_pairs([], [], _).
1042json_dict_pairs([Name=Value0|T0], [Name=Value|T], Options) :-
1043 term_to_dict(Value0, Value, Options),
1044 json_dict_pairs(T0, T, Options).
1045
1046terms_to_dicts([], [], _).
1047terms_to_dicts([Value0|T0], [Value|T], Options) :-
1048 term_to_dict(Value0, Value, Options),
1049 terms_to_dicts(T0, T, Options).
1050
1051to_atom(Tag, Atom) :-
1052 string(Tag),
1053 !,
1054 atom_string(Atom, Tag).
1055to_atom(Atom, Atom) :-
1056 atom(Atom).
1057
1064
1065json_write_dict(Stream, Dict) :-
1066 json_write_dict(Stream, Dict, []).
1067
1068json_write_dict(Stream, Dict, Options) :-
1069 make_json_write_state(Options, State, Options1),
1070 make_json_dict_options(Options1, OptionTerm, _RestOptions),
1071 json_write_term(Dict, Stream, State, OptionTerm).
1072
1073
1074make_json_dict_options(Options, Record, RestOptions) :-
1075 default_json_dict_options(Record0),
1076 set_json_options_fields(Options, Record0, Record, RestOptions).
1077
1088
1089atom_json_dict(Atom, Term, Options) :-
1090 ground(Atom),
1091 !,
1092 setup_call_cleanup(
1093 open_string(Atom, In),
1094 json_read_dict(In, Term, Options),
1095 close(In)).
1096atom_json_dict(Result, Term, Options) :-
1097 select_option(as(Type), Options, Options1, atom),
1098 ( type_term(Type, Result, Out)
1099 -> true
1100 ; must_be(oneof([atom,string,codes]), Type)
1101 ),
1102 with_output_to(Out,
1103 json_write_dict(current_output, Term, Options1)).
1104
1105
1106 1109
1110:- multifile
1111 prolog:error_message/3. 1112
1113prolog:error_message(syntax_error(json(Id))) -->
1114 [ 'JSON syntax error: ' ],
1115 json_syntax_error(Id).
1116
1117json_syntax_error(illegal_comment) -->
1118 [ 'Illegal comment' ].
1119json_syntax_error(illegal_string_escape) -->
1120 [ 'Illegal escape sequence in string' ].
1121json_syntax_error(illegal_surrogate_pair) -->
1122 [ 'Illegal escaped surrogate pair in string' ]