View source with raw 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-2019, VU University Amsterdam
    7                              CWI, 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:- module(pengines_io,
   37          [ pengine_writeln/1,          % +Term
   38            pengine_nl/0,
   39            pengine_flush_output/0,
   40            pengine_format/1,           % +Format
   41            pengine_format/2,           % +Format, +Args
   42
   43            pengine_write_term/2,       % +Term, +Options
   44            pengine_write/1,            % +Term
   45            pengine_writeq/1,           % +Term
   46            pengine_display/1,          % +Term
   47            pengine_print/1,            % +Term
   48            pengine_write_canonical/1,  % +Term
   49
   50            pengine_listing/0,
   51            pengine_listing/1,          % +Spec
   52            pengine_portray_clause/1,   % +Term
   53
   54            pengine_read/1,             % -Term
   55            pengine_read_line_to_string/2, % +Stream, -LineAsString
   56            pengine_read_line_to_codes/2, % +Stream, -LineAsCodes
   57
   58            pengine_io_predicate/1,     % ?Head
   59            pengine_bind_io_to_html/1,  % +Module
   60            pengine_io_goal_expansion/2,% +Goal, -Expanded
   61
   62            message_lines_to_html/3     % +Lines, +Classes, -HTML
   63          ]).   64:- autoload(library(apply),[foldl/4,maplist/3,maplist/4]).   65:- autoload(library(backcomp),[thread_at_exit/1]).   66:- autoload(library(debug),[assertion/1]).   67:- autoload(library(error),[must_be/2]).   68:- autoload(library(listing),[listing/1,portray_clause/1]).   69:- autoload(library(lists),[append/2,append/3,subtract/3]).   70:- autoload(library(option),[option/3,merge_options/3]).   71:- autoload(library(pengines),
   72	    [ pengine_self/1,
   73	      pengine_output/1,
   74	      pengine_input/2,
   75	      pengine_property/2
   76	    ]).   77:- autoload(library(prolog_stream),[open_prolog_stream/4]).   78:- autoload(library(readutil),[read_line_to_string/2]).   79:- autoload(library(yall),[(>>)/4]).   80:- autoload(library(http/term_html),[term/4]).   81
   82:- use_module(library(http/html_write),[html/3,print_html/1, op(_,_,_)]).   83:- use_module(library(settings),[setting/4,setting/2]).   84
   85:- use_module(library(sandbox), []).   86:- autoload(library(thread), [call_in_thread/2]).   87
   88:- html_meta send_html(html).   89:- public send_html/1.   90
   91:- meta_predicate
   92    pengine_format(+,:).

Provide Prolog I/O for HTML clients

This module redefines some of the standard Prolog I/O predicates to behave transparently for HTML clients. It provides two ways to redefine the standard predicates: using goal_expansion/2 and by redefining the system predicates using redefine_system_predicate/1. The latter is the preferred route because it gives a more predictable trace to the user and works regardless of the use of other expansion and meta-calling.

Redefining works by redefining the system predicates in the context of the pengine's module. This is configured using the following code snippet.

:- pengine_application(myapp).
:- use_module(myapp:library(pengines_io)).
pengines:prepare_module(Module, myapp, _Options) :-
      pengines_io:pengine_bind_io_to_html(Module).

Using goal_expansion/2 works by rewriting the corresponding goals using goal_expansion/2 and use the new definition to re-route I/O via pengine_input/2 and pengine_output/1. A pengine application is prepared for using this module with the following code:

:- pengine_application(myapp).
:- use_module(myapp:library(pengines_io)).
myapp:goal_expansion(In,Out) :-
      pengine_io_goal_expansion(In, Out).

*/

  127:- setting(write_options, list(any), [max_depth(1000)],
  128           'Additional options for stringifying Prolog results').  129
  130
  131                 /*******************************
  132                 *            OUTPUT            *
  133                 *******************************/
 pengine_writeln(+Term)
Emit Term as <span class=writeln>Term<br></span>.
  139pengine_writeln(Term) :-
  140    pengine_output,
  141    !,
  142    pengine_module(Module),
  143    send_html(span(class(writeln),
  144                   [ \term(Term,
  145                           [ module(Module)
  146                           ]),
  147                     br([])
  148                   ])).
  149pengine_writeln(Term) :-
  150    writeln(Term).
 pengine_nl
