1/* Part of sCASP 2 3 Author: Jan Wielemaker 4 E-mail: jan@swi-prolog.org 5 Copyright (c) 2021, SWI-Prolog Solutions b.v. 6 All rights reserved. 7 8 Redistribution and use in source and binary forms, with or without 9 modification, are permitted provided that the following conditions 10 are met: 11 12 1. Redistributions of source code must retain the above copyright 13 notice, this list of conditions and the following disclaimer. 14 15 2. Redistributions in binary form must reproduce the above copyright 16 notice, this list of conditions and the following disclaimer in 17 the documentation and/or other materials provided with the 18 distribution. 19 20 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 21 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 22 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 23 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 24 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 25 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 26 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 27 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 28 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 29 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 30 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 31 POSSIBILITY OF SUCH DAMAGE. 32*/ 33 34:- module(scasp_just_human, 35 [ human_justification_tree/2, % :Tree, +Options 36 human_model/2, % :Model, +Options 37 human_query/2, % :Query, +Options 38 human_predicate/2, % :Rule, +Options 39 human_rule/2 % :Rule, +Options 40 ]). 41:- use_module(html). 42:- use_module(html_text). 43:- use_module(library(http/html_write)). 44:- use_module(library(option)). 45 46:- meta_predicate 47 human_justification_tree( , ), 48 human_model( , ), 49 human_query( , ), 50 human_predicate( , ), 51 human_rule( , ). 52 53/** <module> Print s(CASP) output in human language 54 55This module prints the s(CASP) justification, model and query in human 56language. It translates the s(CASP) data into a list of tokens as used 57by the SWI-Prolog print_message/2 and friends and then uses 58print_message_lines/3 to emit the tokens. 59 60This module reuses the human output from html.pl. It does so by 61modifying the DCG that produces the HTML tokens. This transformation is 62defined in html_text.pl. 63*/ 64 65 66%! human_justification_tree(:Tree, +Options) is det. 67% 68% Print Tree to `current_output` in _human_ representation. Normally 69% this is used together with ovar_analyze_term/1. 70% 71% @see print_message/2. 72 73:- det(human_justification_tree/2). 74 75human_justification_tree(M:Tree, Options) :- 76 phrase(human_output(M:Tree, 77 [ depth(0), 78 module(M) 79 | Options 80 ]), Tokens0), 81 fixup_layout(Tokens0, Tokens), 82 format(current_output, '~N', []), 83 print_message_lines(current_output, '', Tokens). 84 85%! human_output(:FilterChildren, +Options) 86 87human_output(Tree, Options) --> 88 !, 89 emit_as(\html_justification_tree(Tree, Options), 90 plain). 91 92 93 /******************************* 94 * MODEL * 95 *******************************/ 96 97%! human_model(:Model, +Options) 98 99human_model(M:Model, Options) :- 100 phrase(emit_model(Model, 101 [ module(M) 102 | Options 103 ]), Tokens0), 104 fixup_layout(Tokens0, Tokens), 105 print_message_lines(current_output, '', Tokens). 106 107:- det(emit_model//2). 108 109emit_model(Model, Options) --> 110 emit_as(\html_model(Model, Options), 111 plain). 112 113 114 /******************************* 115 * QUERY * 116 *******************************/ 117 118%! human_query(:Query, +Options) 119 120human_query(M:Query, Options) :- 121 phrase(emit_query(M:Query, 122 [ module(M) 123 | Options 124 ]), Tokens0), 125 fixup_layout(Tokens0, Tokens), 126 print_message_lines(current_output, '', Tokens). 127 128:- det(emit_query//2). 129 130emit_query(Query, Options) --> 131 emit_as(\html_query(Query, Options), 132 plain). 133 134 135 /******************************* 136 * PROGRAM * 137 *******************************/ 138 139%! human_predicate(Clauses, Options) 140% 141% 142 143human_predicate(Clauses, Options) :- 144 human_text(\html_predicate(Clauses, Options)). 145 146%! human_rule(:Rule, +Options) 147 148human_rule(M:Rule, Options) :- 149 phrase(emit_rule(Rule, 150 [ module(M) 151 | Options 152 ]), Tokens0), 153 fixup_layout(Tokens0, Tokens), 154 print_message_lines(current_output, '', Tokens). 155 156:- det(emit_rule//2). 157 158emit_rule(Rule, Options) --> 159 emit_as(\html_rule(Rule, Options), 160 plain). 161 162 163:- html_meta 164 human_text( ). 165 166human_text(Rule) :- 167 phrase(emit_as(Rule, plain), Tokens0), 168 fixup_layout(Tokens0, Tokens), 169 print_message_lines(current_output, '', Tokens). 170 171 172 173 174 175 /******************************* 176 * INTEGRATION * 177 *******************************/ 178 179:- multifile 180 scasp_stack:justification_tree_hook/2, 181 scasp_model:model_hook/2. 182 183scasp_stackjustification_tree_hook(Tree, Options) :- 184 option(human(true), Options), 185 !, 186 human_justification_tree(Tree, Options). 187scasp_modelmodel_hook(Model, Options) :- 188 option(human(true), Options), 189 !, 190 human_model(Model, Options)