
pengines_io.pl -- Provide Prolog I/O for HTML clientsThis 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).
pengine_writeln(+Term)
pengine_nl
pengine_tab(+N)
pengine_flush_output
pengine_write_term(+Term, +Options)write.
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
pengine_format(+Format) is det
pengine_format(+Format, +Args) is det
pengine_listing is det
pengine_listing(+Spec) is det
user:message_hook(+Term, +Kind, +Lines) is semidet[multifile]
message_lines_to_html(+MessageLines, +Classes, -HTMLString) is det'prolog-message' and the given Classes.
send_html(+HTML) is det
pengine_module(-Module) is det[private]'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:
error, warning,
etc.)
answer_to_json_strings(+Pengine, +AnswerDictIn, -AnswerDict)[private]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.
binding_to_html(+Pengine, +Binding, -Dict) is det[private]
term_html_string(+Term, +VarNames, +Module, -HTMLString, +Options) is det[private]
binding_term(+Term, +Vars, +WriteOptions)// is semidet[multifile]
subst_to_html(+Module, +Binding, -JSON) is det[private]
map_output(+ID, +Term, -JSON) is det[private]
prolog_help:show_html_hook(+HTML)[multifile]
pengine_io_predicate(?Head)
pengine_bind_user_streams[private]
pengine_output is semidet[private]
pengine_input is semidet[private]
pengine_bind_io_to_html(+Module)The following predicates are exported, but not or incorrectly documented.
pengine_io_goal_expansion(Arg1, Arg2)
pengine_portray_clause(Arg1)
pengine_read(Arg1)
pengine_read_line_to_codes(Arg1, Arg2)
pengine_read_line_to_string(Arg1, Arg2)
pengine_display(Arg1)
pengine_print(Arg1)
pengine_write_canonical(Arg1)
pengine_listing(Arg1)
pengine_format(Arg1, Arg2)
pengine_writeq(Arg1)