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)  2014-2023, VU University Amsterdam
    7                              CWI, Amsterdam
    8                              SWI-Prolog Solutions b.v.
    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:- module(pengines_io,
   38          [ pengine_writeln/1,          % +Term
   39            pengine_nl/0,
   40            pengine_tab/1,
   41            pengine_flush_output/0,
   42            pengine_format/1,           % +Format
   43            pengine_format/2,           % +Format, +Args
   44
   45            pengine_write_term/2,       % +Term, +Options
   46            pengine_write/1,            % +Term
   47            pengine_writeq/1,           % +Term
   48            pengine_display/1,          % +Term
   49            pengine_print/1,            % +Term
   50            pengine_write_canonical/1,  % +Term
   51
   52            pengine_listing/0,
   53            pengine_listing/1,          % +Spec
   54            pengine_portray_clause/1,   % +Term
   55
   56            pengine_read/1,             % -Term
   57            pengine_read_line_to_string/2, % +Stream, -LineAsString
   58            pengine_read_line_to_codes/2, % +Stream, -LineAsCodes
   59
   60            pengine_io_predicate/1,     % ?Head
   61            pengine_bind_io_to_html/1,  % +Module
   62            pengine_io_goal_expansion/2,% +Goal, -Expanded
   63
   64            message_lines_to_html/3     % +Lines, +Classes, -HTML
   65          ]).   66:- autoload(library(apply),[foldl/4,maplist/3,maplist/4]).   67:- autoload(library(backcomp),[thread_at_exit/1]).   68:- use_module(library(debug),[assertion/1]).   69:- autoload(library(error),[must_be/2]).   70:- autoload(library(listing),[listing/1,portray_clause/1]).   71:- autoload(library(lists),[append/2,append/3,subtract/3]).   72:- autoload(library(option),[option/3,merge_options/3]).   73:- autoload(library(pengines),
   74	    [ pengine_self/1,
   75	      pengine_output/1,
   76	      pengine_input/2,
   77	      pengine_property/2
   78	    ]).   79:- autoload(library(prolog_stream),[open_prolog_stream/4]).   80:- autoload(library(readutil),[read_line_to_string/2]).   81:- autoload(library(http/term_html),[term/4]).   82
   83:- use_module(library(yall),[(>>)/4]).   84:- use_module(library(http/html_write),[html/3,print_html/1, op(_,_,_)]).   85:- use_module(library(settings),[setting/4,setting/2]).   86
   87:- use_module(library(sandbox), []).   88:- autoload(library(thread), [call_in_thread/2]).   89
   90:- html_meta send_html(html).   91:- public send_html/1.   92
   93:- meta_predicate
   94    pengine_format(+,:).   95
   96/** <module> Provide Prolog I/O for HTML clients
   97
   98This module redefines some of  the   standard  Prolog  I/O predicates to
   99behave transparently for HTML clients. It  provides two ways to redefine
  100the standard predicates: using goal_expansion/2   and  by redefining the
  101system predicates using redefine_system_predicate/1. The   latter is the
  102preferred route because it gives a more   predictable  trace to the user
  103and works regardless of the use of other expansion and meta-calling.
  104
  105*Redefining* works by redefining the system predicates in the context of
  106the pengine's module. This  is  configured   using  the  following  code
  107snippet.
  108
  109  ==
  110  :- pengine_application(myapp).
  111  :- use_module(myapp:library(pengines_io)).
  112  pengines:prepare_module(Module, myapp, _Options) :-
  113        pengines_io:pengine_bind_io_to_html(Module).
  114  ==
  115
  116*Using goal_expansion/2* works by  rewriting   the  corresponding  goals
  117using goal_expansion/2 and use the new   definition  to re-route I/O via
  118pengine_input/2 and pengine_output/1. A pengine  application is prepared
  119for using this module with the following code:
  120
  121  ==
  122  :- pengine_application(myapp).
  123  :- use_module(myapp:library(pengines_io)).
  124  myapp:goal_expansion(In,Out) :-
  125        pengine_io_goal_expansion(In, Out).
  126  ==
  127*/
  128
  129:- setting(write_options, list(any), [max_depth(1000)],
  130           'Additional options for stringifying Prolog results').  131
  132
  133                 /*******************************
  134                 *            OUTPUT            *
  135                 *******************************/
  136
  137%!  pengine_writeln(+Term)
  138%
  139%   Emit Term as <span class=writeln>Term<br></span>.
  140
  141pengine_writeln(Term) :-
  142    pengine_output,
  143    !,
  144    pengine_module(Module),
  145    send_html(span(class(writeln),
  146                   [ \term(Term,
  147                           [ module(Module)
  148                           ]),
  149                     br([])
  150                   ])).
  151pengine_writeln(Term) :-
  152    writeln(Term).
  153
  154%!  pengine_nl
  155%
  156%   Emit a <br/> to the pengine.
  157
  158pengine_nl :-
  159    pengine_output,
  160    !,
  161    send_html(br([])).
  162pengine_nl :-
  163    nl.
  164
  165%!  pengine_tab(+N)
  166%
  167%   Emit N spaces
  168
  169pengine_tab(Expr) :-
  170    pengine_output,
  171    !,
  172    N is Expr,
  173    length(List, N),
  174    maplist(=(&(nbsp)), List),
  175    send_html(List).
  176pengine_tab(N) :-
  177    tab(N).
  178
  179
  180%!  pengine_flush_output
  181%
  182%   No-op.  Pengines do not use output buffering (maybe they should
  183%   though).
  184
  185pengine_flush_output :-
  186    pengine_output,
  187    !.
  188pengine_flush_output :-
  189    flush_output.
  190
  191%!  pengine_write_term(+Term, +Options)
  192%
  193%   Writes term as <span class=Class>Term</span>. In addition to the
  194%   options of write_term/2, these options are processed:
  195%
  196%     - class(+Class)
  197%       Specifies the class of the element.  Default is =write=.
  198
  199pengine_write_term(Term, Options) :-
  200    pengine_output,
  201    !,
  202    option(class(Class), Options, write),
  203    pengine_module(Module),
  204    send_html(span(class(Class), \term(Term,[module(Module)|Options]))).
  205pengine_write_term(Term, Options) :-
  206    write_term(Term, Options).
  207
  208%!  pengine_write(+Term) is det.
  209%!  pengine_writeq(+Term) is det.
  210%!  pengine_display(+Term) is det.
  211%!  pengine_print(+Term) is det.
  212%!  pengine_write_canonical(+Term) is det.
  213%
  214%   Redirect the corresponding Prolog output predicates.
  215
  216pengine_write(Term) :-
  217    pengine_write_term(Term, [numbervars(true)]).
  218pengine_writeq(Term) :-
  219    pengine_write_term(Term, [quoted(true), numbervars(true)]).
  220pengine_display(Term) :-
  221    pengine_write_term(Term, [quoted(true), ignore_ops(true)]).
  222pengine_print(Term) :-
  223    current_prolog_flag(print_write_options, Options),
  224    pengine_write_term(Term, Options).
  225pengine_write_canonical(Term) :-
  226    pengine_output,
  227    !,
  228    with_output_to(string(String), write_canonical(Term)),
  229    send_html(span(class([write, cononical]), String)).
  230pengine_write_canonical(Term) :-
  231    write_canonical(Term).
  232
  233%!  pengine_format(+Format) is det.
  234%!  pengine_format(+Format, +Args) is det.
  235%
  236%   As format/1,2. Emits a series  of   strings  with <br/> for each
  237%   newline encountered in the string.
  238%
  239%   @tbd: handle ~w, ~q, etc using term//2.  How can we do that??
  240
  241pengine_format(Format) :-
  242    pengine_format(Format, []).
  243pengine_format(Format, Args) :-
  244    pengine_output,
  245    !,
  246    format(string(String), Format, Args),
  247    split_string(String, "\n", "", Lines),
  248    send_html(\lines(Lines, format)).
  249pengine_format(Format, Args) :-
  250    format(Format, Args).
  251
  252
  253                 /*******************************
  254                 *            LISTING           *
  255                 *******************************/
  256
  257%!  pengine_listing is det.
  258%!  pengine_listing(+Spec) is det.
  259%
  260%   List the content of the current pengine or a specified predicate
  261%   in the pengine.
  262
  263pengine_listing :-
  264    pengine_listing(_).
  265
  266pengine_listing(Spec) :-
  267    pengine_self(Module),
  268    with_output_to(string(String), listing(Module:Spec)),
  269    split_string(String, "", "\n", [Pre]),
  270    send_html(pre(class(listing), Pre)).
  271
  272pengine_portray_clause(Term) :-
  273    pengine_output,
  274    !,
  275    with_output_to(string(String), portray_clause(Term)),
  276    split_string(String, "", "\n", [Pre]),
  277    send_html(pre(class(listing), Pre)).
  278pengine_portray_clause(Term) :-
  279    portray_clause(Term).
  280
  281
  282                 /*******************************
  283                 *         PRINT MESSAGE        *
  284                 *******************************/
  285
  286:- multifile user:message_hook/3.  287
  288%!  user:message_hook(+Term, +Kind, +Lines) is semidet.
  289%
  290%   Send output from print_message/2 to   the  pengine. Messages are
  291%   embedded in a <pre class=msg-Kind></pre> environment.
  292
  293user:message_hook(Term, Kind, Lines) :-
  294    Kind \== silent,
  295    pengine_self(_),
  296    atom_concat('msg-', Kind, Class),
  297    message_lines_to_html(Lines, [Class], HTMlString),
  298    (   source_location(File, Line)
  299    ->  Src = File:Line
  300    ;   Src = (-)
  301    ),
  302    pengine_output(message(Term, Kind, HTMlString, Src)).
  303
  304%!  message_lines_to_html(+MessageLines, +Classes, -HTMLString) is det.
  305%
  306%   Helper that translates the `Lines` argument from user:message_hook/3
  307%   into an HTML string. The  HTML  is   a  <pre>  object with the class
  308%   `'prolog-message'` and the given Classes.
  309
  310message_lines_to_html(Lines, Classes, HTMlString) :-
  311    phrase(html(pre(class(['prolog-message'|Classes]),
  312                    \message_lines(Lines))), Tokens),
  313    with_output_to(string(HTMlString), print_html(Tokens)).
  314
  315message_lines([]) -->
  316    !.
  317message_lines([nl|T]) -->
  318    !,
  319    html('\n'),                     % we are in a <pre> environment
  320    message_lines(T).
  321message_lines([flush]) -->
  322    !.
  323message_lines([ansi(Attributes, Fmt, Args)|T]) -->
  324    !,
  325    {  is_list(Attributes)
  326    -> foldl(style, Attributes, Fmt-Args, HTML)
  327    ;  style(Attributes, Fmt-Args, HTML)
  328    },
  329    html(HTML),
  330    message_lines(T).
  331message_lines([url(Pos)|T]) -->
  332    !,
  333    location(Pos),
  334    message_lines(T).
  335message_lines([url(HREF, Label)|T]) -->
  336    !,
  337    html(a(href(HREF),Label)),
  338    message_lines(T).
  339message_lines([H|T]) -->
  340    html(H),
  341    message_lines(T).
  342
  343location(File:Line:Column) -->
  344    !,
  345    html([File, :, Line, :, Column]).
  346location(File:Line) -->
  347    !,
  348    html([File, :, Line]).
  349location(File) -->
  350    html([File]).
  351
  352style(bold, Content, b(Content)) :- !.
  353style(fg(default), Content, span(style('color: black'), Content)) :- !.
  354style(fg(Color), Content, span(style('color:'+Color), Content)) :- !.
  355style(_, Content, Content).
  356
  357
  358                 /*******************************
  359                 *             INPUT            *
  360                 *******************************/
  361
  362pengine_read(Term) :-
  363    pengine_input,
  364    !,
  365    prompt(Prompt, Prompt),
  366    pengine_input(Prompt, Term).
  367pengine_read(Term) :-
  368    read(Term).
  369
  370pengine_read_line_to_string(From, String) :-
  371    pengine_input,
  372    !,
  373    must_be(oneof([current_input,user_input]), From),
  374    (   prompt(Prompt, Prompt),
  375        Prompt \== ''
  376    ->  true
  377    ;   Prompt = 'line> '
  378    ),
  379    pengine_input(_{type: console, prompt:Prompt}, StringNL),
  380    string_concat(String, "\n", StringNL).
  381pengine_read_line_to_string(From, String) :-
  382    read_line_to_string(From, String).
  383
  384pengine_read_line_to_codes(From, Codes) :-
  385    pengine_read_line_to_string(From, String),
  386    string_codes(String, Codes).
  387
  388
  389                 /*******************************
  390                 *             HTML             *
  391                 *******************************/
  392
  393lines([], _) --> [].
  394lines([H|T], Class) -->
  395    html(span(class(Class), H)),
  396    (   { T == [] }
  397    ->  []
  398    ;   html(br([])),
  399        lines(T, Class)
  400    ).
  401
  402%!  send_html(+HTML) is det.
  403%
  404%   Convert html//1 term into a string and send it to the client
  405%   using pengine_output/1.
  406
  407send_html(HTML) :-
  408    phrase(html(HTML), Tokens),
  409    with_output_to(string(HTMlString), print_html(Tokens)),
  410    pengine_output(HTMlString).
  411
  412
  413%!  pengine_module(-Module) is det.
  414%
  415%   Module (used for resolving operators).
  416
  417pengine_module(Module) :-
  418    pengine_self(Pengine),
  419    !,
  420    pengine_property(Pengine, module(Module)).
  421pengine_module(user).
  422
  423                 /*******************************
  424                 *        OUTPUT FORMAT         *
  425                 *******************************/
  426
  427%!  pengines:event_to_json(+Event, -JSON, +Format, +VarNames) is semidet.
  428%
  429%   Provide additional translations for  Prolog   terms  to  output.
  430%   Defines formats are:
  431%
  432%     * 'json-s'
  433%     _Simple_ or _string_ format: Prolog terms are sent using
  434%     quoted write.
  435%     * 'json-html'
  436%     Serialize responses as HTML string.  This is intended for
  437%     applications that emulate the Prolog toplevel.  This format
  438%     carries the following data:
  439%
  440%       - data
  441%         List if answers, where each answer is an object with
  442%         - variables
  443%           Array of objects, each describing a variable.  These
  444%           objects contain these fields:
  445%           - variables: Array of strings holding variable names
  446%           - value: HTML-ified value of the variables
  447%           - substitutions: Array of objects for substitutions
  448%             that break cycles holding:
  449%             - var: Name of the inserted variable
  450%             - value: HTML-ified value
  451%         - residuals
  452%           Array of strings representing HTML-ified residual goals.
  453
  454:- multifile
  455    pengines:event_to_json/3.  456
  457%!  pengines:event_to_json(+PrologEvent, -JSONEvent, +Format, +VarNames)
  458%
  459%   If Format equals `'json-s'` or  `'json-html'`, emit a simplified
  460%   JSON representation of the  data,   suitable  for notably SWISH.
  461%   This deals with Prolog answers and output messages. If a message
  462%   originates from print_message/3,  it   gets  several  additional
  463%   properties:
  464%
  465%     - message:Kind
  466%       Indicate the _kind_ of the message (=error=, =warning=,
  467%       etc.)
  468%     - location:_{file:File, line:Line, ch:CharPos}
  469%       If the message is related to a source location, indicate the
  470%       file and line and, if available, the character location.
  471
  472pengines:event_to_json(success(ID, Answers0, Projection, Time, More), JSON,
  473                       'json-s') :-
  474    !,
  475    JSON0 = json{event:success, id:ID, time:Time, data:Answers, more:More},
  476    maplist(answer_to_json_strings(ID), Answers0, Answers),
  477    add_projection(Projection, JSON0, JSON).
  478pengines:event_to_json(output(ID, Term), JSON, 'json-s') :-
  479    !,
  480    map_output(ID, Term, JSON).
  481
  482add_projection([], JSON, JSON) :- !.
  483add_projection(VarNames, JSON0, JSON0.put(projection, VarNames)).
  484
  485
  486%!  answer_to_json_strings(+Pengine, +AnswerDictIn, -AnswerDict).
  487%
  488%   Translate answer dict with Prolog term   values into answer dict
  489%   with string values.
  490
  491answer_to_json_strings(Pengine, DictIn, DictOut) :-
  492    dict_pairs(DictIn, Tag, Pairs),
  493    maplist(term_string_value(Pengine), Pairs, BindingsOut),
  494    dict_pairs(DictOut, Tag, BindingsOut).
  495
  496term_string_value(Pengine, N-V, N-A) :-
  497    with_output_to(string(A),
  498                   write_term(V,
  499                              [ module(Pengine),
  500                                quoted(true)
  501                              ])).
  502
  503%!  pengines:event_to_json(+Event, -JSON, +Format, +VarNames)
  504%
  505%   Implement translation of a Pengine event to =json-html= format. This
  506%   format represents the answer as JSON,  but the variable bindings are
  507%   (structured) HTML strings rather than JSON objects.
  508%
  509%   CHR residual goals are not  bound   to  the projection variables. We
  510%   hacked a bypass to fetch these by returning them in a variable named
  511%   `_residuals`, which must be bound to a term '$residuals'(List). Such
  512%   a variable is removed from  the   projection  and  added to residual
  513%   goals.
  514
  515pengines:event_to_json(success(ID, Answers0, Projection, Time, More),
  516                       JSON, 'json-html') :-
  517    !,
  518    JSON0 = json{event:success, id:ID, time:Time, data:Answers, more:More},
  519    maplist(map_answer(ID), Answers0, ResVars, Answers),
  520    add_projection(Projection, ResVars, JSON0, JSON).
  521pengines:event_to_json(output(ID, Term), JSON, 'json-html') :-
  522    !,
  523    map_output(ID, Term, JSON).
  524
  525map_answer(ID, Bindings0, ResVars, Answer) :-
  526    dict_bindings(Bindings0, Bindings1),
  527    select_residuals(Bindings1, Bindings2, ResVars, Residuals0, Clauses),
  528    append(Residuals0, Residuals1),
  529    prolog:translate_bindings(Bindings2, Bindings3, [], Residuals1,
  530                              ID:Residuals-_HiddenResiduals),
  531    maplist(binding_to_html(ID), Bindings3, VarBindings),
  532    final_answer(ID, VarBindings, Residuals, Clauses, Answer).
  533
  534final_answer(_Id, VarBindings, [], [], Answer) :-
  535    !,
  536    Answer = json{variables:VarBindings}.
  537final_answer(ID, VarBindings, Residuals, [], Answer) :-
  538    !,
  539    residuals_html(Residuals, ID, ResHTML),
  540    Answer = json{variables:VarBindings, residuals:ResHTML}.
  541final_answer(ID, VarBindings, [], Clauses, Answer) :-
  542    !,
  543    clauses_html(Clauses, ID, ClausesHTML),
  544    Answer = json{variables:VarBindings, wfs_residual_program:ClausesHTML}.
  545final_answer(ID, VarBindings, Residuals, Clauses, Answer) :-
  546    !,
  547    residuals_html(Residuals, ID, ResHTML),
  548    clauses_html(Clauses, ID, ClausesHTML),
  549    Answer = json{variables:VarBindings,
  550                  residuals:ResHTML,
  551                  wfs_residual_program:ClausesHTML}.
  552
  553residuals_html([], _, []).
  554residuals_html([H0|T0], Module, [H|T]) :-
  555    term_html_string(H0, [], Module, H, [priority(999)]),
  556    residuals_html(T0, Module, T).
  557
  558clauses_html(Clauses, _ID, HTMLString) :-
  559    with_output_to(string(Program), list_clauses(Clauses)),
  560    phrase(html(pre([class('wfs-residual-program')], Program)), Tokens),
  561    with_output_to(string(HTMLString), print_html(Tokens)).
  562
  563list_clauses([]).
  564list_clauses([H|T]) :-
  565    (   system_undefined(H)
  566    ->  true
  567    ;   portray_clause(H)
  568    ),
  569    list_clauses(T).
  570
  571system_undefined((undefined :- tnot(undefined))).
  572system_undefined((answer_count_restraint :- tnot(answer_count_restraint))).
  573system_undefined((radial_restraint :- tnot(radial_restraint))).
  574
  575dict_bindings(Dict, Bindings) :-
  576    dict_pairs(Dict, _Tag, Pairs),
  577    maplist([N-V,N=V]>>true, Pairs, Bindings).
  578
  579select_residuals([], [], [], [], []).
  580select_residuals([H|T], Bindings, Vars, Residuals, Clauses) :-
  581    binding_residual(H, Var, Residual),
  582    !,
  583    Vars = [Var|TV],
  584    Residuals = [Residual|TR],
  585    select_residuals(T, Bindings, TV, TR, Clauses).
  586select_residuals([H|T], Bindings, Vars, Residuals, Clauses) :-
  587    binding_residual_clauses(H, Var, Delays, Clauses0),
  588    !,
  589    Vars = [Var|TV],
  590    Residuals = [Delays|TR],
  591    append(Clauses0, CT, Clauses),
  592    select_residuals(T, Bindings, TV, TR, CT).
  593select_residuals([H|T0], [H|T], Vars, Residuals, Clauses) :-
  594    select_residuals(T0, T, Vars, Residuals, Clauses).
  595
  596binding_residual('_residuals' = '$residuals'(Residuals), '_residuals', Residuals) :-
  597    is_list(Residuals).
  598binding_residual('Residuals' = '$residuals'(Residuals), 'Residuals', Residuals) :-
  599    is_list(Residuals).
  600binding_residual('Residual'  = '$residual'(Residual),   'Residual', [Residual]) :-
  601    callable(Residual).
  602
  603binding_residual_clauses(
  604    '_wfs_residual_program' = '$wfs_residual_program'(Delays, Clauses),
  605    '_wfs_residual_program', Residuals, Clauses) :-
  606    phrase(delay_list(Delays), Residuals).
  607
  608delay_list(true) --> !.
  609delay_list((A,B)) --> !, delay_list(A), delay_list(B).
  610delay_list(M:A) --> !, [M:'$wfs_undefined'(A)].
  611delay_list(A) --> ['$wfs_undefined'(A)].
  612
  613add_projection(-, _, JSON, JSON) :- !.
  614add_projection(VarNames0, ResVars0, JSON0, JSON) :-
  615    append(ResVars0, ResVars1),
  616    sort(ResVars1, ResVars),
  617    subtract(VarNames0, ResVars, VarNames),
  618    add_projection(VarNames, JSON0, JSON).
  619
  620
  621%!  binding_to_html(+Pengine, +Binding, -Dict) is det.
  622%
  623%   Convert a variable binding into a JSON Dict. Note that this code
  624%   assumes that the module associated  with   Pengine  has the same
  625%   name as the Pengine.  The module is needed to
  626%
  627%   @arg Binding is a term binding(Vars,Term,Substitutions)
  628
  629binding_to_html(ID, binding(Vars,Term,Substitutions), JSON) :-
  630    JSON0 = json{variables:Vars, value:HTMLString},
  631    binding_write_options(ID, Options),
  632    term_html_string(Term, Vars, ID, HTMLString, Options),
  633    (   Substitutions == []
  634    ->  JSON = JSON0
  635    ;   maplist(subst_to_html(ID), Substitutions, HTMLSubst),
  636        JSON = JSON0.put(substitutions, HTMLSubst)
  637    ).
  638
  639binding_write_options(Pengine, Options) :-
  640    (   current_predicate(Pengine:screen_property/1),
  641        Pengine:screen_property(tabled(true))
  642    ->  Options = []
  643    ;   Options = [priority(699)]
  644    ).
  645
  646%!  term_html_string(+Term, +VarNames, +Module, -HTMLString,
  647%!                   +Options) is det.
  648%
  649%   Translate  Term  into  an  HTML    string   using  the  operator
  650%   declarations from Module. VarNames is a   list of variable names
  651%   that have this value.
  652
  653term_html_string(Term, Vars, Module, HTMLString, Options) :-
  654    setting(write_options, WOptions),
  655    merge_options(WOptions,
  656                  [ quoted(true),
  657                    numbervars(true),
  658                    module(Module)
  659                  | Options
  660                  ], WriteOptions),
  661    phrase(term_html(Term, Vars, WriteOptions), Tokens),
  662    with_output_to(string(HTMLString), print_html(Tokens)).
  663
  664%!  binding_term(+Term, +Vars, +WriteOptions)// is semidet.
  665%
  666%   Hook to render a Prolog result term as HTML. This hook is called
  667%   for each non-variable binding,  passing   the  binding  value as
  668%   Term, the names of the variables as   Vars and a list of options
  669%   for write_term/3.  If the hook fails, term//2 is called.
  670%
  671%   @arg    Vars is a list of variable names or `[]` if Term is a
  672%           _residual goal_.
  673
  674:- multifile binding_term//3.  675
  676term_html(Term, Vars, WriteOptions) -->
  677    { nonvar(Term) },
  678    binding_term(Term, Vars, WriteOptions),
  679    !.
  680term_html(Undef, _Vars, WriteOptions) -->
  681    { nonvar(Undef),
  682      Undef = '$wfs_undefined'(Term),
  683      !
  684    },
  685    html(span(class(wfs_undefined), \term(Term, WriteOptions))).
  686term_html(Term, _Vars, WriteOptions) -->
  687    term(Term, WriteOptions).
  688
  689%!  subst_to_html(+Module, +Binding, -JSON) is det.
  690%
  691%   Render   a   variable   substitution     resulting   from   term
  692%   factorization, in this case breaking a cycle.
  693
  694subst_to_html(ID, '$VAR'(Name)=Value, json{var:Name, value:HTMLString}) :-
  695    !,
  696    binding_write_options(ID, Options),
  697    term_html_string(Value, [Name], ID, HTMLString, Options).
  698subst_to_html(_, Term, _) :-
  699    assertion(Term = '$VAR'(_)).
  700
  701
  702%!  map_output(+ID, +Term, -JSON) is det.
  703%
  704%   Map an output term. This is the same for json-s and json-html.
  705
  706map_output(ID, message(Term, Kind, HTMLString, Src), JSON) :-
  707    atomic(HTMLString),
  708    !,
  709    JSON0 = json{event:output, id:ID, message:Kind, data:HTMLString},
  710    pengines:add_error_details(Term, JSON0, JSON1),
  711    (   Src = File:Line,
  712        \+ JSON1.get(location) = _
  713    ->  JSON = JSON1.put(_{location:_{file:File, line:Line}})
  714    ;   JSON = JSON1
  715    ).
  716map_output(ID, Term, json{event:output, id:ID, data:Data}) :-
  717    (   atomic(Term)
  718    ->  Data = Term
  719    ;   is_dict(Term, json),
  720        ground(json)                % TBD: Check proper JSON object?
  721    ->  Data = Term
  722    ;   term_string(Term, Data)
  723    ).
  724
  725
  726%!  prolog_help:show_html_hook(+HTML)
  727%
  728%   Hook into help/1 to render the help output in the SWISH console.
  729
  730:- multifile
  731    prolog_help:show_html_hook/1.  732
  733prolog_help:show_html_hook(HTML) :-
  734    pengine_output,
  735    pengine_output(HTML).
  736
  737
  738                 /*******************************
  739                 *          SANDBOXING          *
  740                 *******************************/
  741
  742:- multifile
  743    sandbox:safe_primitive/1,       % Goal
  744    sandbox:safe_meta/2.            % Goal, Called
  745
  746sandbox:safe_primitive(pengines_io:pengine_listing(_)).
  747sandbox:safe_primitive(pengines_io:pengine_nl).
  748sandbox:safe_primitive(pengines_io:pengine_tab(_)).
  749sandbox:safe_primitive(pengines_io:pengine_flush_output).
  750sandbox:safe_primitive(pengines_io:pengine_print(_)).
  751sandbox:safe_primitive(pengines_io:pengine_write(_)).
  752sandbox:safe_primitive(pengines_io:pengine_read(_)).
  753sandbox:safe_primitive(pengines_io:pengine_read_line_to_string(_,_)).
  754sandbox:safe_primitive(pengines_io:pengine_read_line_to_codes(_,_)).
  755sandbox:safe_primitive(pengines_io:pengine_write_canonical(_)).
  756sandbox:safe_primitive(pengines_io:pengine_write_term(_,_)).
  757sandbox:safe_primitive(pengines_io:pengine_writeln(_)).
  758sandbox:safe_primitive(pengines_io:pengine_writeq(_)).
  759sandbox:safe_primitive(pengines_io:pengine_portray_clause(_)).
  760sandbox:safe_primitive(system:write_term(_,_)).
  761sandbox:safe_primitive(system:prompt(_,_)).
  762sandbox:safe_primitive(system:statistics(_,_)).
  763
  764sandbox:safe_meta(pengines_io:pengine_format(Format, Args), Calls) :-
  765    sandbox:format_calls(Format, Args, Calls).
  766
  767
  768                 /*******************************
  769                 *         REDEFINITION         *
  770                 *******************************/
  771
  772%!  pengine_io_predicate(?Head)
  773%
  774%   True when Head describes the  head   of  a (system) IO predicate
  775%   that is redefined by the HTML binding.
  776
  777pengine_io_predicate(writeln(_)).
  778pengine_io_predicate(nl).
  779pengine_io_predicate(tab(_)).
  780pengine_io_predicate(flush_output).
  781pengine_io_predicate(format(_)).
  782pengine_io_predicate(format(_,_)).
  783pengine_io_predicate(read(_)).
  784pengine_io_predicate(read_line_to_string(_,_)).
  785pengine_io_predicate(read_line_to_codes(_,_)).
  786pengine_io_predicate(write_term(_,_)).
  787pengine_io_predicate(write(_)).
  788pengine_io_predicate(writeq(_)).
  789pengine_io_predicate(display(_)).
  790pengine_io_predicate(print(_)).
  791pengine_io_predicate(write_canonical(_)).
  792pengine_io_predicate(listing).
  793pengine_io_predicate(listing(_)).
  794pengine_io_predicate(portray_clause(_)).
  795
  796term_expansion(pengine_io_goal_expansion(_,_),
  797               Clauses) :-
  798    findall(Clause, io_mapping(Clause), Clauses).
  799
  800io_mapping(pengine_io_goal_expansion(Head, Mapped)) :-
  801    pengine_io_predicate(Head),
  802    Head =.. [Name|Args],
  803    atom_concat(pengine_, Name, BodyName),
  804    Mapped =.. [BodyName|Args].
  805
  806pengine_io_goal_expansion(_, _).
  807
  808
  809                 /*******************************
  810                 *      REBIND PENGINE I/O      *
  811                 *******************************/
  812
  813:- public
  814    stream_write/2,
  815    stream_read/2,
  816    stream_close/1.  817
  818:- thread_local
  819    pengine_io/2.  820
  821stream_write(Stream, Out) :-
  822    (   pengine_io(_,_)
  823    ->  send_html(pre(class(console), Out))
  824    ;   current_prolog_flag(pengine_main_thread, TID),
  825        thread_signal(TID, stream_write(Stream, Out))
  826    ).
  827stream_read(Stream, Data) :-
  828    (   pengine_io(_,_)
  829    ->  prompt(Prompt, Prompt),
  830        pengine_input(_{type:console, prompt:Prompt}, Data)
  831    ;   current_prolog_flag(pengine_main_thread, TID),
  832        call_in_thread(TID, stream_read(Stream, Data))
  833    ).
  834stream_close(_Stream).
  835
  836%!  pengine_bind_user_streams
  837%
  838%   Bind the pengine user  I/O  streams   to  a  Prolog  stream that
  839%   redirects  the  input  and   output    to   pengine_input/2  and
  840%   pengine_output/1. This results in  less   pretty  behaviour then
  841%   redefining the I/O predicates to  produce   nice  HTML, but does
  842%   provide functioning I/O from included libraries.
  843
  844pengine_bind_user_streams :-
  845    Err = Out,
  846    open_prolog_stream(pengines_io, write, Out, []),
  847    set_stream(Out, buffer(line)),
  848    open_prolog_stream(pengines_io, read,  In, []),
  849    set_stream(In,  alias(user_input)),
  850    set_stream(Out, alias(user_output)),
  851    set_stream(Err, alias(user_error)),
  852    set_stream(In,  alias(current_input)),
  853    set_stream(Out, alias(current_output)),
  854    assertz(pengine_io(In, Out)),
  855    thread_self(Me),
  856    thread_property(Me, id(Id)),
  857    set_prolog_flag(pengine_main_thread, Id),
  858    thread_at_exit(close_io).
  859
  860close_io :-
  861    retract(pengine_io(In, Out)),
  862    !,
  863    close(In, [force(true)]),
  864    close(Out, [force(true)]).
  865close_io.
  866
  867%!  pengine_output is semidet.
  868%!  pengine_input is semidet.
  869%
  870%   True when output (input) is redirected to a pengine.
  871
  872pengine_output :-
  873    current_output(Out),
  874    pengine_io(_, Out).
  875
  876pengine_input :-
  877    current_input(In),
  878    pengine_io(In, _).
  879
  880
  881%!  pengine_bind_io_to_html(+Module)
  882%
  883%   Redefine the built-in predicates for IO   to  send HTML messages
  884%   using pengine_output/1.
  885
  886pengine_bind_io_to_html(Module) :-
  887    forall(pengine_io_predicate(Head),
  888           bind_io(Head, Module)),
  889    pengine_bind_user_streams.
  890
  891bind_io(Head, Module) :-
  892    prompt(_, ''),
  893    redefine_system_predicate(Module:Head),
  894    functor(Head, Name, Arity),
  895    Head =.. [Name|Args],
  896    atom_concat(pengine_, Name, BodyName),
  897    Body =.. [BodyName|Args],
  898    assertz(Module:(Head :- Body)),
  899    compile_predicates([Module:Name/Arity])