Emit a <br/> to the pengine.
  156pengine_nl :-
  157    pengine_output,
  158    !,
  159    send_html(br([])).
  160pengine_nl :-
  161    nl.
 pengine_flush_output
No-op. Pengines do not use output buffering (maybe they should though).
  168pengine_flush_output :-
  169    pengine_output,
  170    !.
  171pengine_flush_output :-
  172    flush_output.
 pengine_write_term(+Term, +Options)
Writes term as <span class=Class>Term</span>. In addition to the options of write_term/2, these options are processed:
class(+Class)
Specifies the class of the element. Default is write.
  182pengine_write_term(Term, Options) :-
  183    pengine_output,
  184    !,
  185    option(class(Class), Options, write),
  186    pengine_module(Module),
  187    send_html(span(class(Class), \term(Term,[module(Module)|Options]))).
  188pengine_write_term(Term, Options) :-
  189    write_term(Term, Options).
 pengine_write(+Term) is det
 pengine_writeq(+Term) is det
 pengine_display(+Term) is det
 pengine_print(+Term) is det
 pengine_write_canonical(+Term) is det
Redirect the corresponding Prolog output predicates.
  199pengine_write(Term) :-
  200    pengine_write_term(Term, [numbervars(true)]).
  201pengine_writeq(Term) :-
  202    pengine_write_term(Term, [quoted(true), numbervars(true)]).
  203pengine_display(Term) :-
  204    pengine_write_term(Term, [quoted(true), ignore_ops(true)]).
  205pengine_print(Term) :-
  206    current_prolog_flag(print_write_options, Options),
  207    pengine_write_term(Term, Options).
  208pengine_write_canonical(Term) :-
  209    pengine_output,
  210    !,
  211    with_output_to(string(String), write_canonical(Term)),
  212    send_html(span(class([write, cononical]), String)).
  213pengine_write_canonical(Term) :-
  214    write_canonical(Term).
 pengine_format(+Format) is det
 pengine_format(+Format, +Args) is det
As format/1,2. Emits a series of strings with <br/> for each newline encountered in the string.
To be done
- : handle ~w, ~q, etc using term//2. How can we do that??
  224pengine_format(Format) :-
  225    pengine_format(Format, []).
  226pengine_format(Format, Args) :-
  227    pengine_output,
  228    !,
  229    format(string(String), Format, Args),
  230    split_string(String, "\n", "", Lines),
  231    send_html(\lines(Lines, format)).
  232pengine_format(Format, Args) :-
  233    format(Format, Args).
  234
  235
  236                 /*******************************
  237                 *            LISTING           *
  238                 *******************************/
 pengine_listing is det
 pengine_listing(+Spec) is det
List the content of the current pengine or a specified predicate in the pengine.
  246pengine_listing :-
  247    pengine_listing(_).
  248
  249pengine_listing(Spec) :-
  250    pengine_self(Module),
  251    with_output_to(string(String), listing(Module:Spec)),
  252    split_string(String, "", "\n", [Pre]),
  253    send_html(pre(class(listing), Pre)).
  254
  255pengine_portray_clause(Term) :-
  256    pengine_output,
  257    !,
  258    with_output_to(string(String), portray_clause(Term)),
  259    split_string(String, "", "\n", [Pre]),
  260    send_html(pre(class(listing), Pre)).
  261pengine_portray_clause(Term) :-
  262    portray_clause(Term).
  263
  264
  265                 /*******************************
  266                 *         PRINT MESSAGE        *
  267                 *******************************/
  268
  269:- multifile user:message_hook/3.
 user:message_hook(+Term, +Kind, +Lines) is semidet
Send output from print_message/2 to the pengine. Messages are embedded in a <pre class=msg-Kind></pre> environment.
  276user:message_hook(Term, Kind, Lines) :-
  277    Kind \== silent,
  278    pengine_self(_),
  279    atom_concat('msg-', Kind, Class),
  280    message_lines_to_html(Lines, [Class], HTMlString),
  281    (   source_location(File, Line)
  282    ->  Src = File:Line
  283    ;   Src = (-)
  284    ),
  285    pengine_output(message(Term, Kind, HTMlString, Src)).
 message_lines_to_html(+MessageLines, +Classes, -HTMLString) is det
