33
34:- module(scasp_just_human,
35 [ human_justification_tree/2, 36 human_model/2, 37 human_query/2, 38 human_predicate/2, 39 human_rule/2 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(:, +).
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).
87human_output(Tree, Options) -->
88 !,
89 emit_as(\html_justification_tree(Tree, Options),
90 plain).
91
92
93
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
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
143human_predicate(Clauses, Options) :-
144 human_text(\html_predicate(Clauses, Options)).
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(html). 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 178
179:- multifile
180 scasp_stack:justification_tree_hook/2,
181 scasp_model:model_hook/2. 182
183scasp_stack:justification_tree_hook(Tree, Options) :-
184 option(human(true), Options),
185 !,
186 human_justification_tree(Tree, Options).
187scasp_model:model_hook(Model, Options) :-
188 option(human(true), Options),
189 !,
190 human_model(Model, Options)
Print
s(CASP)
output in human languageThis module prints the
s(CASP)
justification, model and query in human language. It translates thes(CASP)
data into a list of tokens as used by the SWI-Prolog print_message/2 and friends and then uses print_message_lines/3 to emit the tokens.This module reuses the human output from
html.pl
. It does so by modifying the DCG that produces the HTML tokens. This transformation is defined inhtml_text.pl
. */