View source with raw comments or as raw
    1:- module(scasp_swish,
    2          []).    3:- use_module(library(http/html_write)).    4:- use_module(library(pengines)).    5:- use_module(library(apply)).    6:- use_module(library(lists)).    7
    8:- use_module(swish(lib/config)).    9
   10:- use_module(library(scasp/embed)).   11:- use_module(library(scasp/html)).   12:- use_module(library(scasp/output)).

s(CASP) adapter for SWISH

Hook into SWISH to make the model and justification available in the SWISH web interface. */

   20:- multifile
   21    swish_config:config/2,
   22    swish_trace:post_context/1,
   23    swish_trace:post_context/3.
 swish_trace:post_context(+Dict) is semidet
Called before the other context extraction. We use it to name the variables. Note that we also do the work for swish_trace:post_context/3 here because we need to remove the attributes.

The model and justification are communicated as a Prolog string holding HTML. That is dubious as the SWISH infrastructure turns this into escaped HTML which we need to undo in SWISH' runner.js.

   36swish_trace:post_context(Dict) :-
   37    _{bindings:Bindings0} :< Dict,
   38    swish_config:config(scasp_model_var, ModelVar),
   39    swish_config:config(scasp_justification_var, JustificationVar),
   40    selectchk(ModelVar = HTMLModel, Bindings0, Bindings1),
   41    selectchk(JustificationVar = HTMLJustification, Bindings1, Bindings),
   42    pengine_self(Module),
   43    scasp_model(Module:Model),
   44    scasp_justification(Module:Justification, []),
   45    Term = t(Bindings, Model, Justification),
   46    findall(HTMLModel-HTMLJustification, % revert backtrackable changes
   47            to_html(Module:Term, HTMLModel, HTMLJustification),
   48            [ HTMLModel-HTMLJustification ]).
   49
   50:- det(to_html/3).   51
   52to_html(M:Term, HTMLModel, HTMLJustification) :-
   53    Term = t(Bindings, Model, Justification),
   54    maplist(set_name, Bindings),
   55    ovar_analyze_term(Term),
   56    inline_constraints(Term, []),
   57    html_string(html_model(M:Model, []), HTMLModel),
   58    html_string(html_justification_tree(M:Justification, []), HTMLJustification).
   59
   60set_name(Name = Var) :-
   61    (   var(Var)
   62    ->  ovar_set_name(Var, Name)
   63    ;   true
   64    ).
   65
   66swish_config:config(scasp_model_var, '_swish__scasp_model').
   67swish_config:config(scasp_justification_var, '_swish__scasp_justification').
 swish_trace:post_context(+Name, +Goal, -Var) is semidet
Bind Var with the context information that belongs to Name. Note that we suppress normal residuals using the first clause as we report these through the others. The model and justification are already emitted in swish_trace:post_context/1 above.
   76swish_trace:post_context(Name, _Goal,  _) :-
   77    swish_config(residuals_var, Name),
   78    scasp_model(_),
   79    !.
   80
   81:- meta_predicate
   82    html_string(//, -).   83
   84html_string(Goal, HTML) :-
   85    phrase(Goal, Tokens),
   86    with_output_to(string(HTML0), print_html(Tokens)),
   87    split_string(HTML0, "", "\n ", [HTML])