Helper that translates the Lines argument from user:message_hook/3 into an HTML string. The HTML is a <pre> object with the class 'prolog-message' and the given Classes.
  293message_lines_to_html(Lines, Classes, HTMlString) :-
  294    phrase(html(pre(class(['prolog-message'|Classes]),
  295                    \message_lines(Lines))), Tokens),
  296    with_output_to(string(HTMlString), print_html(Tokens)).
  297
  298message_lines([]) -->
  299    !.
  300message_lines([nl|T]) -->
  301    !,
  302    html('\n'),                     % we are in a <pre> environment
  303    message_lines(T).
  304message_lines([flush]) -->
  305    !.
  306message_lines([ansi(Attributes, Fmt, Args)|T]) -->
  307    !,
  308    {  is_list(Attributes)
  309    -> foldl(style, Attributes, Fmt-Args, HTML)
  310    ;  style(Attributes, Fmt-Args, HTML)
  311    },
  312    html(HTML),
  313    message_lines(T).
  314message_lines([H|T]) -->
  315    html(H),
  316    message_lines(T).
  317
  318style(bold, Content, b(Content)) :- !.
  319style(fg(default), Content, span(style('color: black'), Content)) :- !.
  320style(fg(Color), Content, span(style('color:'+Color), Content)) :- !.
  321style(_, Content, Content).
  322
  323
  324                 /*******************************
  325                 *             INPUT            *
  326                 *******************************/
  327
  328pengine_read(Term) :-
  329    pengine_input,
  330    !,
  331    prompt(Prompt, Prompt),
  332    pengine_input(Prompt, Term).
  333pengine_read(Term) :-
  334    read(Term).
  335
  336pengine_read_line_to_string(From, String) :-
  337    pengine_input,
  338    !,
  339    must_be(oneof([current_input,user_input]), From),
  340    (   prompt(Prompt, Prompt),
  341        Prompt \== ''
  342    ->  true
  343    ;   Prompt = 'line> '
  344    ),
  345    pengine_input(_{type: console, prompt:Prompt}, StringNL),
  346    string_concat(String, "\n", StringNL).
  347pengine_read_line_to_string(From, String) :-
  348    read_line_to_string(From, String).
  349
  350pengine_read_line_to_codes(From, Codes) :-
  351    pengine_read_line_to_string(From, String),
  352    string_codes(String, Codes).
  353
  354
  355                 /*******************************
  356                 *             HTML             *
  357                 *******************************/
  358
  359lines([], _) --> [].
  360lines([H|T], Class) -->
  361    html(span(class(Class), H)),
  362    (   { T == [] }
  363    ->  []
  364    ;   html(br([])),
  365        lines(T, Class)
  366    ).
 send_html(+HTML) is det
Convert html//1 term into a string and send it to the client using pengine_output/1.
  373send_html(HTML) :-
  374    phrase(html(HTML), Tokens),
  375    with_output_to(string(HTMlString), print_html(Tokens)),
  376    pengine_output(HTMlString).
 pengine_module(-Module) is det
Module (used for resolving operators).
  383pengine_module(Module) :-
  384    pengine_self(Pengine),
  385    !,
  386    pengine_property(Pengine, module(Module)).
  387pengine_module(user).
  388
  389                 /*******************************
  390                 *        OUTPUT FORMAT         *
  391                 *******************************/
 pengines:event_to_json(+Event, -JSON, +Format, +VarNames) is semidet
Provide additional translations for Prolog terms to output. Defines formats are:
'json-s'
Simple or string format: Prolog terms are sent using quoted write.
'json-html'
Serialize responses as HTML string. This is intended for applications that emulate the Prolog toplevel. This format carries the following data:
data
List if answers, where each answer is an object with
variables
Array of objects, each describing a variable. These objects contain these fields:
  • variables: Array of strings holding variable names
  • value: HTML-ified value of the variables
  • substitutions: Array of objects for substitutions that break cycles holding:
    • var: Name of the inserted variable
    • value: HTML-ified value
residuals
Array of strings representing HTML-ified residual goals.
  420:- multifile
  421    pengines:event_to_json/3.
 pengines:event_to_json(+PrologEvent, -JSONEvent, +Format, +VarNames)
