pengines_io.pl -- 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).
- pengine_writeln(+Term)
- Emit Term as <span class=writeln>Term<br></span>.
- pengine_nl
- Emit a <br/> to the pengine.
- pengine_tab(+N)
- Emit N spaces
- pengine_flush_output
- No-op. Pengines do not use output buffering (maybe they should
though).
- 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
.
- 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.
- 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??
- pengine_listing is det
- pengine_listing(+Spec) is det
- List the content of the current pengine or a specified predicate
in the pengine.
- user:message_hook(+Term, +Kind, +Lines) is semidet[multifile]
- Send output from print_message/2 to the pengine. Messages are
embedded in a <pre class=msg-Kind></pre> environment.
- 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.
- send_html(+HTML) is det
- Convert html//1 term into a string and send it to the client
using pengine_output/1.
- pengine_module(-Module) is det[private]
- Module (used for resolving operators).
- pengines:event_to_json(+Event, -JSON, +Format, +VarNames) is semidet[private]
- 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.
- pengines:event_to_json(+PrologEvent, -JSONEvent, +Format, +VarNames)[private]
- 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:_3307750{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.
- answer_to_json_strings(+Pengine, +AnswerDictIn, -AnswerDict)[private]
- Translate answer dict with Prolog term values into answer dict
with string values.
- pengines:event_to_json(+Event, -JSON, +Format, +VarNames)[private]
- 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.
- binding_to_html(+Pengine, +Binding, -Dict) is det[private]
- 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) |
- term_html_string(+Term, +VarNames, +Module, -HTMLString, +Options) is det[private]
- Translate Term into an HTML string using the operator
declarations from Module. VarNames is a list of variable names
that have this value.
- binding_term(+Term, +Vars, +WriteOptions)// is semidet[multifile]
- 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. |
- subst_to_html(+Module, +Binding, -JSON) is det[private]
- Render a variable substitution resulting from term
factorization, in this case breaking a cycle.
- map_output(+ID, +Term, -JSON) is det[private]
- Map an output term. This is the same for json-s and json-html.
- prolog_help:show_html_hook(+HTML)[multifile]
- Hook into help/1 to render the help output in the SWISH console.
- pengine_io_predicate(?Head)
- True when Head describes the head of a (system) IO predicate
that is redefined by the HTML binding.
- pengine_bind_user_streams[private]
- 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.
- pengine_output is semidet[private]
- pengine_input is semidet[private]
- True when output (input) is redirected to a pengine.
- pengine_bind_io_to_html(+Module)
- Redefine the built-in predicates for IO to send HTML messages
using pengine_output/1.
Re-exported predicates
The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.
- 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.
- 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.
- 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.
- 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.
- 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??
- pengine_listing is det
- pengine_listing(+Spec) is det
- List the content of the current pengine or a specified predicate
in the pengine.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- pengine_io_goal_expansion(Arg1, Arg2)
- pengine_read_line_to_codes(Arg1, Arg2)
- pengine_portray_clause(Arg1)
- pengine_read(Arg1)
- pengine_read_line_to_string(Arg1, Arg2)