Skip to content

Commit b4d5518

Browse files
thetrimeJanWielemaker
authored andcommittedApr 20, 2019
ADDED: a json:json_write_hook/4 hook to allow for end-user control over objects
1 parent 59bef95 commit b4d5518

File tree

1 file changed

+26
-0
lines changed

1 file changed

+26
-0
lines changed
 

‎json.pl

+26
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,9 @@
7474

7575
:- use_foreign_library(foreign(json)).
7676

77+
:- multifile
78+
json_write_hook/4. % +Term, +Stream, +State, +Options
79+
7780
:- predicate_options(json_read/3, 3,
7881
[ null(ground),
7982
true(ground),
@@ -535,6 +538,25 @@
535538
% objects can be safely embedded into an HTML =|<script>|=
536539
% element.
537540

541+
%! json_write_hook(+Term, +Stream, +State, +Options) is semidet.
542+
%
543+
% Hook that can be used to emit a JSON representation for Term to
544+
% Stream. If the predicate succeeds it __must__ have written a
545+
% __valid__ JSON data element and if it fails it may not have produced
546+
% any output. This facility may be used to map arbitrary Prolog terms
547+
% to JSON. It was added to manage the precision with which floating
548+
% point numbers are emitted.
549+
%
550+
% Note that this hook is shared by all users of this library. It is
551+
% generally adviced to map a unique compound term to avoid
552+
% interference with normal output.
553+
%
554+
% @arg State and Options are opaque handles to the current output
555+
% state and settings. Future versions may provide documented access
556+
% to these terms. Currently it is adviced to ignore these arguments.
557+
558+
559+
538560
:- record json_write_state(indent:nonneg = 0,
539561
step:positive_integer = 2,
540562
tab:positive_integer = 8,
@@ -588,6 +610,10 @@
588610
indent(Stream, State),
589611
write(Stream, ']')
590612
).
613+
614+
json_write_term(Term, Stream, State, Options) :-
615+
json_write_hook(Term, Stream, State, Options),
616+
!.
591617
json_write_term(Number, Stream, _State, _Options) :-
592618
number(Number),
593619
!,

0 commit comments

Comments
 (0)
Please sign in to comment.