If Format equals 'json-s' or 'json-html', emit a simplified JSON representation of the data, suitable for notably SWISH. This deals with Prolog answers and output messages. If a message originates from print_message/3, it gets several additional properties:
message:Kind
Indicate the kind of the message (error, warning, etc.)
location:_161832{ch:CharPos, file:File, line:Line}
If the message is related to a source location, indicate the file and line and, if available, the character location.
  438pengines:event_to_json(success(ID, Answers0, Projection, Time, More), JSON,
  439                       'json-s') :-
  440    !,
  441    JSON0 = json{event:success, id:ID, time:Time, data:Answers, more:More},
  442    maplist(answer_to_json_strings(ID), Answers0, Answers),
  443    add_projection(Projection, JSON0, JSON).
  444pengines:event_to_json(output(ID, Term), JSON, 'json-s') :-
  445    !,
  446    map_output(ID, Term, JSON).
  447
  448add_projection([], JSON, JSON) :- !.
  449add_projection(VarNames, JSON0, JSON0.put(projection, VarNames)).
 answer_to_json_strings(+Pengine, +AnswerDictIn, -AnswerDict)
Translate answer dict with Prolog term values into answer dict with string values.
  457answer_to_json_strings(Pengine, DictIn, DictOut) :-
  458    dict_pairs(DictIn, Tag, Pairs),
  459    maplist(term_string_value(Pengine), Pairs, BindingsOut),
  460    dict_pairs(DictOut, Tag, BindingsOut).
  461
  462term_string_value(Pengine, N-V, N-A) :-
  463    with_output_to(string(A),
  464                   write_term(V,
  465                              [ module(Pengine),
  466                                quoted(true)
  467                              ])).
 pengines:event_to_json(+Event, -JSON, +Format, +VarNames)
Implement translation of a Pengine event to json-html format. This format represents the answer as JSON, but the variable bindings are (structured) HTML strings rather than JSON objects.

CHR residual goals are not bound to the projection variables. We hacked a bypass to fetch these by returning them in a variable named _residuals, which must be bound to a term '$residuals'(List). Such a variable is removed from the projection and added to residual goals.

  481pengines:event_to_json(success(ID, Answers0, Projection, Time, More),
  482                       JSON, 'json-html') :-
  483    !,
  484    JSON0 = json{event:success, id:ID, time:Time, data:Answers, more:More},
  485    maplist(map_answer(ID), Answers0, ResVars, Answers),
  486    add_projection(Projection, ResVars, JSON0, JSON).
  487pengines:event_to_json(output(ID, Term), JSON, 'json-html') :-
  488    !,
  489    map_output(ID, Term, JSON).
  490
  491map_answer(ID, Bindings0, ResVars, Answer) :-
  492    dict_bindings(Bindings0, Bindings1),
  493    select_residuals(Bindings1, Bindings2, ResVars, Residuals0, Clauses),
  494    append(Residuals0, Residuals1),
  495    prolog:translate_bindings(Bindings2, Bindings3, [], Residuals1,
  496                              ID:Residuals-_HiddenResiduals),
  497    maplist(binding_to_html(ID), Bindings3, VarBindings),
  498    final_answer(ID, VarBindings, Residuals, Clauses, Answer).
  499
  500final_answer(_Id, VarBindings, [], [], Answer) :-
  501    !,
  502    Answer = json{variables:VarBindings}.
  503final_answer(ID, VarBindings, Residuals, [], Answer) :-
  504    !,
  505    residuals_html(Residuals, ID, ResHTML),
  506    Answer = json{variables:VarBindings, residuals:ResHTML}.
  507final_answer(ID, VarBindings, [], Clauses, Answer) :-
  508    !,
  509    clauses_html(Clauses, ID, ClausesHTML),
  510    Answer = json{variables:VarBindings, wfs_residual_program:ClausesHTML}.
  511final_answer(ID, VarBindings, Residuals, Clauses, Answer) :-
  512    !,
  513    residuals_html(Residuals, ID, ResHTML),
  514    clauses_html(Clauses, ID, ClausesHTML),
  515    Answer = json{variables:VarBindings,
  516                  residuals:ResHTML,
  517                  wfs_residual_program:ClausesHTML}.
  518
  519residuals_html([], _, []).
  520residuals_html([H0|T0], Module, [H|T]) :-
  521    term_html_string(H0, [], Module, H, [priority(999)]),
  522    residuals_html(T0, Module, T).
  523
  524clauses_html(Clauses, _ID, HTMLString) :-
  525    with_output_to(string(Program), list_clauses(Clauses)),
  526    phrase(html(pre([class('wfs-residual-program')], Program)), Tokens),
  527    with_output_to(string(HTMLString), print_html(Tokens)).
  528
  529list_clauses([]).
  530list_clauses([H|T]) :-
  531    (   system_undefined(H)
  532    ->  true
  533    ;   portray_clause(H)
  534    ),
  535    list_clauses(T).
  536
  537system_undefined((undefined :- tnot(undefined))).
  538system_undefined((answer_count_restraint :- tnot(answer_count_restraint))).
  539system_undefined((radial_restraint :- tnot(radial_restraint))).
  540
  541dict_bindings(Dict, Bindings) :-
  542    dict_pairs(Dict, _Tag, Pairs),
  543    maplist([N-V,N=V]>>true, Pairs, Bindings).
  544
  545select_residuals([], [], [], [], []).
  546select_residuals([H|T], Bindings, Vars, Residuals, Clauses) :-
  547    binding_residual(H, Var, Residual),
  548    !,
  549    Vars = [Var|TV],
  550    Residuals = [Residual|TR],
  551    select_residuals(T, Bindings, TV, TR, Clauses).
  552select_residuals([H|T], Bindings, Vars, Residuals, Clauses) :-
  553    binding_residual_clauses(H, Var, Delays, Clauses0),
  554    !,
  555    Vars = [Var|TV],
  556    Residuals = [Delays|TR],
  557    append(Clauses0, CT, Clauses),
  558    select_residuals(T, Bindings, TV, TR, CT).
  559select_residuals([H|T0], [H|T], Vars, Residuals, Clauses) :-
  560    select_residuals(T0, T, Vars, Residuals, Clauses).
  561
  562binding_residual('_residuals' = '$residuals'(Residuals), '_residuals', Residuals) :-
  563    is_list(Residuals).
  564binding_residual('Residuals' = '$residuals'(Residuals), 'Residuals', Residuals) :-
  565    is_list(Residuals).
  566binding_residual('Residual'  = '$residual'(Residual),   'Residual', [Residual]) :-
  567    callable(Residual).
  568
  569binding_residual_clauses(
  570    '_wfs_residual_program' = '$wfs_residual_program'(Delays, Clauses),
  571    '_wfs_residual_program', Residuals, Clauses) :-
  572    phrase(comma_list(Delays), Residuals).
  573
  574comma_list(true) --> !.
  575comma_list((A,B)) --> !, comma_list(A), comma_list(B).
  576comma_list(A) --> [A].
  577
  578add_projection(-, _, JSON, JSON) :- !.
  579add_projection(VarNames0, ResVars0, JSON0, JSON) :-
  580    append(ResVars0, ResVars1),
  581    sort(ResVars1, ResVars),
  582    subtract(VarNames0, ResVars, VarNames),
  583    add_projection(VarNames, JSON0, JSON).
 binding_to_html(+Pengine, +Binding, -Dict) is det
Convert a variable binding into a JSON Dict. Note that this code assumes that the module associated with Pengine has the same name as the Pengine. The module is needed to
Arguments:
Binding- is a term binding(Vars,Term,Substitutions)
  594binding_to_html(ID, binding(Vars,Term,Substitutions), JSON) :-
  595    JSON0 = json{variables:Vars, value:HTMLString},
  596    binding_write_options(ID, Options),
  597    term_html_string(Term, Vars, ID, HTMLString, Options),
  598    (   Substitutions == []
  599    ->  JSON = JSON0
  600    ;   maplist(subst_to_html(ID), Substitutions, HTMLSubst),
  601        JSON = JSON0.put(substitutions, HTMLSubst)
  602    ).
  603
  604binding_write_options(Pengine, Options) :-
  605    (   current_predicate(Pengine:screen_property/1),
  606        Pengine:screen_property(tabled(true))
  607    ->  Options = []
  608    ;   Options = [priority(699)]
  609    ).
 term_html_string(+Term, +VarNames, +Module, -HTMLString, +Options) is det
Translate Term into an HTML string using the operator declarations from Module. VarNames is a list of variable names that have this value.
  618term_html_string(Term, Vars, Module, HTMLString, Options) :-
  619    setting(write_options, WOptions),
  620    merge_options(WOptions,
  621                  [ quoted(true),
  622                    numbervars(true),
  623                    module(Module)
  624                  | Options
  625                  ], WriteOptions),
  626    phrase(term_html(Term, Vars, WriteOptions), Tokens),
  627    with_output_to(string(HTMLString), print_html(Tokens)).
 binding_term(+Term, +Vars, +WriteOptions)// is semidet
Hook to render a Prolog result term as HTML. This hook is called for each non-variable binding, passing the binding value as Term, the names of the variables as Vars and a list of options for write_term/3. If the hook fails, term//2 is called.
Arguments:
Vars- is a list of variable names or [] if Term is a residual goal.
  639:- multifile binding_term//3.  640
  641term_html(Term, Vars, WriteOptions) -->
  642    { nonvar(Term) },
  643    binding_term(Term, Vars, WriteOptions),
  644    !.
  645term_html(Term, _Vars, WriteOptions) -->
  646    term(Term, WriteOptions).
 subst_to_html(+Module, +Binding, -JSON) is det
Render a variable substitution resulting from term factorization, in this case breaking a cycle.
  653subst_to_html(ID, '$VAR'(Name)=Value, json{var:Name, value:HTMLString}) :-
  654    !,
  655    binding_write_options(ID, Options),
  656    term_html_string(Value, [Name], ID, HTMLString, Options).
  657subst_to_html(_, Term, _) :-
  658    assertion(Term = '$VAR'(_)).
 map_output(+ID, +Term, -JSON) is det
Map an output term. This is the same for json-s and json-html.
  665map_output(ID, message(Term, Kind, HTMLString, Src), JSON) :-
  666    atomic(HTMLString),
  667    !,
  668    JSON0 = json{event:output, id:ID, message:Kind, data:HTMLString},
  669    pengines:add_error_details(Term, JSON0, JSON1),
  670    (   Src = File:Line,
  671        \+ JSON1.get(location) = _
  672    ->  JSON = JSON1.put(_{location:_{file:File, line:Line}})
  673    ;   JSON = JSON1
  674    ).
  675map_output(ID, Term, json{event:output, id:ID, data:Data}) :-
  676    (   atomic(Term)
  677    ->  Data = Term
  678    ;   is_dict(Term, json),
  679        ground(json)                % TBD: Check proper JSON object?
  680    ->  Data = Term
  681    ;   term_string(Term, Data)
  682    ).
 prolog_help:show_html_hook(+HTML)
Hook into help/1 to render the help output in the SWISH console.
  689:- multifile
  690    prolog_help:show_html_hook/1.  691
  692prolog_help:show_html_hook(HTML) :-
  693    pengine_output,
  694    pengine_output(HTML).
  695
  696
  697                 /*******************************
  698                 *          SANDBOXING          *
  699                 *******************************/
  700
  701:- multifile
  702    sandbox:safe_primitive/1,       % Goal
  703    sandbox:safe_meta/2.            % Goal, Called
  704
  705sandbox:safe_primitive(pengines_io:pengine_listing(_)).
  706sandbox:safe_primitive(pengines_io:pengine_nl).
  707sandbox:safe_primitive(pengines_io:pengine_flush_output).
  708sandbox:safe_primitive(pengines_io:pengine_print(_)).
  709sandbox:safe_primitive(pengines_io:pengine_write(_)).
  710sandbox:safe_primitive(pengines_io:pengine_read(_)).
  711sandbox:safe_primitive(pengines_io:pengine_read_line_to_string(_,_)).
  712sandbox:safe_primitive(pengines_io:pengine_read_line_to_codes(_,_)).
  713sandbox:safe_primitive(pengines_io:pengine_write_canonical(_)).
  714sandbox:safe_primitive(pengines_io:pengine_write_term(_,_)).
  715sandbox:safe_primitive(pengines_io:pengine_writeln(_)).
  716sandbox:safe_primitive(pengines_io:pengine_writeq(_)).
  717sandbox:safe_primitive(pengines_io:pengine_portray_clause(_)).
  718sandbox:safe_primitive(system:write_term(_,_)).
  719sandbox:safe_primitive(system:prompt(_,_)).
  720sandbox:safe_primitive(system:statistics(_,_)).
  721
  722sandbox:safe_meta(pengines_io:pengine_format(Format, Args), Calls) :-
  723    sandbox:format_calls(Format, Args, Calls).
  724
  725
  726                 /*******************************
  727                 *         REDEFINITION         *
  728                 *******************************/
 pengine_io_predicate(?Head)
True when Head describes the head of a (system) IO predicate that is redefined by the HTML binding.
  735pengine_io_predicate(writeln(_)).
  736pengine_io_predicate(nl).
  737pengine_io_predicate(flush_output).
  738pengine_io_predicate(format(_)).
  739pengine_io_predicate(format(_,_)).
  740pengine_io_predicate(read(_)).
  741pengine_io_predicate(read_line_to_string(_,_)).
  742pengine_io_predicate(read_line_to_codes(_,_)).
  743pengine_io_predicate(write_term(_,_)).
  744pengine_io_predicate(write(_)).
  745pengine_io_predicate(writeq(_)).
  746pengine_io_predicate(display(_)).
  747pengine_io_predicate(print(_)).
  748pengine_io_predicate(write_canonical(_)).
  749pengine_io_predicate(listing).
  750pengine_io_predicate(listing(_)).
  751pengine_io_predicate(portray_clause(_)).
  752
  753term_expansion(pengine_io_goal_expansion(_,_),
  754               Clauses) :-
  755    findall(Clause, io_mapping(Clause), Clauses).
  756
  757io_mapping(pengine_io_goal_expansion(Head, Mapped)) :-
  758    pengine_io_predicate(Head),
  759    Head =.. [Name|Args],
  760    atom_concat(pengine_, Name, BodyName),
  761    Mapped =.. [BodyName|Args].
  762
  763pengine_io_goal_expansion(_, _).
  764
  765
  766                 /*******************************
  767                 *      REBIND PENGINE I/O      *
  768                 *******************************/
  769
  770:- public
  771    stream_write/2,
  772    stream_read/2,
  773    stream_close/1.  774
  775:- thread_local
  776    pengine_io/2.  777
  778stream_write(Stream, Out) :-
  779    (   pengine_io(_,_)
  780    ->  send_html(pre(class(console), Out))
  781    ;   current_prolog_flag(pengine_main_thread, TID),
  782        thread_signal(TID, stream_write(Stream, Out))
  783    ).
  784stream_read(Stream, Data) :-
  785    (   pengine_io(_,_)
  786    ->  prompt(Prompt, Prompt),
  787        pengine_input(_{type:console, prompt:Prompt}, Data)
  788    ;   current_prolog_flag(pengine_main_thread, TID),
  789        call_in_thread(TID, stream_read(Stream, Data))
  790    ).
  791stream_close(_Stream).
 pengine_bind_user_streams
Bind the pengine user I/O streams to a Prolog stream that redirects the input and output to pengine_input/2 and pengine_output/1. This results in less pretty behaviour then redefining the I/O predicates to produce nice HTML, but does provide functioning I/O from included libraries.
  801pengine_bind_user_streams :-
  802    Err = Out,
  803    open_prolog_stream(pengines_io, write, Out, []),
  804    set_stream(Out, buffer(line)),
  805    open_prolog_stream(pengines_io, read,  In, []),
  806    set_stream(In,  alias(user_input)),
  807    set_stream(Out, alias(user_output)),
  808    set_stream(Err, alias(user_error)),
  809    set_stream(In,  alias(current_input)),
  810    set_stream(Out, alias(current_output)),
  811    assertz(pengine_io(In, Out)),
  812    thread_self(Me),
  813    thread_property(Me, id(Id)),
  814    set_prolog_flag(pengine_main_thread, Id),
  815    thread_at_exit(close_io).
  816
  817close_io :-
  818    retract(pengine_io(In, Out)),
  819    !,
  820    close(In, [force(true)]),
  821    close(Out, [force(true)]).
  822close_io.
 pengine_output is semidet
 pengine_input is semidet
True when output (input) is redirected to a pengine.
  829pengine_output :-
  830    current_output(Out),
  831    pengine_io(_, Out).
  832
  833pengine_input :-
  834    current_input(In),
  835    pengine_io(In, _).
 pengine_bind_io_to_html(+Module)
Redefine the built-in predicates for IO to send HTML messages using pengine_output/1.
  843pengine_bind_io_to_html(Module) :-
  844    forall(pengine_io_predicate(Head),
  845           bind_io(Head, Module)),
  846    pengine_bind_user_streams.
  847
  848bind_io(Head, Module) :-
  849    prompt(_, ''),
  850    redefine_system_predicate(Module:Head),
  851    functor(Head, Name, Arity),
  852    Head =.. [Name|Args],
  853    atom_concat(pengine_, Name, BodyName),
  854    Body =.. [BodyName|Args],
  855    assertz(Module:(Head :- Body)),
  856    compile_predicates([Module:Name/Arity])