1 % Heinrich Heine Universitaet Duesseldorf
2 % (c) 2021-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(visb_visualiser,[load_visb_file/1,
6 load_visb_definitions_from_list_of_facts/2,
7 load_visb_definitions_from_term/2,
8 load_visb_file_if_necessary/1,
9 visb_file_is_loaded/1, visb_file_is_loaded/3,
10 visb_current_state_can_be_visualised/0,
11 get_default_visb_file/2, extended_static_check_default_visb_file/0,
12 load_default_visb_file_if_necessary/0,
13 generate_visb_html_for_history/1, generate_visb_html_for_history/2,
14 generate_visb_html_for_history_with_vars/1,
15 generate_visb_html_for_history_with_source/1,
16 generate_visb_html_for_current_state/1, generate_visb_html_for_current_state/2,
17 generate_visb_html_codes_for_states/3,
18 generate_visb_html/3,
19 tcltk_get_visb_items/1, tcltk_get_visb_events/1,
20 tcltk_get_visb_objects/1, tcltk_get_visb_hovers/1,
21 get_visb_items/1, get_visb_attributes_for_state/2,
22 get_visb_click_events/1, get_visb_hovers/1,
23 perform_visb_click_event/4,
24 tcltk_perform_visb_click_event/1,
25 get_visb_default_svg_file_contents/1,
26 get_visb_svg_objects/1]).
27
28 :- use_module(probsrc(module_information),[module_info/2]).
29 :- module_info(group,visualization).
30 :- module_info(description,'This module provides VisB visualisation functionality.').
31
32 % special SVG object attributes treated by VisB
33 % title (creates hover tooltip; currently only works with objects created by VisB itself)
34 % id
35 % svg_class
36 % text
37 % hovers
38 % event, events
39 % predicate
40
41 :- meta_predicate process_repeat(-,-,-,2).
42
43 :- use_module(extrasrc(json_parser),[json_parse_file/3]).
44 :- use_module(library(lists)).
45
46 :- use_module(probsrc(error_manager)).
47 :- use_module(probsrc(preferences),[get_preference/2]).
48 :- use_module(probsrc(debug)).
49 :- use_module(probsrc(state_space), [visited_expression/2, visited_state_corresponds_to_initialised_b_machine/1,
50 get_constants_id_for_state_id/2, get_constants_state_id_for_id/2,
51 set_context_state/2, clear_context_state/0,
52 transition/3, transition/4, invariant_violated/1, invariant_not_yet_checked/1,
53 multiple_concrete_constants_exist/0, is_concrete_constants_state_id/1]).
54 :- use_module(probsrc(translate), [translate_bvalue_to_codes/2, translate_bvalue_to_codes_with_limit/3,
55 translate_bvalue_with_limit/3]).
56 :- use_module(probsrc(specfile),[eventb_mode/0, xtl_mode/0,
57 state_corresponds_to_initialised_b_machine/2,
58 state_corresponds_to_fully_setup_b_machine/2,
59 state_corresponds_to_set_up_constants_only/2,
60 expand_to_constants_and_variables/3,
61 extract_variables_from_state/2]).
62
63 :- use_module(probsrc(tools),[start_ms_timer/1,stop_ms_walltimer_with_msg/2, ajoin_with_sep/3]).
64 :- use_module(probsrc(tools_io),[safe_open_file/4, with_open_stream_to_codes/4]).
65 :- use_module(probsrc(bmachine), [b_machine_name/1, b_get_definition_name_with_pos/4, bmachine_is_precompiled/0,
66 pre_expand_typing_scope/2, determine_type_of_formula/2, determine_type_of_formula/3]).
67 :- use_module(probsrc(bsyntaxtree), [get_texpr_ids/2]).
68 :- use_module(probsrc(tools_lists),[include_maplist/3]).
69 :- use_module(probsrc(tools),[split_list/4, html_escape_codes/2]).
70 :- use_module(probsrc(tools_matching),[get_all_svg_attributes/1, is_svg_attribute/1, is_virtual_svg_attribute/1,
71 is_svg_number_attribute/2, is_svg_color_attribute/1]).
72
73 % --------------------------
74
75 % facts storing loaded JSON VisB file:
76 :- dynamic visb_file_loaded/3, visb_svg_file/5, visb_empty_svg_box_height_width/3,
77 visb_definition/6, visb_special_definition/6,
78 visb_item/7,
79 visb_event/6, visb_hover/6, visb_has_hovers/1, visb_has_visibility_hover/1,
80 visb_event_enable_list/5,
81 visb_svg_object/5, visb_svg_object_debug_info/2,
82 visb_svg_child/2, visb_svg_parent/2, % register parent/child relationships for groups, title, ...
83 visb_svg_child_of_object_from_svg_file/1. % true if parent of object is an SVG in an external file
84 :- dynamic auxiliary_visb_event/5.
85 % visb_svg_file(SVGFile, AbsolutePathSVGFile, JSONFileFromWhichWeImportSVG,PosTerm,ModLocTime)
86 % visb_item(SVGID,Attribute,TypedExpression,UsedIds,Description/Comment,StartPos,OtherMetaInfos)
87 % visb_event(SVGID,Event,PredicateList,TypedPredicate,File,Pos)
88 % visb_svg_object(SVGID,SVG_Class,AttrList,Description/Comment,Pos) ; AttrList contains svg_attribute(Attr,Val)
89
90 reset_visb :- debug_println(9,resetting_visb),
91 retractall(visb_file_loaded(_,_,_)),
92 retractall(visb_empty_svg_box_height_width(_,_,_)),
93 retractall(visb_svg_file(_,_,_,_,_)),
94 retractall(visb_definition(_,_,_,_,_,_)),
95 retractall(visb_special_definition(_,_,_,_,_,_)),
96 retractall(visb_item(_,_,_,_,_,_,_)),
97 retractall(visb_event(_,_,_,_,_,_)),
98 retractall(visb_hover(_,_,_,_,_,_)),
99 retractall(visb_has_hovers(_)),
100 retractall(visb_has_visibility_hover(_)),
101 retractall(visb_event_enable_list(_,_,_,_,_)),
102 retractall(auxiliary_visb_event(_,_,_,_,_)),
103 retractall(visb_svg_object(_,_,_,_,_)),
104 retractall(visb_svg_object_debug_info(_,_)),
105 retractall(visb_svg_child(_,_)),
106 retractall(visb_svg_child_of_object_from_svg_file(_)),
107 retractall(visb_svg_parent(_,_)),
108 reset_auto_attrs.
109
110 visb_file_is_loaded(JSONFile) :-
111 visb_file_is_loaded(JSONFile,_,true).
112 visb_file_is_loaded(JSONFile,SVGFile,AllowEmpty) :-
113 visb_file_loaded(JSONFile,_,_),
114 (visb_svg_file(_,SVGFile,_,_,_) -> true
115 ; visb_empty_svg_box_height_width(_,_,_) -> SVGFile = ''
116 ; user_has_defined_visb_objects -> SVGFile = ''
117 ; JSONFile='' ->
118 AllowEmpty=true,
119 add_warning(visb_visualiser,'No VISB_SVG_FILE or VISB_SVG_OBJECTS specified in DEFINITIONS',''),
120 % Note: warning also generated below No VisB JSON file is specified and no VISB_SVG_OBJECTS were created
121 SVGFile = ''
122 ; add_warning(visb_visualiser,'No SVG file or objects specified for VisB file:',JSONFile),
123 AllowEmpty=true,
124 SVGFile = ''
125 ).
126
127 no_svg_available :-
128 \+ user_has_defined_visb_objects,
129 no_svg_file_available,
130 \+ visb_empty_svg_box_height_width(_,_,_). % no SVG box provided
131
132 no_svg_file_available :- (visb_svg_file(_,SVGFile,_,_,_) -> SVGFile='' ; true).
133 %svg_file_available :- \+ no_svg_file_available.
134
135 :- use_module(probsrc(state_space),[current_state_id/1,
136 current_state_corresponds_to_setup_constants_b_machine/0]).
137 visb_current_state_can_be_visualised :-
138 %visb_file_is_loaded(_), % no longer checked; Tcl/Tk will automatically load VisB file if required
139 (b_or_z_mode -> current_state_corresponds_to_setup_constants_b_machine
140 ; \+ current_state_id(root)
141 ).
142
143 :- use_module(probsrc(eventhandling),[register_event_listener/3]).
144 :- register_event_listener(reset_specification,reset_visb,'Reset VisB information').
145 :- register_event_listener(reset_prob,reset_visb,'Reset VisB information').
146
147 %static_check_visb :- % now done when adding items and not storing multiple items
148 % visb_item(ID,Attr,F1,_,_,Pos1), visb_item(ID,Attr,F2,_,Pos2), F1 @< F2,
149 % add_warning(visb_visualiser,'Multiple formulas for SVG identifier and attribute:',ID/Attr,Pos1),
150 % add_message(visb_visualiser,'Location of second formula for:',ID/Attr,Pos2),
151 % fail.
152 % TO DO: some sanity checks on attributes and values
153 static_check_visb :-
154 no_svg_file_available,
155 visb_hover(SVGID,_ID,Attr,_Enter,_Exit,Pos),
156 \+ svg_id_exists(SVGID),
157 ajoin(['Hover for attribute ',Attr,' has unknown trigger-id (can lead to blank visualisation): '],Msg),
158 add_warning(visb_visualiser,Msg,SVGID,Pos),
159 fail.
160 static_check_visb :-
161 no_svg_file_available,
162 visb_hover(SVGID,ID,Attr,_Enter,_Exit,Pos), ID \= SVGID,
163 \+ svg_id_exists(ID),
164 ajoin(['Hover for attribute ',Attr,' has unknown id (can lead to blank visualisation): '],Msg),
165 add_warning(visb_visualiser,Msg,ID,Pos),
166 fail.
167 static_check_visb :-
168 visb_svg_file(SvgFile,_,_,Pos,_),
169 SvgFile \= '',
170 visb_empty_svg_box_height_width(H,W,ViewBox),
171 ajoin(['VISB_SVG_BOX (width=', W, ', height=', H, ', viewBox=', ViewBox,
172 ') cannot be applied to an existing SVG file (use VISB_SVG_CONTENTS for file or put info into SVG file): '],Msg),
173 add_warning(visb_visualiser,Msg,SvgFile,Pos),
174 fail.
175 static_check_visb.
176
177 svg_id_exists(SVGID) :- visb_svg_object(SVGID,_,_StaticAttrList,_,_ExitPos).
178 % --------------------------
179
180 :- use_module(probsrc(tools),[read_string_from_file/2]).
181
182 % store templates as facts, so that compiled version of probcli does not need to find files
183 :- dynamic visb_template_file_codes/2.
184
185 assert_from_template(Filename) :- %formatsilent('Loading ~w~n',[Filename]),
186 absolute_file_name(visbsrc(Filename), Absolute, []),
187 read_string_from_file(Absolute,String),
188 assertz(visb_template_file_codes(Filename,String)).
189
190 :- assert_from_template('visb_template_header.html').
191 :- assert_from_template('visb_template_svg_downloads.html').
192 :- assert_from_template('visb_template_replayTrace.html').
193 :- assert_from_template('visb_template_middle.html').
194 :- assert_from_template('visb_template_footer.html').
195
196 write_visb_template(HtmlFile,Stream) :-
197 visb_template_file_codes(HtmlFile,Codes),
198 format(Stream,'~s~n',[Codes]).
199
200
201 % --------------------------
202
203 :- use_module(probsrc(pref_definitions),[b_get_definition_string_from_spec/3]).
204 get_default_visb_file(Path, Pos) :- get_default_visb_file(Path, _, Pos).
205 get_default_visb_file(Path, Kind, Pos) :- bmachine_is_precompiled,
206 (b_get_definition_string_from_spec('VISB_JSON_FILE', Pos, Path)
207 -> Kind=json % user provided explicit path to VISB JSON file
208 ; b_get_definition_string_from_spec('VISB_DEFINITIONS_FILE', Pos, Path)
209 -> Kind=def % user provided explicit path to VISB DEFINITIONS file
210 % TODO: in future check that file extension is compatible
211 % advantage of VISB_DEFINITIONS_FILE == "File" over "File"
212 % 1) visualisation can be re-loaded without re-loading machine
213 % 2) can be used in TLA+ or similar
214 % 3) avoid clash if definitions file itself defines empty VISB_JSON_FILE
215 % 4) avoid problems with Atelier-B or other tools
216 ; get_default_visb_svg_file(_,Pos)
217 -> Kind=empty, Path='' % user provided SVG file path
218 ; user_has_defined_visb_objects_in_defs
219 -> Kind=empty, Path='' % user provided SVG object definitions
220 ).
221
222 user_has_defined_visb_objects :-
223 (visb_svg_object(_,_,_,_,_) -> true % created in JSON file
224 ; user_has_defined_visb_objects_in_defs).
225
226 user_has_defined_visb_objects_in_defs :-
227 b_sorted_b_definition_prefixed(expression,'VISB_SVG_OBJECTS',_,_).
228
229 % you should do b_absolute_file_name_relative_to_main_machine
230 get_default_visb_svg_file(Path, Pos) :-
231 b_get_definition_string_from_spec('VISB_SVG_FILE', Pos, Path).
232
233
234 % load default VISB_JSON_FILE if it is specified and not already loaded
235 load_default_visb_file_if_necessary :-
236 get_default_visb_file(File, Pos),!,
237 (load_visb_file_if_necessary(File) -> true
238 ; add_error(visb_visualiser,'Could not load VISB_JSON_FILE:',File,Pos)).
239 load_default_visb_file_if_necessary :-
240 (eventb_mode -> true ; add_message(visb_visualiser,'No VISB_JSON_FILE DEFINITION provided')).
241
242 % --------------------------
243 % Loading a JSON VisB file:
244
245
246 :- use_module(probsrc(tools), [get_filename_extension/2]).
247 :- use_module(probsrc(bmachine), [
248 b_load_additional_definitions_file/1,
249 b_load_additional_definitions_from_list_of_facts/1,
250 b_load_additional_definitions_from_term/1
251 ]).
252 load_visb_file(File) :-
253 temporary_set_preference(allow_arith_operators_on_reals,true,Old),
254 call_cleanup((load_visb_file1(File)),
255 reset_temporary_preference(allow_arith_operators_on_reals,Old)).
256 load_visb_file1(File) :-
257 get_filename_extension(File,def), % a .def B definition file
258 !,
259 add_message(visb_visualiser,'Loading VisB DEFINITIONS from B file: ',File),
260 b_load_additional_definitions_file(File),
261 load_visb_file2('',File).
262 load_visb_file1(File) :- load_visb_file2(File,File).
263
264 load_visb_definitions_from_list_of_facts(DefFilePath, ListOfFacts) :-
265 temporary_set_preference(allow_arith_operators_on_reals,true,Old),
266 call_cleanup(
267 (b_load_additional_definitions_from_list_of_facts(ListOfFacts),
268 load_visb_file2('', DefFilePath)),
269 reset_temporary_preference(allow_arith_operators_on_reals,Old)).
270
271 load_visb_definitions_from_term(DefFilePath, Machine) :-
272 temporary_set_preference(allow_arith_operators_on_reals,true,Old),
273 call_cleanup(
274 (b_load_additional_definitions_from_term(Machine),
275 load_visb_file2('', DefFilePath)),
276 reset_temporary_preference(allow_arith_operators_on_reals,Old)).
277
278 load_visb_file2(JsonFile,OrigFileName) :-
279 reset_visb,
280 load_visb_from_definitions(no_inlining,JsonFile), % TODO: pass InlineObjects?
281 start_ms_timer(T),
282 (JsonFile='' % No JSON file
283 -> (get_default_visb_svg_file(SvgFile,DefaultSVGPos)
284 -> (SvgFile='' -> AbsFile=SvgFile % just dummy empty string provided by user
285 ; b_absolute_file_name_relative_to_main_machine(SvgFile,AbsFile)
286 ),
287 add_visb_svg_file(SvgFile,AbsFile,'',DefaultSVGPos)
288 ; check_objects_created(JsonFile) % no JSON and SVG file; check we have created objects
289 )
290 ; add_visb_file(JsonFile,[]),
291 stop_ms_walltimer_with_msg(T,'loading VisB JSON file: ')
292 ),
293 static_check_visb,
294 (OrigFileName = ''
295 -> ModTime=0, ModLocTime=0 % We could get modification time of files with VISB_SVG_OBJECTS, ... DEFINITIONS
296 ; file_property(OrigFileName, modify_timestamp, ModTime),
297 file_property(OrigFileName, modify_localtime, ModLocTime)
298 ),
299 assertz(visb_file_loaded(OrigFileName,ModTime,ModLocTime)).
300
301 check_objects_created(File) :-
302 (visb_svg_object(_,_,_,_,_) -> true
303 ; add_warning(visb_visualiser,'No VisB JSON file is specified and no VISB_SVG_OBJECTS were created:',File)
304 ).
305
306 load_visb_from_definitions(InlineObjects,JsonFileContext) :-
307 start_ms_timer(T),
308 pre_expand_typing_scope([variables_and_additional_defs],ExpandedScope), % do this only once for all defs
309 get_svg_objects_from_definitions(InlineObjects,ExpandedScope,JsonFileContext),
310 (get_SVG_BOX_definition(InlineObjects) -> true ; true), % TODO: also pass scope
311 stop_ms_walltimer_with_msg(T,'extracting VisB infos from DEFINITIONS: ').
312
313 :- use_module(library(file_systems),[file_exists/1, file_property/3]).
314 %:- use_module(library(system),[now/1, datime/2]).
315 load_visb_file_if_necessary(File) :-
316 visb_file_loaded(File,ModTime1,_), % this file is already loaded
317 (File = '' -> true
318 ; file_exists(File),
319 file_property(File, modify_timestamp, ModTime2), % check if it has the same time stamp
320 debug_println(19,visb_json_already_loaded(File,ModTime1,ModTime2)),
321 ModTime1=ModTime2
322 ),
323 !.
324 load_visb_file_if_necessary(File) :- load_visb_file(File).
325
326
327 :- use_module(probsrc(bmachine),[set_additional_filename_as_parsing_default/3, reset_filename_parsing_default/2]).
328
329 add_visb_file(File,LoadedFiles) :- member(File,LoadedFiles),!,
330 add_error(visb_visualiser,'Circular inclusion of JSON files:',[File|LoadedFiles]).
331 add_visb_file(File,_) :- \+ file_exists(File),!,
332 add_error(visb_visualiser,'JSON file does not exist:',File), fail.
333 add_visb_file(File,LoadedFiles) :-
334 debug_format(19,'Loading JSON File: ~w~n',[File]),
335 set_additional_filename_as_parsing_default(File,NewNr,OldNr),
336 call_cleanup(add_visb_file2(File,LoadedFiles), reset_filename_parsing_default(NewNr,OldNr)).
337
338 add_visb_file2(File,LoadedFiles) :-
339 json_parse_file(File,json(List2),[position_infos(true),multiline_strings(true)]),
340 % tools_printing:trace_print(List2),nl,nl,
341 process_json(List2,File),
342 !,
343 (get_attr_with_pos(include,List2,JsonFileTerm,File,Pos)
344 -> check_json_string(JsonFileTerm,include,Pos,JsonFile),
345 absolute_file_name(JsonFile,AF,[relative_to(File)]),
346 formatsilent('Including JSON file: ~w~n',[JsonFile]),
347 add_visb_file(AF,[File|LoadedFiles])
348 ; true
349 ),
350 (LoadedFiles=[], % only check for main included file
351 get_attr_with_pos('model-name',List2,string(ModelName),File,MPos),
352 b_machine_name(Main), Main \= ModelName
353 -> ajoin(['VisB JSON file expects model-name ',ModelName,' instead of: '],MMsg),
354 add_warning(visb_visualiser,MMsg,Main,MPos)
355 ; true
356 ).
357 add_visb_file2(File,_) :-
358 add_error(visb_visualiser,'Unable to process JSON file:',File),
359 fail.
360
361 % process json content of a VisB file:
362 process_json(List,JSONFile) :- visb_svg_file(_,_,_,_,_),!, % we have already determined the SVG file
363 process_json2(List,JSONFile).
364 process_json(List,JSONFile) :-
365 get_attr_with_pos(svg_box,List,json(BoxList),JSONFile,Pos),
366 % json([=(width,400,3-3),=(height,400,3-3)])
367 (get_attr(svg,List,string(SvgFile)) -> SvgFile='' ; true), % check if svg attr empty or non-existant
368 force_get_attr_nr(height,BoxList,H,JSONFile),
369 force_get_attr_nr(width,BoxList,W,JSONFile),!,
370 (get_attr(viewBox,BoxList,string(VB)) -> ViewBox=VB ; ViewBox=''),
371 add_message(visb_visualiser,'Will create empty SVG image with specified dimensions: ',H:W,Pos),
372 assert_visb_empty_svg_box_height_width(H,W,ViewBox,Pos),
373 process_json2(List,JSONFile).
374 process_json(List,JSONFile) :-
375 get_attr_with_pos(svg,List,FileTerm,JSONFile,Pos),
376 check_json_string(FileTerm,svg,Pos,File),
377 (File = '' -> get_default_visb_svg_file(SvgFile, _)
378 ; get_default_visb_svg_file(SvgFile, DPos)
379 -> add_message(visb_visualiser,'Overriding svg file specified in JSON file: ',File,DPos)
380 ; SvgFile=File),
381 !,
382 absolute_file_name(SvgFile,AbsFile,[relative_to(JSONFile)]),
383 add_visb_svg_file(SvgFile,AbsFile,JSONFile,Pos),
384 process_json2(List,JSONFile).
385 process_json(List,JSONFile) :-
386 get_default_visb_svg_file(SvgFile, Pos), SvgFile \= '',
387 !,
388 absolute_file_name(SvgFile,AbsFile,[]), % relative to B machine??
389 add_visb_svg_file(SvgFile,AbsFile,JSONFile,Pos),
390 process_json2(List,JSONFile).
391 process_json(List,JSONFile) :-
392 process_json2(List,JSONFile),
393 (get_SVG_BOX_definition(no_inlining) -> true % TODO: pass (InlineObjects)
394 ; get_attr_with_pos(svg,List,_,JSONFile,Pos) -> % File is empty
395 add_message(visb_visualiser,'Creating empty SVG image. You can add a declaration like "svg_box": {"width":W,"height":H} to specify dimensions in: ',JSONFile,Pos)
396 ; add_warning(visb_visualiser,'Creating empty SVG image. The JSON file contains no svg attribute (pointing to the SVG file): ',JSONFile)
397 ).
398
399 add_visb_svg_file(SvgFile,AbsFile,JSONFile,Pos) :-
400 (SvgFile='' -> add_message(visb_visualiser,'Empty VisB SVG file:',SvgFile,Pos)
401 ; file_exists(AbsFile)
402 -> debug_format(19,'SVG file = ~w (~w)~n',[SvgFile, AbsFile]),
403 file_property(AbsFile, modify_localtime, ModLocTime)
404 ; add_error(visb_visualiser,'The specified VisB SVG file does not exist:',SvgFile,Pos),
405 ModLocTime=unknown
406 ),
407 assertz(visb_svg_file(SvgFile,AbsFile,JSONFile,Pos,ModLocTime)).
408
409 process_json2(List,JSONFile) :-
410 process_json_definitions(List,JSONFile),
411 process_json_items(List,JSONFile),
412 process_json_events(List,JSONFile),
413 process_json_new_svg_objects(List,JSONFile).
414
415 :- use_module(probsrc(tools_strings),[ajoin/2]).
416 check_json_string(Term,_,_,Atom) :- Term = string(Atom), atom(Atom), !.
417 check_json_string(Term,Attr,Pos,_) :- !,
418 ajoin(['Illegal JSON attribute ',Attr,', expected a JSON string:'],Msg),
419 add_error(visb_visualiser,Msg,Term,Pos),fail.
420 % ----------------
421
422 % B definitions that can help write items, events more compactly
423 process_json_definitions(List,File) :-
424 get_attr(definitions,List,array(Defs)),!,
425 length(Defs,Len),
426 formatsilent('VisB Definitions: ~w~n',[Len]),
427 maplist(process_json_definition(File),Defs).
428 process_json_definitions(_,_File).
429
430 % VisB items which modify attributes of SVG objects
431 process_json_items(List,File) :-
432 get_attr(items,List,array(Items)),!,
433 length(Items,Len),
434 formatsilent('VisB Item declarations: ~w~n',[Len]),
435 maplist(process_visb_json_item(File),Items).
436 process_json_items(_,File) :- \+ visb_special_definition(visb_updates,_,_,_,_,_),!,
437 add_message(visb_visualiser,'The JSON file contains no items: ',File).
438 process_json_items(_,_).
439
440 % VisB events which react to clicks on SVG objects and display hovers
441 process_json_events(List,File) :-
442 get_attr(events,List,array(Items)),!,
443 length(Items,Len),
444 formatsilent('VisB Event declarations: ~w~n',[Len]),
445 maplist(process_json_event(File),Items).
446 process_json_events(_,_).
447
448 % VisB additional SVG objects added to SVG file
449 process_json_new_svg_objects(List,File) :-
450 get_attr(svg_objects,List,array(Items)),!,
451 length(Items,Len),
452 formatsilent('VisB additional svg_objects declarations: ~w~n',[Len]),
453 maplist(process_json_svg_object(File),Items).
454 process_json_new_svg_objects(List,File) :-
455 get_attr_with_pos(objects,List,array(Items),File,Pos),!,
456 add_warning(visb_visualiser,'Use "svg_objects" attribute instead of "objects" in: ',File,Pos),
457 maplist(process_json_svg_object(File),Items).
458 process_json_new_svg_objects(_,_).
459
460 :- use_module(probsrc(custom_explicit_sets),[try_expand_custom_set_with_catch/3,
461 is_custom_explicit_set/1, is_set_value/2]).
462 % evaluate all VISB_SVG_OBJECTS... DEFINITIONS and try and extract SVG objects
463 % this must be a set of records with at least id and svg_class field
464 get_svg_objects_from_definitions(InlineObjects,ExpandedScope,_) :-
465 find_and_eval_visb_DEFINITION('VISB_SVG_OBJECTS', visb_objects, SVG_ID, AttrList, Desc, DefName,
466 _DefPos, EvalPos, InlineObjects, allow_separation, ExpandedScope),
467 %formatsilent('Generating new SVG object ~w with attrs ~w~n',[SVG_ID,AttrList]),
468 add_visb_object_from_definition(visb_objects, SVG_ID, AttrList, Desc, DefName, EvalPos),
469 fail.
470 get_svg_objects_from_definitions(InlineObjects,ExpandedScope,_) :-
471 find_and_eval_visb_DEFINITION('VISB_SVG_EVENTS', visb_events, SVG_ID, AttrList, Desc, DefName,
472 _DefPos, EvalPos, InlineObjects, no_separation, ExpandedScope),
473 add_visb_object_from_definition(visb_events, SVG_ID, AttrList, Desc, DefName, EvalPos),
474 fail.
475 get_svg_objects_from_definitions(InlineObjects,ExpandedScope,_) :-
476 find_and_eval_visb_DEFINITION('VISB_SVG_HOVERS', visb_hovers, SVG_ID, AttrList, Desc, DefName,
477 _DefPos, EvalPos, InlineObjects, no_separation, ExpandedScope),
478 add_visb_hovers_from_definition(SVG_ID, AttrList, Desc, DefName, EvalPos),
479 fail.
480 get_svg_objects_from_definitions(_InlineObjects,ExpandedScope,JsonFileContext) :- % VISB_SVG_UPDATES
481 precompile_svg_object_updates(ExpandedScope,JsonFileContext).
482
483 % example definition VISB_SVG_HOVERS == rec(`id`:"myid", stroke:"black", stroke_exit:"gray");
484 % a hovers field inside VISB_SVG_OBJECTS can be something like:
485 % rec(.... hovers: (rec(class:"train-hover"),rec(trigger_id:"track_polyline",class:"train-hover")), ...)
486 % also used, e.g., as attribute in VISB_SVG_OBJECTS
487 add_visb_hovers_from_definition(SVG_ID,AttrList, Desc, DefName, DefPos) :-
488 select(svg_attribute(hovers,Hovers),AttrList,AttrList2),
489 !,
490 (AttrList2=[] -> true ; add_warning(visb_visualiser,'Unknown extra hover attributes:',AttrList2,DefPos)),
491 flex_member(Record,Hovers,DefName,DefPos),
492 (get_VISB_record_fields(Record,Fields) -> true
493 ; add_warning(visb_visualiser,'VisB hovers field value is not a record of SVG attributes: ',Record,DefPos),fail),
494 include_maplist(extract_attribute_from_record(DefPos),Fields,HoverAttrList),
495 add_visb_object_from_definition(visb_hovers, SVG_ID, HoverAttrList, Desc, DefName, DefPos).
496 add_visb_hovers_from_definition(SVG_ID,AttrList, Desc, DefName, DefPos) :-
497 add_visb_object_from_definition(visb_hovers, SVG_ID, AttrList, Desc, DefName, DefPos).
498
499
500 % add a VisB record object from a HOVER or OBJECT definition:
501 add_visb_object_from_definition(visb_objects,SVG_ID, AttrList, Desc, DefName, DefPos) :- !,
502 (select(svg_attribute(svg_class,SVG_Class),AttrList,AttrList2)
503 -> true % maybe we should call svg_class svg_shape and
504 % allow html_tag for children of foreignObject
505 ; add_warning(visb_visualiser,'SVG objects have no svg_class field: ',DefName,DefPos),
506 fail
507 ),
508 assert_visb_svg_object(SVG_ID,SVG_Class,AttrList2,Desc,DefName,DefPos).
509 add_visb_object_from_definition(visb_hovers,SVG_ID, AttrList, _Desc, _DefName, DefPos) :- !,
510 (select(svg_attribute(trigger_id,TriggerID),AttrList,AttrList2) -> true
511 ; select(svg_attribute('trigger-id',TriggerID),AttrList,AttrList2) -> true
512 ; TriggerID = SVG_ID, AttrList2=AttrList),
513 member(svg_attribute(Attr,EnterVal),AttrList2), % will backtrack for every SVG attribute
514 \+ get_exit_attribute_name(_,Attr), % it is not an exit attribute
515 get_exit_attribute_name(Attr,AttrExitName),
516 (member(svg_attribute(AttrExitName,ExitVal), AttrList2) -> true % user specified exit value explicitly
517 ; visb_svg_object(SVG_ID,_,StaticAttrList,_,ExitPos)
518 -> (member(svg_attribute(Attr,ExitVal),StaticAttrList) -> true % use value specified in VISB_SVG_OBJECTS
519 ; default_attribute_value(Attr,ExitVal)
520 -> add_message(visb_visualiser,'Assuming default hover exit value for attribute: ',Attr,DefPos)
521 ; Attr = 'svg_class'
522 -> add_warning(visb_visualiser,
523 'svg_class cannot be set in hover for: ',SVG_ID,ExitPos),
524 ExitVal=EnterVal
525 ; (Attr = hover ; Attr = hovers) ->
526 add_error(visb_visualiser,
527 'Only provide SVG attributes here; no need to wrap them in this attribute:',Attr,DefPos),fail
528 ; add_warning(visb_visualiser,
529 'No static (exit) value can be retrieved for hover for attribute (be sure to define a static value for this attribute in a VISB_SVG_OBJECT definition): ',Attr,ExitPos),
530 ExitVal=EnterVal
531 )
532 ; ajoin(['No VISB_SVG_OBJECT for id ',SVG_ID,' and no value for ',AttrExitName,
533 '; cannot retrieve hover exit value for attribute: '],Msg),
534 add_warning(visb_visualiser,Msg,Attr,DefPos),
535 fail %ExitVal=EnterVal
536 ),
537 assert_visb_hover(TriggerID,SVG_ID,Attr,EnterVal,ExitVal,DefPos).
538 add_visb_object_from_definition(visb_events,SVG_ID, AttrList, _Desc, DefName, DefPos) :- !,
539 ( select(svg_attribute(event,Event),AttrList,AttrList1) -> true
540 ; select(svg_attribute(events,Events),AttrList,AttrList1) -> % we have events attributes with multiple events
541 flex_member(EvVal,Events,DefName,DefPos),
542 extract_attr_value(event,EvVal,Event,DefPos)
543 ; AttrList = [_|_], % at least one other attribute than id; otherwise it may stem from separating VISB_SVG_OBJECTS
544 add_warning(visb_visualiser,'Missing event attribute in VisB definition: ',DefName,DefPos),
545 fail
546 ),
547 (select(svg_attribute(predicate,Pred),AttrList1,AttrList2) -> Preds=[Pred]
548 ; member(P,[preds,predicates]),
549 select(svg_attribute(P,Pred),AttrList1,AttrList2)
550 -> Preds=[Pred], add_warning(visb_visualiser,'Use predicate as attribute for VisB events instead of: ',P,DefPos)
551 ; Preds=[], AttrList2=AttrList1
552 ),
553 EnableItems=[],
554 maplist(process_remaining_attributes(DefName,DefPos),AttrList2),
555 % TODO extract from AttrList2: visb_enable_item(SvgID,Attr,EnabledValExpr,DisabledValExpr,PosAttr)
556 (error_manager:extract_file_number_and_name(DefPos,_,File) -> true ; File='?'),
557 PredPos = DefPos, %TODO: improve
558 add_visb_event(SVG_ID,Event,Preds,[],EnableItems,File,DefPos,PredPos,[]).
559 add_visb_object_from_definition(SpecialClass,_, _, _, _DefName, DefPos) :-
560 add_warning(visb_visualiser,'Unknown special class, cannot add VisB objects for definition: ',SpecialClass,DefPos).
561
562 % for hovers allow to explicitly specify exit value, in case the SVG object comes from an SVG file
563 get_exit_attribute_name(Attr,ExitAttr) :- atom_concat(Attr,'_exit',ExitAttr).
564
565 process_remaining_attributes(DefName,DefPos,svg_attribute(hover,_)) :- !,
566 add_warning(visb_visualiser,'Attribute hover not supported here (use separate VISB_SVG_HOVERS definition): ',DefName,DefPos).
567 process_remaining_attributes(DefName,DefPos,svg_attribute(hovers,_)) :- !,
568 add_warning(visb_visualiser,'Attribute hovers not supported here (use separate VISB_SVG_HOVERS definition): ',DefName,DefPos).
569 process_remaining_attributes(_,DefPos,Attr) :-
570 add_warning(visb_visualiser,'Unrecognised attribute in VISB_SVG_EVENTS definition: ',Attr,DefPos).
571
572
573 default_attribute_value(fill,black). % is remove for animate, ...
574 default_attribute_value(opacity,1).
575 default_attribute_value('stop-dasharray',none).
576 default_attribute_value('stop-opacity',1).
577 default_attribute_value('stroke-opacity',1).
578 default_attribute_value('stroke-width','1px').
579 default_attribute_value(stroke,none).
580 default_attribute_value(transform,none).
581 default_attribute_value(visibility,visible).
582
583 % is called in process_json when no SVG file specified
584 % VISB_SVG_BOX == rec(width:1000,height:1000,viewBox:"minx miny w h"),
585 get_SVG_BOX_definition(InlineObjects) :-
586 get_and_eval_special_definition('VISB_SVG_BOX','VISB_SVG_BOX',visb_box,DefPos,ResValue,InlineObjects),
587 (ResValue=(BH,BW) -> ViewBox=''
588 ; get_VISB_record_fields(ResValue,Fields),
589 select(field(height,BH),Fields,F1),
590 select(field(width,BW),F1,F2)
591 -> (select(field(viewBox,VBVal),F2,F3)
592 -> (VBVal=string(VB) -> ViewBox=VB
593 % Viewbox is "mx my w h" string, ie: minimum_x, minimum_y, width and height
594 ; VBVal = rec(VBFields)
595 -> (get_view_box_rec(VBFields,DefPos,ViewBox) -> true
596 ; ViewBox='',
597 add_warning(visb_visualiser,'VISB_SVG_BOX viewBox record has illegal fields (expected minx miny width height):',VBVal,DefPos))
598 ; add_warning(visb_visualiser,'VISB_SVG_BOX viewBox is not a string ("minx miny width height") or record:',VBVal,DefPos),
599 ViewBox=''
600 )
601 ; ViewBox='', F3=F2
602 ),
603 (F3=[] -> true
604 ; add_warning(visb_visualiser,'VISB_SVG_BOX unknown attributes (not height, width, viewBox): ',F2,DefPos))
605 ; add_error(visb_visualiser,'Ignoring VISB_SVG_BOX, must be record or pair of integers (height,width):',ResValue,DefPos)),
606 (get_number_from_bvalue(BH,H) -> true
607 ; add_error(visb_visualiser,'VISB_SVG_BOX Height is not a number:',ResValue,DefPos)),
608 (get_number_from_bvalue(BW,W) -> true
609 ; add_error(visb_visualiser,'VISB_SVG_BOX Width is not a number:',ResValue,DefPos)),
610 !,
611 assert_visb_empty_svg_box_height_width(H,W,ViewBox,DefPos).
612
613 get_view_box_rec([field(height,VH),field(minx,MXH),field(miny,MYH),field(width,VW)],DefPos,ViewBoxString) :-
614 (get_number_from_bvalue(VH,Height) -> true
615 ; add_error('VISB_SVG_BOX viewBox\'height is not a number:',VH,DefPos),fail),
616 (get_number_from_bvalue(VW,Width) -> true
617 ; add_error('VISB_SVG_BOX viewBox\'width is not a number:',VH,DefPos),fail),
618 (get_number_from_bvalue(MXH,MinX) -> true
619 ; add_error('VISB_SVG_BOX viewBox\'minx is not a number:',VH,DefPos),fail),
620 (get_number_from_bvalue(MYH,MinY) -> true
621 ; add_error('VISB_SVG_BOX viewBox\'miny is not a number:',VH,DefPos),fail),
622 ajoin([MinX,' ',MinY,' ', Width,' ',Height],ViewBoxString).
623
624
625 assert_visb_empty_svg_box_height_width(H,W,_ViewBox,Pos) :-
626 retract(visb_empty_svg_box_height_width(OldH,OldW,_)),
627 (OldH,OldW) \= (H,W),
628 add_message(visb_visualiser,'Overriding VisB SVG_BOX default dimensions: ',(OldH,OldW),Pos),
629 fail.
630 assert_visb_empty_svg_box_height_width(H,W,ViewBox,_Pos) :-
631 %add_message(visb_visualiser,'Setting VisB SVG_BOX default dimensions: ',(H,W,ViewBox),Pos),
632 assert(visb_empty_svg_box_height_width(H,W,ViewBox)).
633
634 :- use_module(probsrc(bsyntaxtree), [get_texpr_pos/2]).
635 :- use_module(probsrc(bmachine),[b_sorted_b_definition_prefixed/4, b_get_typed_definition/3]).
636 % find DEFINITION with given prefix in name, evaluate it and return SVG_ID and attribute list:
637 % AllowSep = allow_seperation means that the record fields can be separated into static objects and dynamic updates
638 % and only static ones will be retained (dynamic ones dealt with later)
639 find_and_eval_visb_DEFINITION(DEFPREFIX, Kind, SVG_ID, AttrList,Desc, DefName, DefPos,EvalPos,
640 InlineObjects,AllowSep,ExpandedScope) :-
641 ( b_sorted_b_definition_prefixed(expression,DEFPREFIX,DefName,DefPos),
642 if(b_get_typed_definition(DefName,ExpandedScope,Body),true,
643 (add_message(visb_visualiser,'Ignoring VisB DEFINITION due to errors: ',DefName),fail))
644 ; special_backup(DEFPREFIX,Kind),
645 % also look at stored definitions (e.g., from static/dynamic separation of VISB_SVG_OBJECTS)
646 visb_special_definition(Kind,DefName,_Type,Body,_Class,DefPos)
647 ),
648 set_error_context(visb_error_context(definition,DefName,'all_attributes',DefPos)),
649 call_cleanup((get_typed_static_definition_with_constants_state(DefName,Body,
650 ResBody,DefPos,ConstState,InlineObjects,AllowSep),
651 (get_texpr_pos(ResBody,Pos0) -> true ; Pos0=DefPos), % this could be a part of the full definition body
652 get_visb_DEFINITION_svg_object(Kind,DefName,ResBody,Pos0,ConstState,SVG_ID,AttrList,Desc,EvalPos)),
653 clear_error_context).
654
655 special_backup('VISB_SVG_HOVERS',visb_hovers).
656
657 % evaluate a typed body expressions evaluating to a record or set of records
658 % and translate into SVG attribute lists:
659 get_visb_static_svg_object_for_typed_expr(Kind,DefName,Body,DefPos,SVG_ID,AttrList,Desc,InnerPos) :-
660 AllowSep=no_separation,
661 Inline=no_inlining,
662 get_typed_static_definition_with_constants_state(DefName,Body,ResBody,DefPos,ConstState,Inline,AllowSep),
663 get_visb_DEFINITION_svg_object(Kind,DefName,ResBody,DefPos,ConstState,SVG_ID,AttrList,Desc,InnerPos).
664
665
666 flatten_couple(b(couple(A,B),_,_)) --> !,flatten_couple(A),flatten_couple(B).
667 % we could also flatten union(A,B), but at the risk of duplicate warnings when the same element occurs in A and B
668 flatten_couple(A) --> [A].
669
670 get_typed_static_definition_with_constants_state(DefName,Body,ResBody,DefPos,ConstantsState,InlineObjects,AllowSep) :-
671 flatten_couple(Body,TupleList,[]),
672 % the VISB_SVG_OBJECT definition may consist of a tuple (Obj1,Obj2,...) to allow grouping
673 (TupleList = [_,_|_]
674 -> add_debug_message(visb_visualiser,'Decomposed VisB definition body tuple:',DefName,DefPos)
675 ; true),
676 nth1(DefNr,TupleList,TupleBody),
677 (get_texpr_pos(TupleBody,TuplePos) -> true ; TuplePos=DefPos),
678 get_typed_static_definition_with_constants_state3(DefName,DefNr,TupleBody,ResBody,TuplePos,
679 ConstantsState,InlineObjects,AllowSep).
680 get_typed_static_definition_with_constants_state3(DefName,DefNr,Body,ResBody,DefPos,ConstantsState,InlineObjects,AllowSep) :-
681 determine_type_of_visb_formula(Body,TIds,Class),
682 debug_format(19,'Detected VisB DEFINITION ~w (~w)~n',[DefName,Class]),
683 (%Class=requires_variables, % now also useful if event field present
684 AllowSep=allow_separation, % allowed for VISB_SVG_OBJECTS
685 if(separate_into_static_and_dynamic_part(DefName,DefNr,Body,StaticBody,DynamicBody,EventBody,HoverBody),
686 true,
687 (get_texpr_type(Body,Type),
688 (contains_events_or_hovers_field(Type)
689 -> add_warning(visb_visualiser,'Static/Dynamic separation failed for (required for events or hovers): ',DefName,DefPos)
690 % VISB_SVG_OBJECT definition contains events/hovers and as such requires separation; which failed here
691 ; add_debug_message(visb_visualiser,'Static/Dynamic separation failed or not useful for: ',DefName,DefPos)
692 ),
693 fail)),
694 determine_type_of_visb_formula(StaticBody,SIds,SClass),
695 get_unique_initial_state_for_visb(SClass,DefName,DefPos,SIds,ConstantsState)
696 -> Separated=true, ResBody=StaticBody,
697 add_debug_message(visb_visualiser,'Automatically separated fields into static and dynamic: ',DefName,DefPos),
698 %write('STATIC: '),translate:print_bexpr(StaticBody),nl, write('DYNAMIC: '),translate:print_bexpr(DynamicBody),nl,
699 assert_visb_udpate_def_body(visb_updates,DefName,DynamicBody,DefPos),
700 add_visb_events_from_def_body(visb_events,DefName,EventBody,DefPos),
701 assert_visb_udpate_def_body(visb_hovers,DefName,HoverBody,DefPos) % needs to be asserted so that it can be evaluated after svg objects have been created to extract exit value
702 ; get_unique_initial_state_for_visb(Class,DefName,DefPos,TIds,ConstantsState)
703 -> ResBody=Body
704 ; ResBody=Body,
705 (Class=requires_constants ->
706 get_texpr_ids(TIds,Ids),
707 % we could check if values of Ids are identical in all constants solutions
708 (is_concrete_constants_state_id(_)
709 -> BMsg='multiple solutions for used constants exist: '
710 ; BMsg='but no constants were found or setup yet: '
711 ),
712 ajoin(['DEFINITION ',DefName, ' requires constants but ',BMsg],Msg),
713 (get_a_constants_state(ConstantsState,StateID,InlineObjects)
714 -> (member(CstID,Ids),
715 other_constant_value_exists_for(CstID,ConstantsState,StateID)
716 -> add_warning(visb_visualiser,Msg,CstID,DefPos)
717 ; ajoin(['DEFINITION ',DefName,
718 ' requires constants and all SETUP_CONSTANTS solutions have same value thus far: '],Msg2),
719 % constraint-based checks or execute by predicate could later create others !
720 add_message(visb_visualiser,Msg2,Ids,DefPos)
721 )
722 ; add_error(visb_visualiser,Msg,Ids,DefPos), ConstantsState=[]
723 )
724 ; ConstantsState=[]
725 )
726 ),
727 (Class=requires_variables, Separated=false
728 -> get_texpr_ids(TIds,AIds),
729 include(b_is_variable,AIds,VIds),
730 ajoin_with_sep(VIds,',',SVids),
731 (get_preference(visb_allow_variables_for_objects,false)
732 -> ajoin(['Ignoring DEFINITION which requires variables ',SVids,': '],WMsg),
733 add_warning(visb_visualiser,WMsg,DefName,DefPos),fail
734 ; ConstantsState=[]
735 -> add_warning(visb_visualiser,'Ignoring DEFINITION which requires variables, could not find unique initial state: ',DefName,DefPos),fail
736 ; ajoin(['DEFINITION requires variables ',SVids,
737 '; exporting history to HTML may not work correctly: '],WMsg),
738 add_message(visb_visualiser,WMsg,DefName,DefPos)
739 )
740 ; true).
741
742
743 :- use_module(probsrc(bsyntaxtree), [create_couple/2, create_couple/3]).
744 % separate/split/filter VISB_SVG_OBJECTS definitions into a static part and a dynamic part depending on variables
745 % (aka updates/items)
746 separate_into_static_and_dynamic_part(DefName,DefNr,Body,StaticBody,DynamicBody,EventBody,HoverBody) :-
747 separate_static_dyn_aux(DefName,DefNr,[],[],Body,StaticBody,DynamicBody,EventBody,HoverBody).
748
749
750 :- use_module(probsrc(state_space),[ time_out_for_node/3]).
751 :- use_module(probsrc(specfile),[ translate_operation_name/2]).
752 :- use_module(probsrc(bsyntaxtree),[replace_ids_by_exprs/4]).
753 rewrite_expression(let_expression(Ids,Exprs,Body),NewBody) :-
754 % currently we cannot process LET's here, expand them
755 replace_ids_by_exprs(Body,Ids,Exprs,NewBody). % see also expand_all_lets/2
756
757 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,Path,b(Expr,_Type,_Info), Static,Dynamic,Event,Hover) :-
758 rewrite_expression(Expr,NewExpr),!,
759 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,Path,NewExpr, Static,Dynamic,Event,Hover).
760 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,Path,b(couple(A,B),_,_Info),
761 StaticCouple,DynamicCouple,EventCouple,HoverCouple) :- !,
762 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,[0|Path],A,SA,DA,EA,HA),
763 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,[1|Path],B,SB,DB,EB,HB),
764 create_couple(SA,SB,StaticCouple),
765 create_couple(DA,DB,DynamicCouple),
766 create_couple(EA,EB,EventCouple),
767 create_couple(HA,HB,HoverCouple).
768 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,Path,TExpr,
769 b(StaticSetComp,set(ST),I),
770 b(DynamicSetComp,set(DT),I),
771 b(EventsSetComp,set(ET),I),
772 b(HoversSetComp,set(HT),I)) :-
773 bsyntaxtree:is_eventb_comprehension_set(TExpr,Ids,Pred,Expr),
774 (OuterQuantifiedIds = []
775 -> add_debug_message(visb_visualiser,'Top-level set comprehensions for VISB: ',Ids,TExpr)
776 ; add_message(visb_visualiser,'Nested set comprehensions for VISB: ',OuterQuantifiedIds,TExpr)
777 ),
778 !,
779 determine_type_of_visb_formula(b(exists(Ids,Pred),pred,[]),SIds,Class),
780 (get_unique_initial_state_for_visb(Class,DefName,Pred,SIds,_)
781 -> true % The predicate must be statically executable
782 ; time_out_for_node(root,O,_Type),
783 translate_operation_name(O,Op) ->
784 ajoin(['Due to TIME_OUT of ',Op,' the comprehension set domain cannot be evaluated: '],Msg),
785 add_warning(visb_visualiser,Msg,Pred,Pred),
786 % TODO: avoid other error messages that will occur after that
787 fail
788 ; add_message(visb_visualiser,'Cannot statically evaluate comprehension set domain: ',Pred,Pred),
789 % at the moment we require the domain to be computable statically for both static/dynamic attributes
790 fail
791 ),
792 append(OuterQuantifiedIds,Ids,NewOuterQuantifiedIds),
793 separate_static_dyn_aux(DefName,DefNr,NewOuterQuantifiedIds,Path,Expr,
794 StaticRec,DynamicRec,EventRec,HoverRec),
795 get_texpr_type(StaticRec,ST),
796 get_texpr_type(DynamicRec,DT),
797 get_texpr_type(EventRec,ET),
798 get_texpr_type(HoverRec,HT),
799 bsyntaxtree:get_texpr_info(TExpr,I),
800 b_ast_cleanup:rewrite_event_b_comprehension_set(Ids,StaticRec,Pred, set(ST), StaticSetComp),
801 b_ast_cleanup:rewrite_event_b_comprehension_set(Ids,DynamicRec,Pred,set(DT), DynamicSetComp),
802 b_ast_cleanup:rewrite_event_b_comprehension_set(Ids,EventRec,Pred,set(ET), EventsSetComp),
803 b_ast_cleanup:rewrite_event_b_comprehension_set(Ids,HoverRec,Pred,set(HT), HoversSetComp).
804 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,Path,b(rec(Fields),_,Info),
805 b(rec(StaticFields),record(SFT),Info), % VISB_OBJECTS (static)
806 b(UpdateRecWithDynamicFields,record(DFT),Info), % VISB_UPDATES (dynamic)
807 b(rec(AllEventFields),record(EFT),Info), % VISB_EVENTS
808 b(rec(AllHoverFields),record(HFT),Info) % VISB_HOVERS
809 ) :- !,
810 split_list(is_visb_event_field,Fields,EventFields,ObjectAndHoverFields),
811 (select(field(hovers,HoverRec),ObjectAndHoverFields,ObjectFields)
812 -> HoverFields = [field(hovers,HoverRec)] % record deconstructed in add_visb_hovers_from_definition
813 ; ObjectFields=ObjectAndHoverFields, HoverFields = []),
814 % maplist(check_field_is_supported(Info),ObjectFields), % will lead to duplicate warning messages, check_visb_update_type e.g., will be called for dynamic updates
815 separate_fields(ObjectFields,StaticFields0,DynamicFields,DefName),
816 (member(field(svg_class,_SVG_Class),StaticFields0) -> true
817 ; member(field(svg_class,SVG_Class),DynamicFields)
818 -> add_warning(visb_visualiser,'SVG svg_class field is not static in: ',DefName,SVG_Class),
819 fail
820 ; add_warning(visb_visualiser,'No svg_class field in: ',DefName,Info),
821 fail
822 ),
823 (member(field(id,SVGID),StaticFields0)
824 -> (DynamicFields \= [] ; EventFields \= [] ; HoverFields \= [] % separation is useful for this record
825 ; Path \= [] % we are part of a couple; maybe other records have a dynamic,event or hover part; so proceed
826 ),
827 StaticFields = StaticFields0,
828 TStatic_SVGID = SVGID
829 ; member(field(id,SVGID),DynamicFields)
830 -> add_warning(visb_visualiser,'SVG id field is not static in: ',DefName,SVGID),
831 fail
832 ; OuterQuantifiedIds = []
833 -> gensym(svg_id,GenID),
834 ajoin(['Generated id ',GenID, ' for SVG object without id field in: '],Msg),
835 add_debug_message(visb_visualiser,Msg,DefName,Info),
836 SVGID = b(string(GenID),string,[]),
837 sort([field(id,SVGID) | StaticFields0],StaticFields)
838 ; % the record is quantified within a set comprehension; we need to compute the ID from OuterQuantifiedIds
839 % it has to be identical for VISB_SVG_OBJECTS and VISB_SVG_UPDATES
840 SVGID = b(ExtFunCall,string,[]),
841 convert_path_to_int(Path,IntPath),
842 PathExpr = b(integer(IntPath),integer,[]),
843 create_couple([b(string(DefName),string,[]),b(integer(DefNr),integer,[]),PathExpr|OuterQuantifiedIds],Tuple),
844 % add DefName and DefNr to avoid clash if other Definition has same quantified ids
845 ExtFunCall = external_function_call('SHA_HASH_HEX',[Tuple]),
846 add_debug_message(visb_visualiser,'Generated SHA_HASH_HEX call for id of SVG objects without id field in: ',DefName,Info),
847 sort([field(id,SVGID) | StaticFields0],StaticFields)
848 ),
849 maplist(get_field_type,StaticFields,SFT),
850 ( (select(field(visibility,VisibExpr),DynamicFields,RestDynamicFields)
851 ; member(field(visibility,VisibExpr),StaticFields0), % the visibility expression is static
852 RestDynamicFields = DynamicFields
853 ),
854 RestDynamicFields = [_|_],
855 \+ hovers_can_set_visibility(HoverFields),
856 (nonvar(TStatic_SVGID), TStatic_SVGID = b(string(Static_SVGID),_,_) % TODO: evaluate properly
857 -> \+ visb_has_visibility_hover(Static_SVGID) % TODO: check no other hover definition added later
858 ; true) % the ID is generated and cannot be accessed by other hovers which could make object visible
859 -> % create IF-THEN-ELSE to avoid evaluating fields when object not visible; also fixes WD issues
860 TRUE = b(boolean_true,boolean,[]),
861 sort([field(id,SVGID),field(visibility,TRUE)|RestDynamicFields],AllDynamicFields),
862 maplist(construct_dummy_value,RestDynamicFields,RestDummyFields),
863 sort([field(id,SVGID),field(visibility,b(boolean_false,boolean,[]))|RestDummyFields],AllDummyFields),
864 create_visibility_check(VisibExpr,VisibilityCond),
865 UpdateRecWithDynamicFields = if_then_else(VisibilityCond,
866 b(rec(AllDynamicFields),record(DFT),Info),
867 b(rec(AllDummyFields),record(DFT),Info)),
868 add_debug_message(visb_visualiser,'Refactoring VisB Record with visibility attribute: ',VisibilityCond)
869 % ,translate:print_bexpr(b(UpdateRecWithDynamicFields,any,[])),nl
870 ; sort([field(id,SVGID)|DynamicFields],AllDynamicFields), % TODO: use kernel_records
871 UpdateRecWithDynamicFields = rec(AllDynamicFields)
872 ),
873 maplist(get_field_type,AllDynamicFields,DFT),
874 sort([field(id,SVGID)|EventFields],AllEventFields), % ditto
875 maplist(get_field_type,AllEventFields,EFT),
876 sort([field(id,SVGID)|HoverFields],AllHoverFields), % ditto
877 maplist(get_field_type,AllHoverFields,HFT).
878 separate_static_dyn_aux(DefName,DefNr,OuterQuantifiedIds,_Path,TEXPR, _, _, _,_) :-
879 ajoin(['Uncovered expression for ',DefName,'-',DefNr,' ',OuterQuantifiedIds],Msg),
880 add_debug_message(visb_visualiser,Msg,TEXPR,TEXPR),fail.
881
882 hovers_can_set_visibility(HoverFields) :- member(field(hovers,Expr),HoverFields),
883 hover_expr_can_set_visibility(Expr).
884
885 hover_expr_can_set_visibility(b(E,_,_)) :- hovers_can_set_visib_aux(E).
886 hovers_can_set_visib_aux(couple(A,B)) :- !, (hover_expr_can_set_visibility(A) ; hover_expr_can_set_visibility(B)).
887 hovers_can_set_visib_aux(rec(Fields)) :- !, member(field(visibility,_),Fields).
888 hovers_can_set_visib_aux(set_extension(L)) :- !, member(E,L), hover_expr_can_set_visibility(E).
889 hovers_can_set_visib_aux(E) :- write(assume_hover_can_set_visibility(E)),nl.
890 % TODO: synchronise with flex_expand and check we cover all relevant cases like partial functions
891
892 :- use_module(probsrc(bsyntaxtree), [create_equality/3]).
893 create_visibility_check(VisibExpr,VisibilityCond) :- get_texpr_type(VisibExpr,string),!,
894 VISIBLE = b(string('visible'),string,[]),
895 create_equality(VisibExpr,VISIBLE,VisibilityCond).
896 create_visibility_check(VisibExpr,VisibilityCond) :-
897 TRUE = b(boolean_true,boolean,[]),
898 create_equality(VisibExpr,TRUE,VisibilityCond).
899
900 :- use_module(probsrc(typing_tools),[any_value_for_type/2]).
901 construct_dummy_value(field(Name,TExpr),field(Name,b(value(DummyValue),Type,[]))) :-
902 get_texpr_type(TExpr,Type),
903 any_value_for_type(Type,DummyValue). % object not visible: do not evaluate expression; just produce dummy value
904
905 % treat path of 0,1 as binary number, but add 1 at end to distinguish [0,0] and [0] or [1,0] and [1,0,0]
906 convert_path_to_int([],1).
907 convert_path_to_int([H|T],Res) :- convert_path_to_int(T,IT),
908 Res is IT*2+H.
909
910 % is the name of a field for events inside a VISB_SVG_OBJECT record
911 is_visb_event_field(field(Name,_)) :- is_visb_event_field_name(Name).
912 is_visb_event_field_name(event).
913 is_visb_event_field_name(events). % tuple or set of events inside VISB_SVG_OBJECTS
914 is_visb_event_field_name(predicate).
915 % is the name of a field for hovers inside a VISB_SVG_OBJECT record
916 %is_visb_hover_field_name(hovers).
917 %is_visb_hover_field_name(items). % enable items
918 %is_visb_hover_field_name(optional). % not needed ?
919 %is_visb_hover_field_name(override). % not needed ?
920
921 % check if the type of a VISB_SVG_OBJECTS expression requires separation for hovers/events
922 contains_events_or_hovers_field(set(X)) :- contains_events_or_hovers_field(X).
923 contains_events_or_hovers_field(couple(A,B)) :-
924 (contains_events_or_hovers_field(A) -> true ; contains_events_or_hovers_field(B)).
925 contains_events_or_hovers_field(record(F)) :- member(field(Name,_),F),
926 (is_visb_event_field_name(Name) -> true ; is_visb_event_field_name(Name)).
927
928 get_field_type(field(Name,Expr),field(Name,T)) :- get_texpr_type(Expr,T).
929
930 % separate fields from a SVG/VISB_SVG_OBJECT record into static part and dynamic update expressions
931 separate_fields([],[],[],_).
932 separate_fields([field(Field,Expr)|T],[field(Field,Expr)|TS],TD,DefName) :-
933 is_static_expr(Expr,Field,DefName),!,
934 separate_fields(T,TS,TD,DefName).
935 separate_fields([field(Field,Expr)|T],[field(Field,Default)|TS],[field(Field,Expr)|TD],DefName) :-
936 requires_static_default_value(Field,Default), !,
937 separate_fields(T,TS,TD,DefName).
938 separate_fields([H|T],TS,[H|TD],DefName) :-
939 separate_fields(T,TS,TD,DefName).
940
941 % fields which require a static default value; here to set up child SVG objects of title
942 % static default values could also be useful for hovers in general?
943 requires_static_default_value(title,b(string('-title-not-set-'),string,[])).
944
945 % virtual SVG attributes which are translated to children tags/objects
946 attribute_automatically_creates_children(title).
947
948 is_static_expr(Expr,Field,DefName) :-
949 determine_type_of_visb_formula(Expr,_TIds,Class), % TODO pass local variables from exists above
950 (Class=requires_nothing -> true
951 ; Class=requires_constants,
952 \+ multiple_concrete_constants_exist, % TODO: check if _TIds have multiple solutions
953 is_concrete_constants_state_id(_) -> true
954 ; ajoin(['Detected dynamic expression for field ',Field,' in ',DefName,': '],Msg),
955 add_debug_message(visb_visualiser,Msg,Expr,Expr),fail
956 ).
957
958 % --------
959
960
961 extract_attribute_from_record(DefPos,field(OrigName,Value),svg_attribute(Name,SVal)) :-
962 opt_rewrite_field_name(OrigName,Name),
963 extract_attribute_value(DefPos,Name,Value,SVal).
964 extract_attribute_from_record(DefPos,F,_) :-
965 add_error(bvisualiser,'Extract SVG attribute failed: ',F,DefPos),fail.
966
967 % extract a value for a particular field Name
968 extract_attribute_value(DefPos,Name,Value,SVal) :-
969 (deconstruct_singleton_set(Name,Value,Element)
970 -> Element \= '$optional_field_absent',
971 extract_attr_value(Name,Element,SVal,DefPos)
972 ; extract_attr_value(Name,Value,SVal,DefPos)
973 ).
974
975 :- use_module(probsrc(specfile), [classical_b_mode/0]).
976
977 % in TLA+ mode optional record fields have {TRUE|->VALUE} rather than VALUE
978 % this can also be useful in B to allow mixing different SVG records in a set
979 % for Alloy mode we may want to also support singleton sets as scalars
980 deconstruct_singleton_set(Name,Set,Res) :-
981 singleton_set(Set,El),
982 detect_partial_records_for_field(Name),
983 (El=(pred_true,El2)
984 -> Val=El2 % TLA2B encoding for optional fields that are present
985 ; Val=El), % Alloy
986 !,
987 Res = Val.
988 deconstruct_singleton_set(Name,[],Res) :-
989 detect_partial_records_for_field(Name),
990 Res = '$optional_field_absent'.
991
992 detect_partial_records_for_field(children) :- !, fail. % children field for groups is a set of ids
993 detect_partial_records_for_field(Name) :-
994 is_svg_number_attribute(Name),!. % sets never sensible as a numerical value
995 detect_partial_records_for_field(Name) :- is_id_or_text_attribute(Name),!. % ditto for ids
996 detect_partial_records_for_field(Name) :- is_svg_color_attribute(Name),!. % ditto for colors
997 detect_partial_records_for_field(_) :-
998 \+ classical_b_mode. % TODO: check that we are in TLA or Alloy mode?
999 % TODO: ensure ProB2 sets animation minor mode for TLA
1000
1001 :- use_module(probsrc(tools),[split_chars/3, safe_number_codes/2,safe_atom_codes/2]).
1002 :- use_module(extrasrc(external_functions_svg),[svg_points/4]).
1003 extract_attr_value(Name,Value,SVal,DefPos) :-
1004 is_svg_number_attribute(Name),!, % we could try and extract svg_class from attribute list above
1005 (get_number_from_bvalue(Value,NrVal)
1006 -> SVal=NrVal % convert to atom?
1007 ; b_value_to_string(Value,SVal),
1008 (is_special_svg_number_form(SVal) -> true
1009 ; atom_codes(SVal,CC),
1010 safe_number_codes(_NrVal,CC) -> true
1011 ; ajoin(['The value of the SVG attribute "',Name,
1012 '" is not a number: '],Msg),
1013 add_warning(visb_visualiser,Msg,SVal,DefPos)
1014 )
1015 ).
1016 extract_attr_value(children,Value,SVal,DefPos) :- !,
1017 (is_set_value(Value,extract_attr_value)
1018 -> (try_expand_custom_set_with_catch(Value,ExpandedSet,extract_attr_value),
1019 maplist(b_value_to_id_string,ExpandedSet,SVal) -> true
1020 ; add_warning(visb_visualiser,'The children attribute should be a finite set of identifiers: ',Value,DefPos),
1021 SVal=[]
1022 )
1023 ; add_warning(visb_visualiser,'The children attribute should be a set of identifiers: ',Value,DefPos),
1024 SVal=[]).
1025 extract_attr_value(points,Value,SVal,DefPos) :- % Class should be polygon or polyline
1026 % automatically translate sequences of pairs of numbers to SVG string format
1027 (Value = [(int(_),_)|_] ; Value = avl_set(node((int(_),_),_,_,_,_))), % TODO: check typing
1028 svg_points(Value,Str,DefPos,no_wf_available),!,
1029 string(SVal)=Str.
1030 extract_attr_value(points,Value,SVal,_DefPos) :- Value = [],!, SVal = ''.
1031 extract_attr_value(visibility,Value,SVal,DefPos) :- !,
1032 % convert TRUE -> visible, FALSE -> hidden
1033 ( Value=pred_true -> TxtVal='visible'
1034 ; Value=pred_false -> TxtVal='hidden'
1035 ; b_value_to_text_string(Value,TxtVal),
1036 (member(TxtVal,[collapse,hidden,visible]) -> true
1037 ; add_warning(visb_visualiser,'Value of SVG attribute "visibility" must be collapse,hidden or visible and not: ',TxtVal,DefPos))
1038 ),
1039 SVal=TxtVal.
1040 extract_attr_value(Name,Value,_,DefPos) :-
1041 is_svg_color_attribute(Name),
1042 illegal_color(Value),
1043 ajoin(['Value of SVG attribute "',Name,
1044 '" is not a colour: ' ],Msg),
1045 add_warning(visb_visualiser,Msg,Value,DefPos),fail.
1046 extract_attr_value(Name,Value,SVal,_) :-
1047 is_id_or_text_attribute(Name),!,
1048 (is_text_attribute(Name)
1049 -> b_value_to_text_string(Value,SVal)
1050 ; b_value_to_id_string(Value,SVal)).
1051 extract_attr_value(Attr,RawValue,ResValue,_DefPos) :- raw_value_attribute(Attr),!, % keep value intact
1052 ResValue = RawValue.
1053 extract_attr_value(_Name,Value,SVal,_) :-
1054 b_value_to_string(Value,SVal).
1055
1056 % do not convert to string; these are treated separately
1057 raw_value_attribute(hovers).
1058 raw_value_attribute(events).
1059
1060 % now checked by check_attribute_type for updates, we could later check strings, currentcolor is allowed
1061 illegal_color(pred_false).
1062 illegal_color(pred_true).
1063 illegal_color([]).
1064 illegal_color(avl_set(_)).
1065 illegal_color([_|_]).
1066 illegal_color(closure(_,_,_)).
1067 illegal_color(term(floating(_))).
1068
1069 % evaluate a DEFINITION to a set of B records representing SVG objects
1070 % returns a possibly refined sub-position corresponding to generated SVG objects as last argument
1071 get_visb_DEFINITION_svg_object(SpecialClass,DefName,Body,_DefPos,ExpandedState,SVG_ID,AttrList,Desc,InnerPos) :-
1072 get_preference(visb_show_debug_infos,true),
1073 bsyntaxtree:is_eventb_comprehension_set(Body,Ids,Pred,Expr),
1074 % try and separate couple in Expr so that we have better position info for source of VISB_SVG_OBJECTS
1075 Body = b(_,Type,II),
1076 Expr = b(couple(_,_),_,_),
1077 !,
1078 couple_member(NewExpr,Expr), % evaluate each part of the couple in isolation, with better position info
1079 get_texpr_pos(NewExpr,InnerPos),
1080 b_ast_cleanup:rewrite_event_b_comprehension_set(Ids,NewExpr,Pred, Type, NewBody),
1081 get_visb_DEF_svg_object_aux(SpecialClass,DefName,b(NewBody,Type,II),InnerPos,ExpandedState,SVG_ID,AttrList,Desc).
1082 get_visb_DEFINITION_svg_object(SpecialClass,DefName,Body,DefPos,ExpandedState,SVG_ID,AttrList,Desc,DefPos) :-
1083 get_visb_DEF_svg_object_aux(SpecialClass,DefName,Body,DefPos,ExpandedState,SVG_ID,AttrList,Desc).
1084
1085 couple_member(TExpr,b(couple(A,B),_,_)) :- !, (couple_member(TExpr,A) ; couple_member(TExpr,B)).
1086 couple_member(TExpr,TExpr).
1087
1088 get_visb_DEF_svg_object_aux(SpecialClass,DefName,Body,DefPos,ExpandedState,SVG_ID,AttrList,Desc) :-
1089 evaluate_visb_formula(Body,DefName,'',ExpandedState,ResValue,DefPos),
1090 flex_expand(ResValue,DefName,DefPos,Expanded,[]),
1091 (Expanded = [] -> add_message(visb_visualiser,'Empty set of SVG object records: ',DefName,DefPos)
1092 ; Expanded =[Record|_] ->
1093 (get_VISB_record_fields(Record,Fs)
1094 % TODO: as we now can have different type of records, check in flex_expand below
1095 -> (member(field(id,_),Fs)
1096 -> true
1097 ; add_message(visb_visualiser,'DEFINITION needs an `id` field if you want to use updates: ',DefName,DefPos)
1098 )
1099 ; ajoin(['DEFINITION ', DefName,' should evaluate to a set of records or tuples of records: '],Msg),
1100 add_warning(visb_visualiser,Msg,Record,DefPos)
1101 )
1102 ),
1103 member(Records,Expanded),
1104 get_VISB_record_fields(Records,Fields),
1105 (select(field(id,VID),Fields,F1)
1106 -> extract_attribute_value(DefPos,id,VID,SVG_ID)
1107 ; gensym(svg_id,SVG_ID), F1=Fields),
1108 (select(field(comment,CC),F1,F2), b_value_to_string(CC,Desc) -> true
1109 ; Desc = '', F2=F1),
1110 (SpecialClass=visb_updates, member(field(visibility,VV),F2),
1111 is_invisible(VV),
1112 \+ visb_has_visibility_hover(SVG_ID) % check for hover which may make object visible
1113 -> AttrList=[svg_attribute(visibility,'hidden')] % do not transmit updates
1114 ; include_maplist(extract_attribute_from_record(DefPos),F2,AttrList0),
1115 exclude(check_unsupported_special_visb_attribute(SpecialClass,DefPos),AttrList0,AttrList),
1116 (select(svg_attribute(svg_class,SVG_Class),AttrList,A2)
1117 -> maplist(check_attribute_is_supported(SVG_Class,DefPos),A2)
1118 ; true)
1119 ).
1120
1121 is_invisible(string(hidden)). % also treat collapse ?
1122 is_invisible(pred_false).
1123
1124 % expand nested tuples/sets to a single list of SVG records (possibly of different types)
1125 flex_expand(Value,DefName,Pos) --> {is_custom_explicit_set(Value)},!,
1126 {try_expand_custom_set_with_catch(Value,ExpandedSet,flex_expand),
1127 (is_custom_explicit_set(ExpandedSet)
1128 -> ajoin(['Could not expand set of SVG object records or tuples thereof for ',DefName,': '],Msg),
1129 add_warning(visb_visualiser,Msg,Value,Pos),
1130 fail
1131 ; true)},
1132 flex_expand(ExpandedSet,DefName,Pos).
1133 flex_expand([],_,_) --> !, [].
1134 flex_expand(L,_DefName,_Pos) --> {L =[(string(_),string(_))|_]}, !,
1135 [L]. % is probably a partial function {"id" |-> ,...}
1136 flex_expand([H|T],DefName,Pos) --> !, flex_expand(H,DefName,Pos), l_flex_expand(T,DefName,Pos).
1137 flex_expand((A,B),DefName,Pos) --> !, flex_expand(A,DefName,Pos), flex_expand(B,DefName,Pos).
1138 flex_expand(T,_,_) --> [T].
1139
1140 l_flex_expand([],_,_) --> !, [].
1141 l_flex_expand([H|T],DefName,Pos) --> !, flex_expand(H,DefName,Pos), l_flex_expand(T,DefName,Pos).
1142 l_flex_expand(T,_,_) --> [T].
1143
1144 flex_member(X,SetPairVal,DefName,Pos) :- flex_expand(SetPairVal,DefName,Pos,List,[]), member(X,List).
1145
1146
1147 % get the fields of a B value record
1148 % also transparently handles alternative representations, like a function from STRING to STRING
1149 get_VISB_record_fields(rec(Fields),Res) :- !, Res=Fields.
1150 get_VISB_record_fields(StringFunction,Fields) :-
1151 is_set_value(StringFunction,get_VISB_record_fields),
1152 try_expand_custom_set_with_catch(StringFunction,Expanded,get_VISB_record_fields),
1153 % TODO: check we have no duplicates
1154 maplist(convert_to_field,Expanded,Fields).
1155 % TODO: support records as generated by READ_XML:
1156 % rec(attributes:{("fill"|->"#90ee90"),("height"|->"360px"),("id"|->"background_rect"),("width"|->"600px"),("x"|->"1px"),("y"|->"2px")},element:"rect",meta:{("xmlLineNumber"|->"3")},pId:5,recId:6)
1157 % for <rect height="360px" x="1px" y="2px" id="background_rect" width="600px" fill="#90ee90"></rect>
1158
1159 convert_to_field((string(FieldName),Value),field(FieldName,Value)).
1160 % TODO: maybe handle enumerated set values as field names
1161
1162
1163 % already extract and type-check VISB_SVG_UPDATES definitions
1164 precompile_svg_object_updates(ExpandedScope,JsonFileContext) :-
1165 b_sorted_b_definition_prefixed(expression,'VISB_SVG_UPDATES',DefName,DefPos),
1166 b_get_typed_definition(DefName,ExpandedScope,TypedExpr),
1167 assert_visb_udpate_def_body(visb_updates,DefName,TypedExpr,DefPos),
1168 add_children_for_visb_update_def_body(TypedExpr,DefName,JsonFileContext),
1169 fail.
1170 precompile_svg_object_updates(_,_).
1171
1172 % assert VisB updates or hovers from B DEFINITION,
1173 % either from VISB_SVG_UPDATES or hovers or dynamic parts of VISB_SVG_OBJECTS:
1174 assert_visb_udpate_def_body(_Kind,DefName,TypedExpr,_DefPos) :-
1175 TypedExpr=b(rec([field(id,_)]),_,Info),!, % can happen when all fields are static
1176 add_debug_message(visb_visualiser,'Useless update/hover (just id field): ',DefName,Info).
1177 assert_visb_udpate_def_body(Kind,DefName,b(couple(A,B),_,_),DefPos) :- !,
1178 % separate couples into individual expressions; in case of WD errors we have more localised errors/problems
1179 assert_visb_udpate_def_body(Kind,DefName,A,DefPos),
1180 assert_visb_udpate_def_body(Kind,DefName,B,DefPos).
1181 assert_visb_udpate_def_body(Kind,DefName,TypedExpr,DefPos) :-
1182 get_texpr_type(TypedExpr,Type),
1183 determine_type_of_visb_formula(TypedExpr,_,FormulaClass),
1184 debug_format(19,'Detected ~w: ~w (~w)~n',[Kind,DefName,FormulaClass]),
1185 assertz(visb_special_definition(Kind,DefName,Type,TypedExpr,FormulaClass,DefPos)),
1186 check_visb_update_type(Kind,Type,DefName,unknown_svg_class,DefPos).
1187
1188 % check if we need to add virtual children for an VISB_SVG_UPDATES body:
1189 % (e.g., for title updates to SVG objects coming from an SVG file)
1190 add_children_for_visb_update_def_body(b(couple(A,B),_,_),DefName,JsonFile) :- !,
1191 (add_children_for_visb_update_def_body(A,DefName,JsonFile)
1192 ;
1193 add_children_for_visb_update_def_body(B,DefName,JsonFile)).
1194 add_children_for_visb_update_def_body(b(rec(Fields),_,_),DefName,JsonFile) :-
1195 select(field(id,TParentId),Fields,F2),!,
1196 is_static_expr(TParentId,id,DefName), % we need a static value to create children for it
1197 TParentId = b(_,_,Info),
1198 evaluate_static_visb_formula(TParentId,DefName,'',[],ResValue,Info),
1199 b_value_to_id_string(ResValue,ParentId),
1200 \+ svg_id_exists(ParentId),
1201 (\+ get_default_visb_svg_file(_,_), % cannot call no_svg_file_available yet
1202 JsonFile = '' % No JSON file to be loaded after, which could add SVG file or objects
1203 -> ajoin(['Unknown VISB_SVG_OBJECT with id ',ParentId,' in: '],Msg),
1204 add_warning(visb_visualiser,Msg,DefName,Info)
1205 ; select(field(title,TTitle),F2,_),
1206 (TTitle = b(string(Title),_,_) -> true ; Title = 'no-title-set'),
1207 get_texpr_pos(TTitle,Pos),
1208 add_virtual_title_object(Title,DefName,Pos,TitleID),
1209 assert_visb_svg_child(ParentId,Pos,TitleID),
1210 assert(visb_svg_child_of_object_from_svg_file(TitleID))
1211 ),
1212 fail.
1213 % TODO: set comprehensions like {x•x:Obj|rec(id=("obj",x), title=....)}
1214 % TODO: support sets and warn when ID is not statically known?
1215
1216 % assert VisB events or hovers from B DEFINITION, from part of VISB_SVG_OBJECTS:
1217 % supporting event attribute and optional predicate attribute
1218 % Kind = visb_events or visb_hovers
1219 add_visb_events_from_def_body(Kind,DefName,Body,DefPos) :-
1220 get_texpr_type(Body,Type),
1221 \+ empty_update_or_hover_type(Type), % at least one more field than just id field
1222 get_visb_static_svg_object_for_typed_expr(Kind,DefName,Body,DefPos,SVG_ID,AttrList,Desc,InnerPos),
1223 add_visb_object_from_definition(Kind, SVG_ID, AttrList, Desc, DefName, InnerPos),
1224 fail.
1225 add_visb_events_from_def_body(_,_,_,_).
1226
1227 empty_update_or_hover_type(record(Fields)) :- !, Fields \= [_,_|_]. % at least one more field than just id field
1228 empty_update_or_hover_type(set(X)) :- !, empty_update_or_hover_type(X).
1229 empty_update_or_hover_type(couple(A,B)) :- !, empty_update_or_hover_type(A), empty_update_or_hover_type(B).
1230
1231 get_svg_object_updates_from_definitions(ExpandedBState,SVG_ID,SvgAttribute,Value,Pos) :-
1232 visb_special_definition(visb_updates,DefName,_Type,BodyTypedExpr,_Class,DefPos),
1233 get_visb_DEFINITION_svg_object(visb_updates,DefName,BodyTypedExpr,DefPos,ExpandedBState,SVG_ID,AttrList,_Desc,Pos),
1234 member(svg_attribute(SvgAttribute,Value),AttrList).
1235
1236 % check types of VisB updates
1237 check_visb_update_type(Kind,Type,DefName,Class,DefPos) :-
1238 get_update_record_fields_type(Type,Fields),
1239 % other types are STRING +-> STRING, ...; this will be checked in get_visb_DEFINITION_svg_object
1240 (memberchk(field('svg_class',_),Fields)
1241 -> add_warning(visb_visualiser,'VisB updates should not set svg_class:',DefName,DefPos)
1242 ; true),
1243 member(field(Name,FieldType),Fields),
1244 (Name = trigger_id ->
1245 (Kind=visb_hovers -> true ;
1246 add_warning(visb_visualiser,'Attribute trigger_id can only be used for hovers:',DefName,DefPos)
1247 )
1248 ; check_attribute_type(FieldType,Name,DefName,Class,DefPos)
1249 ),
1250 fail.
1251 check_visb_update_type(_,_,_,_,_).
1252
1253 % get a fields type list from a type
1254 get_update_record_fields_type(set(X),Fields) :- !,
1255 get_update_record_fields_type(X,Fields).
1256 get_update_record_fields_type(record(Fields),R) :- !, R=Fields.
1257 get_update_record_fields_type(couple(A,B),Fields) :-
1258 (get_update_record_fields_type(A,Fields)
1259 ; get_update_record_fields_type(B,Fields)).
1260
1261 :- use_module(probsrc(translate), [pretty_type/2]).
1262 % check B type of a field for an SVG update or object
1263 check_attribute_type(Type,Name,DefName,Class,DefPos) :- alternative_spelling(Name,AName),!,
1264 check_attribute_type(Type,AName,DefName,Class,DefPos).
1265 check_attribute_type(Type,Name,DefName,Class,DefPos) :- Class \= unknown_svg_class,
1266 check_is_number_attribute(Name,Class,DefPos),!,
1267 illegal_number_type(Type),
1268 ajoin(['Type of field ',Name,' of ', DefName, ' is not a number: '],Msg),
1269 pretty_type(Type,TS),
1270 add_warning(visb_visualiser,Msg,TS,DefPos).
1271 check_attribute_type(Type,Name,DefName,_,DefPos) :-
1272 is_svg_color_attribute(Name),!,
1273 illegal_col_type(Type),
1274 ajoin(['Type of field ',Name,' of ', DefName, ' is not a color: '],Msg),
1275 pretty_type(Type,TS),
1276 add_warning(visb_visualiser,Msg,TS,DefPos).
1277 check_attribute_type(_Type,Name,_DefName,Class,DefPos) :-
1278 check_attribute_name_is_supported(Class,Name,DefPos).
1279
1280 illegal_nr_or_col_type(boolean).
1281 illegal_nr_or_col_type(set(_)).
1282 illegal_nr_or_col_type(seq(_)).
1283 illegal_nr_or_col_type(record(_)).
1284 illegal_nr_or_col_type(couple(A,B)) :- (illegal_nr_or_col_type(A) -> true ; illegal_nr_or_col_type(B)).
1285 % check if couple types can work by concatenating string representations
1286
1287 illegal_col_type(X) :- illegal_nr_or_col_type(X),!.
1288 illegal_col_type(real).
1289 % integer ? or can we map integers to colours using a color scheme like in DOT?
1290
1291 illegal_number_type(X) :- illegal_nr_or_col_type(X),!.
1292 %illegal_number_type(global(_)). % what if we use a global set with weird constants using back-quotes ?
1293
1294 % ----------------
1295
1296 % parse and load an individual JSON VisB item, e.g, :
1297 % { "name":"xscale",
1298 % "value" : "(100.0 / real(TrackElementNumber))"
1299 % }
1300
1301 process_json_definition(File,json(List)) :-
1302 (get_attr_true(ignore,List,File) -> true % ignore this definition
1303 ; process_json_def_lst(File,List)).
1304
1305 :- use_module(probsrc(bsyntaxtree), [get_texpr_type/2]).
1306 process_json_def_lst(File,List) :-
1307 force_del_attr_with_pos(name,List,string(ID),L1,File,NamePos),
1308 force_del_attr_with_pos(value,L1,string(Formula),L2,File,VPos),
1309 debug_format(19,' Processing definition for ~w with value-formula (lines ~w):~w~n',[ID,VPos,Formula]),
1310 !,
1311 set_gen_parse_errors(L2,VPos,GenParseErrors), % treat optional attribute
1312 process_json_definition(ID,NamePos,Formula,VPos,GenParseErrors).
1313 process_json_def_lst(File,List) :- get_pos_from_list(List,File,Pos),
1314 add_error(visb_visualiser,'Illegal VisB Definition:',List,Pos).
1315
1316 % we could also load a classical B Definition file and process its definitions like this:
1317 process_json_definition(ID,NamePos,Formula,VPos,GenParseErrors) :-
1318 atom_codes(Formula,FCodes),
1319 set_error_context(visb_error_context(definition,ID,'value',VPos)),
1320 (b_get_definition_name_with_pos(ID,_Arity,_DefType,_DPos)
1321 -> add_warning(visb_visualiser,'Ignoring VisB definition, DEFINITION of the same name already exists:',ID,NamePos)
1322 ; parse_expr(FCodes,TypedExpr,GenParseErrors)
1323 -> add_visb_json_definition(ID,TypedExpr,VPos)
1324 ; GenParseErrors=false -> formatsilent('Ignoring optional VisB definition for ~w due to error in B formula~n',[ID])
1325 ; add_error(visb_visualiser,'Cannot parse or typecheck VisB formula for definition',ID,VPos)
1326 ),
1327 clear_error_context.
1328
1329 add_visb_json_definition(ID,TypedExpr,VPos) :-
1330 get_texpr_type(TypedExpr,Type),
1331 determine_type_of_visb_formula(TypedExpr,TIds,Class), %write(type(ID,Class,TIds)),nl,
1332 (try_eval_static_def(Class,'static definition', ID,TypedExpr,TIds,StaticValue,VPos)
1333 -> get_texpr_type(TypedExpr,Type),StaticValueExpr = b(value(StaticValue),Type,[]),
1334 assert_visb_json_definition(ID,Type,StaticValueExpr,TIds,Class,VPos)
1335 ; assert_visb_json_definition(ID,Type,TypedExpr,TIds,Class,VPos)
1336 ).
1337
1338 % assert a VisB definition stemming from the JSON definitions section:
1339 assert_visb_json_definition(DefName,Type,TypedExpr,UsedTIds,Class,DefPos) :-
1340 (is_special_visb_def_name(DefName,SpecialClass) -> true ; SpecialClass = regular_def),
1341 assertz(visb_definition(DefName,Type,TypedExpr,Class,DefPos,SpecialClass)),
1342 (SpecialClass \= regular_def
1343 -> formatsilent('Detected special ~w definition ~w (~w)~n',[SpecialClass,DefName,Class]),
1344 add_special_json_definition(SpecialClass,DefName,Type,TypedExpr,UsedTIds,Class,DefPos)
1345 ; true
1346 ).
1347
1348 % register some special definitions, in which a set of objects/hovers/updates can be specified
1349 % by a single definition returning a set of records
1350 add_special_json_definition(visb_updates,DefName,Type,TypedExpr,_,Class,DefPos) :- !,
1351 check_visb_update_type(visb_updates,Type,DefName,Class,DefPos),
1352 assertz(visb_special_definition(visb_updates,DefName,Type,TypedExpr,Class,DefPos)). % will be evaluated later
1353 add_special_json_definition(visb_contents,DefName,Type,TypedExpr,_,Class,DefPos) :- !,
1354 assertz(visb_special_definition(visb_contents,DefName,Type,TypedExpr,Class,DefPos)).
1355 add_special_json_definition(visb_box,DefName,Type,TypedExpr,_,Class,DefPos) :- !,
1356 assertz(visb_special_definition(visb_box,DefName,Type,TypedExpr,Class,DefPos)).
1357 add_special_json_definition(visb_objects,DefName,_Type,TypedExpr,_UsedTIds,_Class,DefPos) :- !,
1358 AllowSep=allow_separation, % TODO: we re-determine the class and used ids below:
1359 get_typed_static_definition_with_constants_state(DefName,TypedExpr,ResBody,DefPos,CS,no_inlining,AllowSep),
1360 (get_visb_DEFINITION_svg_object(visb_objects,DefName,ResBody,DefPos,CS,SVG_ID,AttrList,Desc,InnerPos),
1361 %formatsilent('Adding ~w : ~w (from ~w)~n',[visb_objects,SVG_ID,DefName]),
1362 add_visb_object_from_definition(visb_objects, SVG_ID, AttrList, Desc, DefName, InnerPos),
1363 fail ; true).
1364 add_special_json_definition(SpecialClass,DefName,_Type,TypedExpr,UsedTIds,Class,DefPos) :-
1365 (get_unique_initial_state_for_visb(Class,DefName,DefPos,UsedTIds,ConstantsState) -> true
1366 ; ConstantsState=[]),
1367 get_static_visb_state(ConstantsState,FullState), % add static VisB Defs
1368 (Class=requires_variables,
1369 (get_preference(visb_allow_variables_for_objects,false) ; ConstantsState=[])
1370 -> add_warning(visb_visualiser,'Ignoring VisB definition which requires variables:',DefName,DefPos)
1371 ; get_visb_DEFINITION_svg_object(SpecialClass,DefName,TypedExpr,DefPos,FullState,SVG_ID,AttrList,Desc,InnerPos),
1372 %formatsilent('Adding ~w : ~w (from ~w)~n',[SpecialClass,SVG_ID,DefName]),
1373 add_visb_object_from_definition(SpecialClass, SVG_ID, AttrList, Desc, DefName, InnerPos)
1374 ; true).
1375
1376 is_special_visb_def_name(DefName,visb_updates) :- atom_concat('VISB_SVG_UPDATES',_,DefName).
1377 is_special_visb_def_name(DefName,visb_hovers) :- atom_concat('VISB_SVG_HOVERS',_,DefName).
1378 is_special_visb_def_name(DefName,visb_objects) :- atom_concat('VISB_SVG_OBJECTS',_,DefName).
1379 is_special_visb_def_name(DefName,visb_contents) :- atom_concat('VISB_SVG_CONTENTS',_,DefName).
1380 is_special_visb_def_name(DefName,visb_events) :- atom_concat('VISB_SVG_EVENTS',_,DefName).
1381 is_special_visb_def_name('VISB_SVG_BOX',visb_box).
1382 % TODO: maybe provide VISB_HTML_CONTENTS which appear after the SVG
1383
1384 % evaluate static VisB defs only once or evaluate expressions in svg_objects and loop bounds
1385 eval_static_def(Class,VisBKind,ID,TypedExpr,UsedTIds,StaticValue,VPos) :-
1386 get_unique_initial_state_for_visb(Class,ID,VPos,UsedTIds,ConstantsState),
1387 evaluate_static_visb_formula(TypedExpr,VisBKind,ID,ConstantsState,StaticValue,VPos).
1388
1389 % only evaluate statically if possible; no warnings/messages if not possible (just fail)
1390 try_eval_static_def(requires_variables,_VisBKind,_ID,_TypedExpr,_UsedTIds,_StaticValue,_VPos) :- !,
1391 fail. % do not try to evaluate statically; events will change the variable values anyway
1392 try_eval_static_def(Class,VisBKind,ID,TypedExpr,UsedTIds,StaticValue,VPos) :-
1393 % TODO: disable messages for multiple constants values; just fail
1394 eval_static_def(Class,VisBKind,ID,TypedExpr,UsedTIds,StaticValue,VPos).
1395
1396 % check if a unique constant value exists for a model
1397 get_unique_initial_state_for_visb(requires_nothing,_,_,_,State) :- !, State=[].
1398 get_unique_initial_state_for_visb(Class,DefName,DefPos,_,State) :-
1399 \+ multiple_concrete_constants_exist,
1400 is_concrete_constants_state_id(StateID),!,
1401 (Class=requires_variables
1402 -> get_preference(visb_allow_variables_for_objects,true),
1403 unique_initialisation_id_exists_from(StateID,DefName,DefPos,State)
1404 % Note: variable can still be modified by other events later, e.g., in ProB2-UI
1405 ; visited_expression(StateID,StateTerm),
1406 state_corresponds_to_set_up_constants_only(StateTerm,State)).
1407 get_unique_initial_state_for_visb(requires_constants,DefName,DefPos,Ids,State) :- Ids \= all,
1408 % try and see if all values for Ids are the same; TODO: also support requires_variables
1409 is_concrete_constants_state_id(StateID),!,
1410 visited_expression(StateID,StateTerm),
1411 state_corresponds_to_set_up_constants_only(StateTerm,State),
1412 (member(C,Ids), get_texpr_id(C,CstID),
1413 other_constant_value_exists_for(CstID,State,StateID)
1414 -> ajoin(['Multiple values for constant ',CstID, ' in context of: '],Msg),
1415 add_message(visb_visualiser,Msg,DefName,DefPos),fail
1416 ; true).
1417
1418 get_a_constants_state(State,StateID,inline_objects(SingleStateId)) :-
1419 get_constants_state_id_for_id(SingleStateId,StateID),!,
1420 visited_expression(StateID,StateTerm),
1421 state_corresponds_to_set_up_constants_only(StateTerm,State).
1422 get_a_constants_state(State,StateID,InlineObjects) :-
1423 check_inlining(InlineObjects),
1424 is_concrete_constants_state_id(StateID),!,
1425 visited_expression(StateID,StateTerm),
1426 state_corresponds_to_set_up_constants_only(StateTerm,State).
1427
1428 check_inlining(no_inlining) :- !.
1429 check_inlining(inline_objects(_SingleStateId)) :- !.
1430 check_inlining(X) :- add_internal_error('Invalid inlining value:',check_inlining(X)).
1431
1432 :- use_module(probsrc(store), [lookup_value_for_existing_id/3]).
1433 other_constant_value_exists_for(CstID,State,StateId) :-
1434 lookup_value_for_existing_id(CstID,State,Val1),
1435 is_concrete_constants_state_id(StateId2), StateId2 \= StateId,
1436 visited_expression(StateId2,StateTerm2),
1437 state_corresponds_to_set_up_constants_only(StateTerm2,State2),
1438 lookup_value_for_existing_id(CstID,State2,Val2),
1439 Val2 \= Val1.
1440
1441
1442 unique_initialisation_id_exists_from(FromStateId,DefName,DefPos,State) :-
1443 transition(FromStateId,_,StateID),!,
1444 (transition(FromStateId,_,StateID2),
1445 StateID2 \= StateID
1446 -> ajoin(['Multiple initialisations exists (state ids ',StateID,',',StateID2,') for: '],Msg),
1447 add_message(visb_visualiser,Msg,DefName,DefPos),fail
1448 ; true),
1449 visited_expression(StateID,StateTerm),
1450 state_corresponds_to_initialised_b_machine(StateTerm,State).
1451
1452 parse_expr_for_visb(Formula,JsonList,Pos,TypedExpr) :-
1453 set_gen_parse_errors(JsonList,Pos,GenParseErrors),
1454 parse_expr(Formula,TypedExpr,GenParseErrors).
1455
1456 set_gen_parse_errors(JSonList,Pos,GenParseErrors) :-
1457 (get_attr(optional,JSonList,_)
1458 -> GenParseErrors=false
1459 ; %get_pos_from_list(JSonList,File,Position),
1460 GenParseErrors=gen_parse_errors_for(Pos)).
1461
1462 % ----------------
1463
1464 % parse and load an individual JSON SVG object listed under svg_objects, e.g, :
1465 % {
1466 % "svg_class":"rect",
1467 % "id":"train_rect",
1468 % "x":"0",
1469 % "y":"0",
1470 % "comment":"..."
1471 % },
1472 process_json_svg_object(File,Json) :-
1473 process_repeat(0,Json,File,add_visb_json_svg_object).
1474
1475 add_visb_json_svg_object(File,json(List)) :- get_attr_true(ignore,List,File), !. % ignore this item
1476 add_visb_json_svg_object(File,json(List)) :-
1477 (force_del_attr_with_pos(svg_class,List,string(SVG_Class),L1,File,Pos1) -> true % shape: line, rect, ...
1478 ; infer_svg_class(List,SVG_Class,File,Pos1)
1479 -> add_message(visb_visualiser,'Inferred svg_class: ',SVG_Class,Pos1),L1=List),
1480 force_del_attr(id,L1,string(ID),L2,File),
1481 (del_attr(comment,L2,string(Desc),JsonList3) -> true ; Desc = '', JsonList3=L2),
1482 debug_format(19,' Creating new SVG object ~w with id:~w~n',[SVG_Class,ID]),
1483 add_debug_message(visb_visualiser,'New object: ',ID,Pos1),
1484 % TODO: we could pre-process all attributes not depending on %0, %1, ...
1485 maplist(get_svg_attr(SVG_Class,File),JsonList3,AttrList),
1486 %formatsilent('Adding SVG Object ~w with ID ~w (~w): ~w~n',[SVG_Class,ID,Desc,AttrList]),
1487 assert_visb_svg_object(ID,SVG_Class,AttrList,Desc,'JSON',Pos1),
1488 !.
1489 add_visb_json_svg_object(File,Json) :-
1490 !,
1491 get_pos_from_list(Json,File,Pos),
1492 add_error(visb_visualiser,'Illegal VisB additional SVG object:',Json,Pos).
1493
1494 infer_svg_class(List,line,File,Pos) :- get_attr_with_pos(x1,List,_,File,Pos),!.
1495 infer_svg_class(List,circle,File,Pos) :- get_attr_with_pos(r,List,_,File,Pos),!.
1496 infer_svg_class(List,rect,File,Pos) :- get_attr_with_pos(height,List,_,File,Pos),!.
1497 infer_svg_class(List,rect,File,Pos) :- get_attr_with_pos(width,List,_,File,Pos),!.
1498 infer_svg_class(List,ellipse,File,Pos) :- get_attr_with_pos(rx,List,_,File,Pos),!. % could also be rect
1499 infer_svg_class(List,text,File,Pos) :- get_attr_with_pos(text,List,_,File,Pos),!.
1500 infer_svg_class(List,g,File,Pos) :- get_attr_with_pos(children,List,_,File,Pos),!. % group + foreignObject have children
1501 infer_svg_class(List,use,File,Pos) :- get_attr_with_pos(href,List,_,File,Pos),!. % href can also be used with image, pattern, ...
1502
1503 % assert a new SVG object to be created upon SETUP_CONSTANTS/INITIALISATION:
1504 assert_visb_svg_object(ID,SVG_Class,_AttrList,_Desc,DefName,Pos1) :-
1505 visb_svg_object(ID,_,_,_,_Pos0),!,
1506 ajoin(['SVG object (from ',DefName,', svg_class=',SVG_Class,') with same id already created: '],Msg),
1507 add_warning(visb_visualiser,Msg,ID,Pos1).
1508 assert_visb_svg_object(_ID,_SVG_Class,AttrList,_Desc,_DefName,Pos1) :-
1509 \+ (AttrList=[] ; AttrList=[_|_]),!,
1510 add_error(visb_visualiser,'SVG objects attributes are not a list:',AttrList,Pos1).
1511 assert_visb_svg_object(ID,SVG_Class,AttrList,Desc,DefName,Pos1) :-
1512 check_svg_shape_class(ID,SVG_Class,Pos1),
1513 add_visb_debug_infos(ID,SVG_Class,AttrList,AttrList2,DefName,Pos1),
1514 sort(AttrList2,SAttrList),
1515 get_all_children(SAttrList,Children,RestAttrs,DefName,Pos1),
1516 (Children = [] -> true
1517 ; svg_shape_can_have_children(SVG_Class) -> true % g, foreignObject, HTML tags
1518 ; Children = [C1_ID|_], visb_svg_object(C1_ID,CAttr,_,_,_),
1519 attribute_automatically_creates_children(CAttr) % e.g., title object created for title attribute of ID
1520 -> true
1521 ; add_message(visb_visualiser,'Children attribute only useful for certain SVG classes such as groups (g) or foreignObject or when adding title objects (as tooltips): ',Children,Pos1)
1522 ),
1523 (select(svg_attribute(group_id,ParentGroupId),RestAttrs,RestAttrs2)
1524 -> assert_visb_svg_child(ParentGroupId,Pos1,ID) % register parent group id
1525 ; RestAttrs2=RestAttrs),
1526 compute_auto_attributes(RestAttrs,RestAttrs2,SVG_Class,NewRestAttrs),
1527 assertz(visb_svg_object(ID,SVG_Class,NewRestAttrs,Desc,Pos1)),
1528 maplist(assert_visb_svg_child(ID,Pos1),Children). % add all children
1529
1530 % adapt visb_svg_object to provide developer debug infos, e.g., in title hover messages
1531 add_visb_debug_infos(ID,SVG_Class,AttrList,NewAttrList,DefName,Pos) :- SVG_Class \= title,
1532 get_preference(visb_show_debug_infos,true),
1533 (select(svg_attribute(title,Title),AttrList,RestAttrs) -> true
1534 ; Title='', RestAttrs=AttrList),
1535 !,
1536 extract_span_description_with_opts(Pos,PosStr,
1537 [relative_file_name,compact_pos_info,
1538 inner_context_separator('\n in ','\n at ')]),
1539 %extract_definition_call_stack_desc(Pos,CS), already displayed in inner context
1540 ajoin(['-- VISB_DEBUG_INFO --\nid=',ID, '\nsvg_class=',SVG_Class, '\nsrc=',DefName,'\n', PosStr],DebugInfo),
1541 (Title='' -> NewTitle=DebugInfo ; ajoin([Title,'\n',DebugInfo],NewTitle)),
1542 %format('~nDEBUG::~n~w~n~w~n---~n',[ID,DebugInfo]),
1543 assert(visb_svg_object_debug_info(ID,DebugInfo)),
1544 NewAttrList = [svg_attribute(title,NewTitle)|RestAttrs].
1545 add_visb_debug_infos(_,_,AttrList,AttrList,_,_).
1546
1547 % compute the value of VisB auto attributes, e.g., automatically
1548 % doing a layout of objects in a grid
1549 % TODO: SVG/special_svg_number already supports auto but not for x,y coordinates?
1550 % TODO: try and determine width of object automatically; keep track of auto objects max height per row
1551 % TODO: support cx,cy
1552 compute_auto_attributes([],_,_,[]).
1553 compute_auto_attributes([svg_attribute(Attr,Val)|T],AllAttrs,SVG_Class,
1554 [svg_attribute(Attr,NewVal)|NT]) :-
1555 (Val=auto, compute_auto_attribute(Attr,AllAttrs,SVG_Class,NewVal)
1556 -> true
1557 ; NewVal=Val),
1558 compute_auto_attributes(T,AllAttrs,SVG_Class,NT).
1559
1560 :- dynamic next_auto_x/1, next_auto_y/2.
1561 next_auto_x(0).
1562 next_auto_y(0,10).
1563 reset_auto_attrs :- retractall(next_auto_x(_)),
1564 retractall(next_auto_y(_,_)),
1565 assertz(next_auto_x(0)),
1566 assertz(next_auto_y(0,10)).
1567
1568 get_x_auto_limit(Limit) :- visb_empty_svg_box_height_width(_H,W,_ViewBox),!,
1569 Limit = W. %TODO: inspect viewBox
1570 get_x_auto_limit(400).
1571
1572 compute_auto_attribute(id,_,_,GenID) :- !, gensym(svg_id,GenID).
1573 compute_auto_attribute(Attr,AllAttrs,SVG_Class,Val) :-
1574 auto_compute_x_coordinate(Attr,Kind),!,
1575 retract(next_auto_x(XV)),
1576 (get_width(SVG_Class,AllAttrs,Offset) -> true ; Offset=10),
1577 Padding = 2, % TODO: make customisable
1578 NewXV is XV+Offset+Padding,
1579 get_x_auto_limit(Lim),
1580 (NewXV > Lim
1581 -> NewVal=0, retract(next_auto_y(OldY,YOffset)),
1582 (get_height(SVG_Class,AllAttrs,Offset) -> true ; Offset = 10),
1583 NewY is OldY+YOffset,
1584 assert(next_auto_y(NewY,YOffset))
1585 ; NewVal=NewXV),
1586 assertz(next_auto_x(NewVal)),
1587 (Kind=left -> Val=XV ; Val is XV + Offset/2).
1588 compute_auto_attribute(Attr,AllAttrs,SVG_Class,Val) :- auto_compute_y_coordinate(Attr,Kind),
1589 next_auto_y(YV,_),
1590 (Kind = top -> Val = YV
1591 ; get_height(SVG_Class,AllAttrs,Height) -> Val is YV + Height/2
1592 ; Val is YV+5).
1593
1594 auto_compute_x_coordinate(x,left). % rect, ..
1595 auto_compute_x_coordinate(cx,center). % circle, ellipse
1596 auto_compute_y_coordinate(y,top). % rect, ..
1597 auto_compute_y_coordinate(cy,center). % circle, ellipse
1598
1599 get_width(rect,Attrs,Wid) :- member(svg_attribute(width,Wid),Attrs).
1600 get_width(circle,Attrs,Wid) :- member(svg_attribute(r,Radius),Attrs), Wid is 2*Radius.
1601 get_width(ellipse,Attrs,Wid) :- member(svg_attribute(rx,Radius),Attrs), Wid is 2*Radius.
1602 get_width(line,Attrs,Wid) :- member(svg_attribute(x1,X1),Attrs),
1603 member(svg_attribute(x2,X2),Attrs), Wid is abs(X2-X1).
1604
1605 get_height(rect,Attrs,Wid) :- member(svg_attribute(height,Wid),Attrs).
1606 get_height(circle,Attrs,Wid) :- member(svg_attribute(r,Radius),Attrs), Wid is 2*Radius.
1607 get_height(ellipse,Attrs,Wid) :- member(svg_attribute(ry,Radius),Attrs), Wid is 2*Radius.
1608 get_height(line,Attrs,Wid) :- member(svg_attribute(y1,X1),Attrs),
1609 member(svg_attribute(y2,X2),Attrs), Wid is abs(X2-X1).
1610
1611
1612 % register an SVG ID as child of a group
1613 assert_visb_svg_child(_ParentId,Pos,ChildID) :- visb_svg_child(ChildID,OldParent),!,
1614 ajoin(['SVG object already child of group ',OldParent,': '],Msg),
1615 add_warning(visb_visualiser,Msg,ChildID,Pos).
1616 assert_visb_svg_child(ParentId,Pos,ChildID) :- visb_svg_child(ParentId,ChildID),!, % TODO: full cycle detection
1617 ajoin(['SVG object already parent of group ',ParentId,' (cycle): '],Msg),
1618 add_warning(visb_visualiser,Msg,ChildID,Pos).
1619 assert_visb_svg_child(ParentId,_Pos,ChildID) :-
1620 assertz(visb_svg_child(ChildID,ParentId)),
1621 assertz(visb_svg_parent(ParentId,ChildID)).
1622
1623
1624
1625
1626 :- use_module(probsrc(gensym),[gensym/2]).
1627 % we need to translate a title attribute to a separate title object and add it as a child
1628 % see also post_process_visb_item which dispatches title updates to the child object
1629 get_all_children(SAttrList,Children,Rest,DefName,Pos) :-
1630 select(svg_attribute(title,Title),SAttrList,SList2),!,
1631 add_virtual_title_object(Title,DefName,Pos,TitleID),
1632 Children=[TitleID|TChilds],
1633 get_children_attribute(SList2,TChilds,Rest,Pos).
1634 get_all_children(SAttrList,Children,Rest,_,Pos) :-
1635 % get the children explicitly defined by the user:
1636 get_children_attribute(SAttrList,Children,Rest,Pos).
1637
1638 add_virtual_title_object(Title,DefName,Pos,TitleID) :-
1639 gensym(visb_title,TitleID),
1640 assert_visb_svg_object(TitleID,'title',[svg_attribute(text,Title)],'',DefName,Pos),
1641 add_debug_message(visb_visualiser,'Adding virtual title child object: ',TitleID,Pos).
1642
1643 get_children_attribute(SAttrList,Children,Rest,Pos) :-
1644 select(svg_attribute(children,C),SAttrList,R),!,
1645 (is_list(C) -> Children=C
1646 ; add_warning(visb_visualiser,'Children attribute should be a list (of SVG ids): ',C,Pos),
1647 Children=[]),
1648 Rest=R.
1649 get_children_attribute(SAttrList,[],SAttrList,_).
1650
1651
1652
1653 :- use_module(probsrc(tools_matching), [get_possible_fuzzy_matches_and_completions_msg/3,
1654 get_all_svg_classes/1, is_svg_shape_class/1,
1655 is_html_tag/1, is_html_attribute/1]).
1656
1657
1658 svg_shape_can_have_children(defs).
1659 svg_shape_can_have_children(foreignObject).
1660 svg_shape_can_have_children(g).
1661 svg_shape_can_have_children(pattern).
1662 svg_shape_can_have_children(X) :- is_html_tag(X).
1663
1664
1665 :- use_module(probsrc(tools_matching), [dotshape2svg_class/2]).
1666 % check whether svg_class value seems valid
1667 check_svg_shape_class(ID,Shape,Pos) :-
1668 (is_svg_shape_class(Shape) -> true
1669 ; is_html_tag(Shape) ->
1670 (visb_svg_child(ID,ParentId),
1671 visb_svg_object(ParentId,ParClass,_,_,_),
1672 (is_html_tag(ParClass) -> true ; ParClass=foreignObject)
1673 -> add_debug_message(visb_visualiser,'HTML tag used as svg_class in foreignObject child: ',Shape,Pos)
1674 ; ajoin(['SVG object ', ID, ' has HTML tag as svg_class (and should probably be a child of a foreignObject): '],Msg),
1675 add_message(visb_visualiser,Msg,Shape,Pos) % probably should be child of foreignObject
1676 )
1677 ; dotshape2svg_class(Shape,Class)
1678 -> ajoin(['SVG object ', ID, ' has unknown svg_class (did you mean ',Class,' ?): '],Msg),
1679 add_warning(visb_visualiser,Msg,Shape,Pos)
1680 ; get_all_svg_classes(Classes),
1681 get_possible_fuzzy_matches_and_completions_msg(Shape,Classes,FMsg)
1682 -> ajoin(['SVG object ', ID, ' has unknown svg_class (did you mean ',FMsg,' ?): '],Msg),
1683 add_warning(visb_visualiser,Msg,Shape,Pos)
1684 ; ajoin(['SVG object ', ID, ' has unknown svg_class: '],Msg),
1685 add_message(visb_visualiser,Msg,Shape,Pos)
1686 ).
1687
1688 % get SVG attribute for an svg_object:
1689 get_svg_attr(SVG_Class,File,'='(Attr,AttrVal,Pos),svg_attribute(Attr,Val)) :- !,
1690 construct_prob_pos_term(Pos,File,PosTerm),
1691 get_svg_static_attribute_value(Attr,SVG_Class,PosTerm,AttrVal,Val).
1692 get_svg_attr(_,File,Json,_) :-
1693 get_pos_from_list([Json],File,Position),
1694 add_error(visb_visualiser,'Illegal SVG object attribute',Json,Position),fail.
1695
1696 get_svg_static_attribute_value(Attr,SVG_Class,Pos,AttrVal,Nr) :-
1697 check_is_number_attribute(Attr,SVG_Class,Pos),
1698 \+ is_special_svg_number_form(AttrVal),
1699 !,
1700 (get_number_value(AttrVal,Nr,Attr,Pos) -> true
1701 ; add_error(visb_visualiser,'Illegal number value:',AttrVal,Pos), Nr=0).
1702 get_svg_static_attribute_value(_,_,_,string(Val),Res) :- !, Res=Val.
1703 % for children we get something like array([string(button1_1),string(button1_2)])
1704 get_svg_static_attribute_value(Attr,SVG_Class,Pos,array(List),ResList) :- !,
1705 maplist(get_svg_static_attribute_value(Attr,SVG_Class,Pos),List,ResList).
1706 get_svg_static_attribute_value(_Attr,_,Pos,Val,Val) :-
1707 add_warning(visb_visualiser,'Illegal SVG object attribute value: ',Val,Pos).
1708
1709
1710 % detect special SVG number forms, like 50%
1711 is_special_svg_number_form(string(Atom)) :-
1712 atom_codes(Atom,Codes),
1713 special_svg_number(Codes,[]).
1714
1715 :- use_module(probsrc(self_check)).
1716 :- assert_must_succeed(visb_visualiser:special_svg_number("10%",[])).
1717 :- assert_must_succeed(visb_visualiser:special_svg_number("10 %",[])).
1718 :- assert_must_succeed(visb_visualiser:special_svg_number(" 99em ",[])).
1719 :- assert_must_succeed(visb_visualiser:special_svg_number("1.0em",[])).
1720 :- assert_must_fail(visb_visualiser:special_svg_number("10",[])).
1721 :- assert_must_fail(visb_visualiser:special_svg_number("10+nrcols+%0",[])).
1722 special_svg_number --> " ",!, special_svg_number.
1723 special_svg_number --> [X], {digit(X)},!, special_svg_number2.
1724 special_svg_number --> "auto".
1725 special_svg_number2 --> [X], {digit(X)},!, special_svg_number2.
1726 special_svg_number2 --> ".",!, special_svg_number2. % TODO: only allow one dot; + accept e notation?
1727 ?special_svg_number2 --> optws,!, svg_unit,!, optws.
1728
1729 % using info from https://oreillymedia.github.io/Using_SVG/guide/units.html
1730 svg_unit --> "%".
1731 svg_unit --> "ch".
1732 svg_unit --> "cm".
1733 svg_unit --> "em".
1734 svg_unit --> "ex".
1735 svg_unit --> "in".
1736 svg_unit --> "mm".
1737 svg_unit --> "pc".
1738 svg_unit --> "pt".
1739 svg_unit --> "px".
1740 svg_unit --> "deg". % angle units
1741 svg_unit --> "grad".
1742 svg_unit --> "rad".
1743 svg_unit --> "turn".
1744 svg_unit --> "rem". % root em
1745 svg_unit --> "vh". % viewport height unit (1%)
1746 svg_unit --> "vw". % viewport width unit (1%)
1747 svg_unit --> "vmin". % min ov vh, vw
1748 svg_unit --> "vmax". % max ov vh, vw
1749
1750
1751 optws --> " ",!,optws.
1752 optws --> [].
1753
1754 digit(X) :- X >= 48, X =< 57.
1755
1756 is_svg_number_attribute(Attr) :- is_svg_number_attribute(Attr,_).
1757
1758
1759 :- use_module(probsrc(tools_matching), [dot2svg_attribute/2, is_dot_attribute/1]).
1760 % some checks to see whether the attribute is supported by the given SVG class
1761
1762 check_attribute_is_supported(SVG_Class,DefPos,svg_attribute(Name,_V)) :- !,
1763 (nonvar(SVG_Class), check_is_number_attribute(Name,SVG_Class,DefPos) -> true
1764 % TODO: check color and other attributes, see also check_attribute_type
1765 ; check_attribute_name_is_supported(SVG_Class,Name,DefPos)).
1766 check_attribute_is_supported(S,DefPos,F) :-
1767 add_internal_error('Illegal call:',check_attribute_is_supported(S,DefPos,F)).
1768
1769 % if these special attributes occur here, something went wrong, e.g.,
1770 % when separating static/dynamic parts
1771 check_unsupported_special_visb_attribute(visb_objects,_,_) :- !,fail. % here we can process everything
1772 check_unsupported_special_visb_attribute(SpecialClass,DefPos,svg_attribute(Name,_)) :-
1773 special_visb_attribute_not_allowed_in_dynamic_objects(Name,SpecialClass,Kind),
1774 ajoin(['The VisB special attribute ',Name,' cannot be used here (',SpecialClass,' use separate ',Kind,' definition): '],Msg),
1775 add_warning(visb_visualiser,Msg,Name,DefPos).
1776
1777 special_visb_attribute_not_allowed_in_dynamic_objects(hover,SC,'VISB_SVG_HOVERS') :- SC \= visb_hovers.
1778 special_visb_attribute_not_allowed_in_dynamic_objects(hovers,SC,'VISB_SVG_HOVERS') :- SC \= visb_hovers.
1779 special_visb_attribute_not_allowed_in_dynamic_objects(event,SC,'VISB_SVG_EVENTS') :- SC \= visb_events.
1780 special_visb_attribute_not_allowed_in_dynamic_objects(events,SC,'VISB_SVG_EVENTS') :- SC \= visb_events.
1781 special_visb_attribute_not_allowed_in_dynamic_objects(predicate,SC,'VISB_SVG_EVENTS') :- SC \= visb_events.
1782 special_visb_attribute_not_allowed_in_dynamic_objects(predicates,SC,'VISB_SVG_EVENTS') :- SC \= visb_events.
1783 special_visb_attribute_not_allowed_in_dynamic_objects(preds,SC,'VISB_SVG_EVENTS') :- SC \= visb_events.
1784
1785
1786 check_attribute_name_is_supported(SVG_Class,Name,DefPos) :-
1787 nonvar(SVG_Class),
1788 is_html_tag(SVG_Class),
1789 \+ is_svg_shape_class(SVG_Class), % script and title can be both SVG and HTML
1790 !,
1791 (is_html_attribute(Name)
1792 -> true % TODO: we could check whether attribute appropriate for Tag
1793 ; is_virtual_svg_attribute(Name) -> true % Virtual VisB attribute like children, text, ...
1794 ; ajoin(['Unknown HTML attribute used inside HTML tag ',SVG_Class,': '],Msg),
1795 add_message(visb_visualiser,Msg,Name,DefPos)
1796 ).
1797 check_attribute_name_is_supported(_SVG_Class,Name,DefPos) :-
1798 \+ is_svg_attribute(Name),
1799 !,
1800 (dot2svg_attribute(Name,GraphVizTranslName)
1801 -> ajoin(['Unknown SVG attribute (maybe you want to use ',GraphVizTranslName,' ?): '],Msg),
1802 add_warning(visb_visualiser,Msg,Name,DefPos)
1803 ; get_all_svg_attributes(Attrs),
1804 (get_possible_fuzzy_matches_and_completions_msg(Name,Attrs,FMsg)
1805 -> ajoin(['Unknown SVG attribute (did you mean ',FMsg,' ?): '],Msg),
1806 add_warning(visb_visualiser,Msg,Name,DefPos) % create warning, as it is likely we have made an error
1807 ; is_dot_attribute(Name)
1808 -> add_warning(visb_visualiser,'This Dot/Graphviz attribute is not a valid SVG attribute: ',Name,DefPos)
1809 ; add_message(visb_visualiser,'Unknown SVG attribute: ',Name,DefPos)
1810 )
1811 ).
1812 check_attribute_name_is_supported(_,_,_).
1813
1814 % succeed if attribute is a number attribute and perform a check the attribute is supported by the class
1815 check_is_number_attribute(Attr,Class,Pos) :-
1816 is_svg_number_attribute(Attr,ClassList),
1817 (nonvar(Class), nonmember(Class,ClassList)
1818 -> (equivalent_attribute(Attr,List2,NewAttr), member(Class,List2)
1819 -> ajoin(['The number attribute ',Attr,' is not supported for SVG class ',Class,', use: '],Msg),
1820 add_warning(visb_visualiser,Msg,NewAttr,Pos)
1821 ; ajoin(['The number attribute ',Attr,' is not supported for this SVG class: '],Msg),
1822 add_warning(visb_visualiser,Msg,Class,Pos)
1823 )
1824 ; true
1825 ).
1826
1827 % optionally rewrite record field to alternative spelling
1828 opt_rewrite_field_name(Name,Res) :-
1829 (alternative_spelling(Name,Alt) -> Res=Alt ; Res=Name).
1830
1831 % these alternatives are useful e.g. in TLA+ without backquote:
1832 alternative_spelling(colour,'color').
1833 alternative_spelling(fill_opacity,'fill-opacity').
1834 alternative_spelling(fill_rule,'fill-rule').
1835 alternative_spelling(font_family,'font-family').
1836 alternative_spelling(font_size,'font-size').
1837 alternative_spelling(font_style,'font-style').
1838 alternative_spelling(font_variant,'font-variant').
1839 alternative_spelling(font_weight,'font-weight').
1840 alternative_spelling(marker_end,'marker-end').
1841 alternative_spelling(marker_start,'marker-start').
1842 alternative_spelling(stroke_opacity,'stroke-opacity').
1843 alternative_spelling(stroke_dasharray,'stroke-dasharray').
1844 %alternative_spelling('stroke-dash-array','stroke-dasharray').
1845 alternative_spelling(stroke_linecap,'stroke-linecap').
1846 alternative_spelling(stroke_linejoin,'stroke-linejoin').
1847 alternative_spelling(stroke_width,'stroke-width').
1848
1849
1850
1851 % used to suggest fixing unsupported attributes in SVG objects:
1852 equivalent_attribute(cx,[rect],x).
1853 equivalent_attribute(cy,[rect],y).
1854 equivalent_attribute(x,[circle,ellipse],cx).
1855 equivalent_attribute(x,[line],x1).
1856 equivalent_attribute(y,[circle,ellipse],cy).
1857 equivalent_attribute(y,[line],y1).
1858 equivalent_attribute(r,[rect],rx). % ry also exists
1859 equivalent_attribute(rx,[circle],r).
1860 equivalent_attribute(width,[circle],r).
1861 equivalent_attribute(width,[ellipse],rx).
1862 equivalent_attribute(height,[ellipse],ry).
1863
1864
1865
1866
1867 % ----------------
1868
1869 % parse and load an individual JSON VisB item, e.g, :
1870 % {
1871 % "id":"train_info_text",
1872 % "attr":"x",
1873 % "value":"real(train_rear_end)*100.0/real(TrackElementNumber+1)",
1874 % "comment":"move info field above train"
1875 % },
1876 process_visb_json_item(File,Json) :-
1877 process_repeat(0,Json,File,add_visb_json_item).
1878
1879 add_visb_json_item(File,json(List)) :-
1880 get_attr_true(ignore,List,File), % ignore this item
1881 !.
1882 add_visb_json_item(File,json(List)) :-
1883 del_attr_with_pos(id,List,string(ID),L1,File,PosStartOfItem),
1884 !,
1885 process_visb_json_item_id(File,L1,ID,PosStartOfItem).
1886 add_visb_json_item(File,Json) :-
1887 !,
1888 get_pos_from_list(Json,File,Pos),
1889 add_error(visb_visualiser,'VisB Item has no id attribute:',Json,Pos).
1890
1891 process_visb_json_item_id(File,L1,ID,PosStartOfItem) :-
1892 del_attr(attr,L1,string(Attr),L2), % VisB has attr and value infos
1893 force_del_attr_with_pos(value,L2,string(Formula),L3,File,PosFormula),
1894 !,
1895 (del_attr(comment,L3,string(Desc),L4) -> true ; Desc = '',L4=L3),
1896 debug_format(19,' Processing id:~w attr:~w : value:~w desc:~w~n',[ID,Attr,Formula,Desc]),
1897 actually_add_visb_json_item(ID,Attr,Formula,Desc,L4,PosStartOfItem,PosFormula,File).
1898 process_visb_json_item_id(File,L1,ID,PosStartOfItem) :-
1899 get_attr(SomeSVGAttr,L1,_V),
1900 is_svg_attribute(SomeSVGAttr),
1901 debug_format(19,'Detected new style VisB JSON declaration with id:~w and SVG attr:~w~n',[ID,SomeSVGAttr]),
1902 !,
1903 % object is in new format with multiple attributes "x":"0" rather than "attr":"x", "value":"0"
1904 (del_attr(comment,L1,string(Desc),L2) -> true ; Desc = '',L2=L1),
1905 (non_det_del_attr_with_pos(SVGATTR,L2,string(Formula),L3,File,PosFormula),
1906 is_visb_item_svg_attribute(PosFormula,SVGATTR,Formula),
1907 debug_format(19,' -> Processing new style id:~w attr:~w : value:~w desc:~n',[ID,SVGATTR,Formula,Desc]),
1908 actually_add_visb_json_item(ID,SVGATTR,Formula,Desc,L3,PosStartOfItem,PosFormula,File),
1909 fail
1910 ;
1911 true).
1912 process_visb_json_item_id(_File,_JsonList,ID,PosStartOfItem) :-
1913 !,
1914 add_error(visb_visualiser,'Illegal VisB Item without attr and value fields:',ID,PosStartOfItem).
1915
1916 is_visb_item_svg_attribute(Pos,Attr,Val) :-
1917 Attr \= override, % so we ignore a possible override attribute
1918 (is_svg_attribute(Attr) -> true
1919 ; add_warning(visb_visualiser,'Ignoring unknown attribute: ',Attr=Val,Pos),
1920 fail
1921 ).
1922
1923 :- use_module(probsrc(tools_strings),[safe_name/2]).
1924 actually_add_visb_json_item(ID,Attr,Formula,Desc,JsonList,PosStartOfItem,PosFormula,File) :-
1925 set_error_context(visb_error_context(item,ID,Attr,PosFormula)),
1926 atom_codes(Formula,FormulaC),
1927 (parse_expr_for_visb(FormulaC,JsonList,PosFormula,TypedExpr)
1928 % TO DO: if optional attribute present: avoid generating errors in b_parse_machine_expression_from_codes
1929 -> assert_visb_item(ID,Attr,TypedExpr,Desc,PosStartOfItem,JsonList,File)
1930 ; get_attr_with_pos(optional,JsonList,_,File,Pos)
1931 -> formatsilent('Ignoring optional VisB item for ~w (lines ~w) due to error in B formula~n',[ID,Pos])
1932 ; ajoin(['Cannot parse or typecheck VisB formula for ',ID,' and attribute ',Attr,':'],Msg),
1933 add_error(visb_visualiser,Msg,Formula,PosFormula)
1934 ), clear_error_context.
1935
1936
1937 :- use_module(probsrc(bsyntaxtree), [find_identifier_uses/3]).
1938 % assert a VISB item (aka VISB_SVG_UPDATE)
1939 assert_visb_item(ID,Attr,_TypedExpr,_Desc,PosStartOfItem,_,_) :-
1940 visb_item(ID,Attr,_,_,_,Pos2,Meta2),
1941 !,
1942 get_file_name_msg(PosStartOfItem,From1,File1),
1943 (member(override,Meta2)
1944 -> ajoin(['Overriding VisB item',From1,File1,' for same SVG ID ',ID,' and attribute '],Msg),
1945 add_debug_message(visb_visualiser,Msg,Attr,Pos2)
1946 ; ajoin(['Overriding VisB item',From1,File1,' for same SVG ID ',ID,
1947 '. Add an \"override\" attribute to remove this warning. Overriden attribute '],Msg),
1948 add_warning(visb_visualiser,Msg,Attr,Pos2),
1949 % error_context already includes attribute and ID
1950 add_message(visb_visualiser,'Overriding this stored formula for ',ID,PosStartOfItem) % provide detailed info
1951 ).
1952 assert_visb_item(ID,Attr,_TypedExpr,_Desc,PosStartOfItem,_JsonList,_File) :-
1953 illegal_attribute_for_visb_item(ID,Attr),!,
1954 add_warning(visb_visualiser,'This attribute cannot be modified in a VisB item: ',Attr,PosStartOfItem).
1955 assert_visb_item(ID,Attr,TypedExpr,Desc,PosStartOfItem,JsonList,File) :-
1956 (get_attr_true(override,JsonList,File) -> Meta = [override] ; Meta=[]),
1957 % determine_type_of_visb_formula(TypedExpr,_,Class) now does take definitions into account; TODO: save info
1958 find_identifier_uses(TypedExpr,[],UsedIds),
1959 assertz(visb_item(ID,Attr,TypedExpr,UsedIds,Desc,PosStartOfItem,Meta)).
1960
1961 illegal_attribute_for_visb_item(_,children).
1962 illegal_attribute_for_visb_item(_,group_id).
1963 illegal_attribute_for_visb_item(_,id).
1964 illegal_attribute_for_visb_item(_,svg_class).
1965
1966
1967 get_file_name_msg(Pos1,' from ',File1) :- extract_tail_file_name(Pos1,File1),!.
1968 get_file_name_msg(_,'',''). % no file info
1969
1970 % ----
1971
1972 get_attr_true(Attr,JsonList,File) :-
1973 get_attr_with_pos(Attr,JsonList,TRUE,File,Pos),
1974 (json_true_value(TRUE) -> true
1975 ; json_false_value(TRUE) -> fail
1976 ; ajoin(['Value for attribute ',Attr,' is not true or false: '],Msg),
1977 add_warning(visb_visualiser,Msg,TRUE,Pos)
1978 ).
1979
1980 json_true_value(@(true)).
1981 json_true_value(string(true)).
1982 json_true_value(number(1)).
1983
1984 json_false_value(@(false)).
1985 json_false_value(string(false)).
1986 json_false_value(number(0)).
1987
1988 % ----------------
1989 % FOR-LOOP / REPEAT processing
1990
1991 %process_repeat(RepCounter, Json, FinalCall to be executed repeatedly for each instance with File and Json, File)
1992 % RepCounter tells us which of %0, %1, ... should be replaced next
1993
1994 process_repeat(RepCount,json(JsonList),File,FinalCall) :-
1995 non_det_del_attr_with_pos(FOR_REP,JsonList,Value,RestJsonList,File,ForRepPos),
1996 % find first for or repeat and process it
1997 (FOR_REP=for ; FOR_REP=repeat),
1998 !,
1999 process_first_repeat(FOR_REP,Value,ForRepPos,RepCount,json(RestJsonList),File,FinalCall).
2000 process_repeat(_RepCount,Json,File,FinalCall) :-
2001 % we have processed all for/repeat loops: now perform the final call on the transformed codes
2002 call(FinalCall,File,Json).
2003
2004 process_first_repeat(for,json(ForList),ForPos,RepCount,JsonData,File,FinalCall) :-
2005 !, % we have a for loop like "for": {"from":1, "to":4}
2006 force_get_attr_nr(from,ForList,From,File),
2007 force_get_attr_nr(to,ForList,To,File),
2008 (get_attr_with_pos(step,ForList,StepAttrVal,File,StepPos),
2009 get_number_value(StepAttrVal,Step,step,StepPos)
2010 -> true % there is an explicit step attribute
2011 ; Step=1),
2012 debug_format(19,' -> Iterating %~w from ~w to ~w with step ~w~n',[RepCount,From,To,Step]),
2013 R1 is RepCount+1,
2014 number_codes(RepCount,Pat),
2015 check_between(From,To,Step,ForPos), % check whether step value makes sense
2016 ( between(From,To,Step,IterElem),
2017 number_codes(IterElem,IterElemC), % we will replace the text %Pat by the text of the number IterElem
2018 replace_in_json(Pat,IterElemC,JsonData,ReplacedJsonData), % replace within other for/repeat loops, but also other attributes
2019 process_repeat(R1,ReplacedJsonData,File,FinalCall), % now process next loop or finish
2020 fail
2021 ; true).
2022 process_first_repeat(repeat,array(RepList),RepPos,RepCount,JsonData,File,FinalCall) :-
2023 !, % we have a repetition like "repeat": ["tr1","tr2"] or "repeat": [ ["1","2"] , ...]
2024 (RepList=[array(L1)|_], length(L1,Len)
2025 -> NewRepCount is RepCount+Len, % we have a multi-repeat with list of values to be replaced
2026 LastRepCount is NewRepCount-1,
2027 debug_format(19,' -> Iterating repeat (%~w,...,%~w) over ~w~n',[RepCount,LastRepCount,RepList]),
2028 check_all_same_length_json(RepList,Len,RepPos)
2029 ; NewRepCount is RepCount+1, % next replacement starts at $(RepCount+1)
2030 debug_format(19,' -> Iterating repeat (%~w) over ~w~n',[RepCount,RepList])
2031 ),
2032 ( member(IterElem,RepList),
2033 multi_replace_in_json(IterElem,RepCount,JsonData,ReplacedJsonData), % replace within other for/repeat loops, but also other attributes
2034 process_repeat(NewRepCount,ReplacedJsonData,File,FinalCall), % now process next loop or finish
2035 fail
2036 ; true).
2037
2038 check_all_same_length_json(List,ExpectedLen,Pos) :-
2039 nth1(Nr,List,Json),
2040 (Json=array(SubList),length(SubList,Len) -> Len \= ExpectedLen ; Len='not a list'),
2041 !,
2042 ajoin(['The element number ',Nr,' of the repeat list has not the expected length of ',ExpectedLen,', length is: '],Msg),
2043 add_warning(visb_visualiser,Msg,Len,Pos).
2044 check_all_same_length_json(_,_,_).
2045
2046 json_value_to_codes(@(Literal), C) :- atom(Literal), !, atom_codes(Literal, C).
2047 json_value_to_codes(number(Number), C) :- number(Number), !, number_codes(Number, C).
2048 json_value_to_codes(string(String), C) :- atom(String), !, atom_codes(String, C).
2049 json_value_to_codes(Json, _) :- !, add_error(json_value_to_codes,'Cannot convert json term to codes:', Json), fail.
2050
2051 % replace (possibly) multiple patterns at once
2052 multi_replace_in_json(array([]),_RepCount,JsonIn,JsonOut) :- !, JsonOut=JsonIn.
2053 multi_replace_in_json(array([IterElem|TIT]),RepCount,JsonIn,JsonOut) :-
2054 !,
2055 number_codes(RepCount,Pat),
2056 json_value_to_codes(IterElem,IterElemC),
2057 %format('Replacing in JSON: ~s -> ~s~n',[Pat,IterElemC]),
2058 replace_in_json(Pat,IterElemC,JsonIn,Json),
2059 R1 is RepCount+1,
2060 multi_replace_in_json(array(TIT),R1,Json,JsonOut).
2061 multi_replace_in_json(IterElem,RepCount,JsonIn,JsonOut) :- % a value, not a list
2062 !,
2063 number_codes(RepCount,Pat),
2064 json_value_to_codes(IterElem,IterElemC),
2065 %format('Replacing in JSON: ~s -> ~s~n',[Pat,IterElemC]),
2066 replace_in_json(Pat,IterElemC,JsonIn,JsonOut).
2067
2068 check_between(_,_,Step,ForPos) :- Step =< 0, !,
2069 add_error(visb_visualiser,'The step of a for loop must be positive:',Step,ForPos),fail.
2070 check_between(From,To,Step,ForPos) :- Iters is (To-From)/Step,
2071 Iters > 100000,!,
2072 add_error(visb_visualiser,'Very large for loop:',Iters,ForPos),fail.
2073 check_between(_,_,_,_).
2074
2075
2076 % ----------------
2077
2078 % parse and load VisB events
2079 % A VisB Event looks like:
2080 % {
2081 % "id": "button",
2082 % "event": "toggle_button",
2083 % "hovers": [{ "attr":"stroke-width", "enter":"6", "leave":"1"},
2084 % { "attr":"opacity", "enter":"0.8", "leave":"1.0"}]
2085 % }
2086 process_json_event(File,Json) :-
2087 process_repeat(0,Json,File,add_visb_json_event).
2088
2089 add_visb_json_event(File,json(List)) :- get_attr_true(ignore,List,File), !. % ignore this item
2090 add_visb_json_event(File,json(List)) :-
2091 get_pos_from_list(List,File,Pos),
2092 force_del_attr(id,List,string(ID),L0,File), % for items it could make sense to not specify an id
2093 (del_attr(event,L0,string(Event),L1) -> true ; Event='', L1=L0),
2094 (del_attr_with_pos(predicates,L1,array(Preds),L2,File,PredPos) -> true
2095 ; del_attr_with_pos(preds,L1,array(Preds),L2,File,PredPos) -> true
2096 ; Preds=[], L2=L1, PredPos=unknown),
2097 (del_attr(hovers,L2,array(Hovers),L3) -> true ; Hovers=[],L3=L2),
2098 (del_attr(items,L3,array(EI),L4)
2099 -> (empty_b_event(Event)
2100 -> EnableItems=[],
2101 add_warning(visb_visualiser,'Ignoring enable items; you need to provide an event name:',ID,Pos)
2102 ; EnableItems=EI)
2103 ; EnableItems=[],L4=L3),
2104 debug_format(19,' Processing id:~w event:~w preds:~w enable:~w hovers:~w~n',[ID,Event,Preds,EnableItems,Hovers]),
2105 !,
2106 actually_add_visb_json_event(ID,Event,Preds,Hovers,EnableItems,L4,File,Pos,PredPos).
2107 add_visb_json_event(File,Json) :-
2108 !,
2109 get_pos_from_list(Json,File,Pos),
2110 add_error(visb_visualiser,'Illegal VisB Event:',Json,Pos).
2111
2112 actually_add_visb_json_event(ID,Event,JsonPreds,JsonHovers,JsonEnableItems,JsonList,File,Pos,PredPos) :-
2113 check_additional_args(JsonList,File),
2114 maplist(process_json_pred,JsonPreds,Preds),
2115 maplist(process_json_enabling_item(ID,Event,File),JsonEnableItems,EnableItems),
2116 maplist(process_json_hover(ID,File),JsonHovers,Hovers),
2117 add_visb_event(ID,Event,Preds,Hovers,EnableItems,File,Pos,PredPos,JsonList).
2118
2119 :- use_module(probsrc(tools_strings), [atom_prefix/2]).
2120 :- use_module(probsrc(bmachine), [b_is_operation_name/1]).
2121 add_visb_event(ID,Event,Preds,Hovers,EnableItems,File,Pos,PredPos,JsonList) :-
2122 (retract(visb_event(ID,OldEvent,OldPreds,OldTypedPred,OldFile,OldPos))
2123 -> (get_attr_true(override,JsonList,File)
2124 -> ajoin(['Overriding VisB event from file ',OldFile,' for ID: '],Msg),
2125 add_debug_message(visb_visualiser,Msg,ID,Pos),
2126 retractall(visb_hover(ID,_,_,_,_,_))
2127 ; (OldFile=File
2128 -> ajoin(['No override attribute: adding VisB event ',Event,
2129 ' (first event ',OldEvent,') for ID: '],Msg)
2130 ; ajoin(['No override attribute: adding VisB event ',Event,
2131 ' (first event ',OldEvent,' in file ',OldFile,') for ID: '],Msg)
2132 ),
2133 add_debug_message(visb_visualiser,Msg,ID,Pos),
2134 assertz(auxiliary_visb_event(ID,OldEvent,OldPreds,OldTypedPred,OldPos))
2135 ),
2136 assert_visb_event(ID,Event,Preds,Hovers,EnableItems,File,Pos,PredPos)
2137 % ProB2-UI cannot currently support multiple events associated with the same id
2138 % TODO: merge visb_events if we have no override attribute
2139 ; (xtl_mode ; b_is_operation_name_or_external_subst(Event)) ->
2140 assert_visb_event(ID,Event,Preds,Hovers,EnableItems,File,Pos,PredPos)
2141 ; (empty_b_event(Event) ; \+ b_or_z_mode)
2142 -> % for empty event we just want hovers
2143 (Preds = [] -> true
2144 ; add_warning(visb_visualiser,'Ignoring preds for VisB event for SVG ID: ',ID,Pos)
2145 ),
2146 assert_visb_event(ID,Event,[],Hovers,EnableItems,File,Pos,PredPos)
2147 ; get_attr_with_pos(optional,JsonList,_,File,Pos) ->
2148 formatsilent('Ignoring optional VisB event for ~w (lines ~w) due to unknown B operation ~w~n',[ID,Pos,Event])
2149 ; detect_op_call_with_paras(Event,OpName) ->
2150 add_warning(visb_visualiser,'Ignoring parameters provided in event; use predicate attribute to specify parameters: ',Event,Pos),
2151 assert_visb_event(ID,OpName,Preds,Hovers,EnableItems,File,Pos,PredPos)
2152 ; atom(Event), atom_prefix('{',Event) ->
2153 ajoin(['Unknown B operation ', Event, ' in VisB for SVG ID (be sure to use events attribute for multiple events): '],Msg),
2154 add_warning(visb_visualiser,Msg,ID,Pos)
2155 ; ajoin(['Unknown B operation ', Event, ' in VisB for SVG ID: '],Msg),
2156 add_warning(visb_visualiser,Msg,ID,Pos)
2157 ).
2158
2159 b_is_operation_name_or_external_subst(OpName) :- b_is_operation_name(OpName).
2160 b_is_operation_name_or_external_subst(Special) :- special_operation(Special).
2161
2162 % maybe we should provide those via the external substitution interface:
2163 % these are all schedulers which choose among existing enabled operations in some manner
2164 special_operation('MCTS_AUTO_PLAY').
2165 special_operation('RANDOM_ANIMATE').
2166 special_operation('RANDOM_ANIMATE_UNTIL_LTL').
2167 % maybe other special names like random_animate with nr of steps, LTL until, ...
2168 special_operation_enabled('MCTS_AUTO_PLAY',_,_,_) :- mcts_auto_play_available.
2169 special_operation_enabled('RANDOM_ANIMATE',_,_,_). % TODO: check if a transition exists
2170 special_operation_enabled('RANDOM_ANIMATE_UNTIL_LTL',_,_,_).
2171
2172 % detect operation call with parameters
2173 detect_op_call_with_paras(Event,OpName) :- atom(Event),
2174 atom_codes(Event,Codes), parse_op_call_name(OpC,Codes,_),!,
2175 atom_codes(OpName,OpC),
2176 b_is_operation_name(OpName).
2177
2178 parse_op_call_name([X|T]) --> alpha(X), parse_op_call_name2(T).
2179 parse_op_call_name2([]) --> "(".
2180 parse_op_call_name2([H|T]) --> alphadigit(H), parse_op_call_name2(T).
2181
2182 alpha(X) --> [X],{X>=97, X=<122}.
2183 alphadigit(X) --> [X], ({X>=97,X=<122} ; {X>=65, X=<90} ; {X=95} ; {X>=48, X=<57}).
2184
2185 empty_b_event('').
2186
2187 assert_visb_event(ID,Event,Preds,Hovers,EnableItems,File,Pos,PredPos) :-
2188 construct_pre_post_predicate(ID,Event,Preds,TypedPred,PredPos),
2189 assertz(visb_event(ID,Event,Preds,TypedPred,File,Pos)),
2190 % process hovers
2191 (member(HoverElement,Hovers),
2192 (HoverElement=visb_hover(HoverID,Attr,EnterVal,ExitVal) -> true ; add_error(visb_visualiser,'Illegal hover term:',HoverElement),fail),
2193 assert_visb_hover(ID,HoverID,Attr,EnterVal,ExitVal,Pos),fail
2194 ; true),
2195 % now process any additional items with disabled and enabled values
2196 assert_visb_enabling_item_list(Event,TypedPred,EnableItems,File,Pos).
2197
2198 process_json_pred(string(P),R) :- !, R=P.
2199 process_json_pred(Json,_) :- !, add_error(visb_visualiser,'Illegal json term for predicate:',Json), fail.
2200
2201 process_json_hover(OriginID,File,json(Hover),visb_hover(ID,Attr,EnterVal,LeaveVal)) :-
2202 force_del_attr(attr,Hover,string(Attr),H2,File),
2203 force_del_attr_with_pos(enter,H2,EV,H3,File,EnterPos),
2204 force_del_attr_with_pos(leave,H3,LV,H4,File,ExitPos),
2205 (is_svg_number_attribute(Attr) % we evaluate number attributes
2206 -> get_number_value(EV,EnterVal,Attr,EnterPos),
2207 get_number_value(LV,LeaveVal,Attr,ExitPos)
2208 ; string(EnterVal)=EV, string(LeaveVal)=LV % return string as is; TODO: also evaluate other attributes
2209 ),
2210 (get_attr(id,H4,string(ID)) -> true ; ID=OriginID).
2211
2212
2213 assert_visb_hover(TriggerID,SVG_ID,Attr,EnterVal,ExitVal,Pos) :-
2214 assert(visb_hover(TriggerID,SVG_ID,Attr,EnterVal,ExitVal,Pos)),
2215 (visb_has_hovers(TriggerID) -> true ; assert(visb_has_hovers(TriggerID))),
2216 (visb_has_visibility_hover(SVG_ID) -> true
2217 ; Attr=visibility -> assert(visb_has_visibility_hover(TriggerID)) % object can be made visible by hover
2218 ; true),
2219 debug_format(19,'Adding hover for ~w : ~w.~w -> ~w <- ~w~n',[TriggerID,SVG_ID,Attr,EnterVal,ExitVal]).
2220
2221
2222 % process items in event which get translated to enabling/disabling predicates
2223 % "items":[ {"attr":"stroke-width","enabled":"10", "disabled":"1"} ]
2224 process_json_enabling_item(ID,Event,File,json(JsonList),
2225 visb_enable_item(SvgID,Attr,EnabledValExpr,DisabledValExpr,PosAttr)) :-
2226 force_del_attr_with_pos(attr,JsonList,string(Attr),L2,File,PosAttr),
2227 force_del_attr_with_pos('enabled',L2,string(EnVal),L3,File,EPos),
2228 force_del_attr_with_pos('disabled',L3,string(DisVal),L4,File,DPos),
2229 (del_attr(id,L4,string(SvgID),L5) -> true ; SvgID=ID, L4=L5),
2230 atom_codes(EnVal,EC),
2231 parse_expr_for_visb(EC,L5,EPos,EnabledValExpr),
2232 atom_codes(DisVal,DC),
2233 parse_expr_for_visb(DC,L5,DPos,DisabledValExpr),
2234 (debug_mode(off) -> true
2235 ; translate_bexpression_with_limit(EnabledValExpr,30,EVS),
2236 translate_bexpression_with_limit(DisabledValExpr,30,DVS),
2237 formatsilent('Enabling item for event ~w and SVG ID ~w and attribute ~w : ~w <-> ~w~n',[Event,SvgID,Attr,EVS,DVS])
2238 ).
2239
2240 assert_visb_enabling_item_list(Event,TypedPred,EnableList,File,Pos) :-
2241 maplist(check_enabling_item(Event),EnableList),
2242 (EnableList \= []
2243 -> (debug_mode(off)
2244 -> true
2245 ; format('Associating enabling/disabling list with event ~w and predicate: ',[Event]), translate:print_bexpr(TypedPred),nl),
2246 assert(visb_event_enable_list(Event,TypedPred,EnableList,File,Pos))
2247 ; true).
2248
2249 check_enabling_item(Event,visb_enable_item(SvgID,Attr,_,_,PosAttr)) :-
2250 (visb_item(SvgID,Attr,_,_,_Desc,DuplicatePos,_)
2251 -> (extract_span_description(DuplicatePos,DuplPos) -> true; DuplPos=DuplicatePos),
2252 ajoin(['VisB conflict for SVG ID ',SvgID,' and attribute ',Attr,
2253 '. Conflict between VisB item (',DuplPos,') and VisB enable/disable entry for event: '],Msg),
2254 add_warning(visb_visualiser,Msg,Event,PosAttr)
2255 ; true).
2256
2257 valid_additional_attributes(comment).
2258 valid_additional_attributes(description).
2259 valid_additional_attributes(optional).
2260 valid_additional_attributes(override).
2261
2262 % check if there are additional unprocessed args and generate a warning
2263 check_additional_args(JsonList,File) :-
2264 get_attr_with_pos(Attr,JsonList,_,File,Pos),
2265 \+ valid_additional_attributes(Attr),
2266 add_warning(visb_visualiser,'Ignoring unknown JSON field: ',Attr,Pos),
2267 fail.
2268 check_additional_args(_,_).
2269
2270 :- use_module(probsrc(bsyntaxtree), [conjunct_predicates/2]).
2271 % construct a pre-post typed predicate for a VisB Event
2272 construct_pre_post_predicate(SvgID,OpName,Preds,TypedPred,Pos) :-
2273 set_error_context(visb_error_context(event,SvgID,OpName,Pos)),
2274 maplist(construct_pre_post_pred(OpName,Pos),Preds,TL),
2275 clear_error_context,
2276 conjunct_predicates(TL,TypedPred).
2277
2278 :- use_module(probsrc(bmachine), [b_parse_machine_operation_pre_post_predicate/5]).
2279 construct_pre_post_pred(OpName,Pos,PredStr,TypedPred) :- empty_b_event(OpName),!,
2280 add_error(visb_visualiser,'Cannot parse VisB event predicate without event name:',PredStr,Pos),
2281 TypedPred = b(truth,pred,[]).
2282 construct_pre_post_pred(OpName,Pos,String,TypedExpr) :- special_operation(OpName),!,
2283 % we have a special operation; allow to provide an expression with options/parameters
2284 atom_codes(String,Codes),
2285 GenParseErrors=gen_parse_errors_for(Pos),
2286 parse_expr(Codes,TypedExpr,GenParseErrors). % TODO: should we require a predicate instead, and provide arg names?
2287 construct_pre_post_pred(OpName,Pos,String,TypedPred) :-
2288 atom_codes(String,Codes), replace_special_patterns(Codes,RCodes,Pos), %format("Replaced : ~S~n",[RCodes]),
2289 get_visb_extra_scope([identifier(VisBExtraScope)]),
2290 visb_click_meta_b_type(MetaRecType),
2291 ExtraScope = [identifier([b(identifier('VISB_CLICK_META_INFOS'),MetaRecType,[visb_generated])|VisBExtraScope])],
2292 (b_parse_machine_operation_pre_post_predicate(RCodes,ExtraScope,TypedPred,OpName,gen_parse_errors_for(Pos))
2293 -> true
2294 ; add_error(visb_visualiser,'Error for VisB event predicate:',String,Pos),
2295 TypedPred = b(truth,pred,[])
2296 ).
2297
2298 % replace special patterns by dummy values to avoid error messages in ProB2-UI
2299 replace_special_patterns([],[],_Pos) :- !.
2300 replace_special_patterns([37|T],Res,Pos) :- !, % percentage sign %
2301 replace_aux(T,Res,Pos).
2302 replace_special_patterns([H|T],[H|RT],Pos) :- !, replace_special_patterns(T,RT,Pos).
2303
2304 replace_aux(Input,Res,Pos) :-
2305 replace_pat(PAT,Replacement),
2306 append(PAT,T,Input),
2307 !,
2308 atom_codes(PatAtom,PAT),
2309 ajoin(['The %',PatAtom,' pattern is obsolete. Please use VISB_CLICK_META_INFOS\'',PatAtom,' instead.'],Msg),
2310 add_warning(visb_visualiser,Msg,'',Pos),
2311 append(Replacement,ResT,Res),
2312 replace_special_patterns(T,ResT,Pos).
2313 replace_aux(Input,[37|Res],Pos) :- !, replace_special_patterns(Input,Res,Pos).
2314
2315 replace_pat("shiftKey","VISB_CLICK_META_INFOS'shiftKey").
2316 replace_pat("metaKey","VISB_CLICK_META_INFOS'metaKey").
2317 replace_pat("pageX","VISB_CLICK_META_INFOS'pageX").
2318 replace_pat("pageY","VISB_CLICK_META_INFOS'pageY").
2319
2320
2321
2322 % small utils:
2323 % ----------------
2324
2325 % a variation of between/3 with a step argument
2326 between(From,To,_,_) :- From > To, !,fail.
2327 between(From,_,_,From).
2328 between(From,To,Step,Elem) :- F1 is From+Step, between(F1,To,Step,Elem).
2329
2330 :- use_module(probsrc(tools_strings),[is_simple_classical_b_identifier_codes/1]).
2331 :- use_module(probsrc(preferences), [reset_temporary_preference/2,temporary_set_preference/3]).
2332 parse_expr(ExprCodes,TypedExpr,_GenParseErrors) :-
2333 is_simple_classical_b_identifier_codes(ExprCodes),
2334 atom_codes(DefID,ExprCodes),
2335 visb_definition(DefID,Type,_DefFormula,Class,_VPos,_),
2336 !,
2337 TypedExpr = b(identifier(DefID),Type,[type_of_formula(Class)]).
2338 parse_expr(ExprCodes,TypedExpr,GenParseErrors) :-
2339 temporary_set_preference(allow_arith_operators_on_reals,true,CHNG),
2340 get_visb_extra_scope(ExtraScope),
2341 % formatsilent('Parsing: ~s (extra ids: ~w)~n',[ExprCodes,ExtraScope]), start_ms_timer(T1),
2342 call_cleanup(bmachine:b_parse_machine_expression_from_codes_with_prob_ids(ExprCodes,ExtraScope,TypedExpr,
2343 GenParseErrors),
2344 reset_temporary_preference(allow_arith_operators_on_reals,CHNG)).
2345 %stop_ms_walltimer_with_msg(T1,'parsing: ').
2346 % TODO: we could share a machine parameter M like in prob2_interface
2347 % so that b_type_expression_for_full_b_machine will load machine only once
2348 % cf b_type_open_predicate_for_full_b_machine
2349
2350 determine_type_of_visb_formula(b(_,_,[type_of_formula(Class)]),all,Res) :- !,
2351 Res = Class. % generated by VisB, TODO: store UsedTIds in type_of_formula(.)
2352 determine_type_of_visb_formula(TypedExpr,TIds,Class) :-
2353 determine_type_of_formula_with_visb_defs(TypedExpr,TIds,Class).
2354
2355 %check for used_ids inside TypedExpr an see what type of visb_definition are used
2356 determine_type_of_formula_with_visb_defs(TypedExpr,TIds,ResClass) :-
2357 determine_type_of_formula(TypedExpr,TIds,Class1), % compute class w/o knowledge of VisB definitions
2358 (class_more_general_than(Class2,Class1),
2359 required_by_visb_def(TIds,Class2) -> Class=Class2
2360 ; Class=Class1),
2361 (Class=requires_variables -> ResClass=Class
2362 ; expression_requires_state(TypedExpr) -> ResClass = requires_variables
2363 ; ResClass=Class).
2364
2365 :- use_module(probsrc(bsyntaxtree),[map_over_bexpr/2]).
2366 :- use_module(probsrc(external_functions),[external_function_requires_state/1]).
2367 expression_requires_state(TypedExpr) :-
2368 (map_over_bexpr(sub_expression_requires_state,TypedExpr) -> true ; fail).
2369 % TODO: should we also check is_not_declarative/1 ? e.g., for RANDOM or CHANGED
2370 sub_expression_requires_state(external_pred_call(P,_)) :- external_function_requires_state(P).
2371 sub_expression_requires_state(external_function_call(P,_)) :- external_function_requires_state(P).
2372
2373
2374 class_more_general_than(requires_variables,requires_nothing).
2375 class_more_general_than(requires_variables,requires_constants).
2376 class_more_general_than(requires_constants,requires_nothing).
2377
2378 required_by_visb_def(TIds,Class) :-
2379 member(TID,TIds), get_texpr_id(TID,ID),visb_definition(ID,_,_,Class,_,_).
2380
2381
2382 get_visb_extra_scope([identifier(ExtraIDs)]) :-
2383 get_visb_extra_identifiers(ExtraIDs).
2384 get_visb_extra_identifiers(ExtraIDs) :-
2385 findall(b(identifier(ID),Type,[visb_generated]),visb_definition(ID,Type,_,_,_,_),ExtraIDs).
2386
2387 % replace a pattern code prefixed by % by another code list
2388 replace_in_json(Pattern,RepStr,string(Val),string(NewVal)) :- !, replace_atom(Pattern,RepStr,Val,NewVal).
2389 replace_in_json(Pattern,RepStr,array(Vals),array(NewVals)) :- !, maplist(replace_in_json(Pattern,RepStr),Vals,NewVals).
2390 replace_in_json(Pattern,RepStr,json(Vals),json(NewVals)) :- !, maplist(replace_in_json_pair(Pattern,RepStr),Vals,NewVals).
2391 replace_in_json(_,_,Val,Val). % number/literal (no replacement necessary)
2392
2393 replace_in_json_pair(Pattern,RepStr,'='(KIn,VIn,Pos),'='(KOut,VOut,Pos)) :-
2394 replace_atom(Pattern,RepStr,KIn,KOut),
2395 replace_in_json(Pattern,RepStr,VIn,VOut).
2396
2397 replace_atom(Pattern,RepStr,Val,NewVal) :-
2398 atom_codes(Val,Codes),
2399 replace_pat(Pattern,RepStr,NewCodes,Codes,[]),
2400 atom_codes(NewVal,NewCodes). % TO DO: keep as codes for efficiency
2401
2402 :- assert_must_succeed((visb_visualiser: replace_pat("0","_1_",Res,"ab%0cd",[]), Res == "ab_1_cd")).
2403 :- assert_must_succeed((visb_visualiser: replace_pat("0","",Res,"ab%0%0cd%0",[]), Res == "abcd")).
2404 % dcg utility to replace %Pat by NewStr constructing Res
2405 replace_pat(Pat,NewStr,Res) --> "%", Pat, !, {append(NewStr,TR,Res)}, replace_pat(Pat,NewStr,TR).
2406 replace_pat(Pat,RepStr,[H|T]) --> [H],!, replace_pat(Pat,RepStr,T).
2407 replace_pat(_,_,[]) --> [].
2408
2409
2410 % small JSON utils:
2411 % ----------------
2412
2413 get_attr(Attr,List,Val) :- member('='(Attr,Val,_),List).
2414 get_attr_with_pos(Attr,List,Val,File,Pos) :-
2415 El = '='(Attr,Val,_),
2416 member(El,List),
2417 get_pos_from_list([El],File,Pos).
2418
2419 del_attr(Attr,List,Val,Rest) :- select('='(Attr,Val,_Pos),List,Rest).
2420 %del_attr_with_pos(Attr,List,Val,Rest,Pos) :- select('='(Attr,Val,Pos),List,Rest).
2421 del_attr_with_pos(Attr,List,Val,Rest,File,PosTerm) :- select('='(Attr,Val,From-To),List,Rest),!,
2422 PosTerm = src_position_with_filename_and_ec(From,1,To,1,File).
2423 non_det_del_attr_with_pos(Attr,List,Val,Rest,File,PosTerm) :- select('='(Attr,Val,From-To),List,Rest),
2424 PosTerm = src_position_with_filename_and_ec(From,1,To,1,File).
2425
2426 force_del_attr(Attr,List,Val,Rest,File) :- force_del_attr_with_pos(Attr,List,Val,Rest,File,_).
2427
2428 force_del_attr_with_pos(Attr,List,Val,Rest,File,PosTerm) :- select('='(Attr,Val,From-To),List,Rest),!,
2429 %TODO: we would ideally want to extract the exact column position of Val, for this we need to extend the JSON parser first
2430 PosTerm = src_position_with_filename_and_ec(From,1,To,1,File).
2431 force_del_attr_with_pos(Attr,List,_,_,File,_) :- get_pos_from_list(List,File,Pos),!,
2432 add_error(visb_visualiser,'The JSON object has no attribute:',Attr,Pos),fail.
2433
2434 construct_prob_pos_term(From-To,File,PosTerm) :- !,
2435 PosTerm = src_position_with_filename_and_ec(From,1,To,1,File).
2436 construct_prob_pos_term(Pos,_,Pos).
2437
2438 force_get_attr_nr(Attr,List,Nr,File) :-
2439 force_del_attr_with_pos(Attr,List,AttrVal,_,File,Pos),!,
2440 get_number_value(AttrVal,Nr,Attr,Pos).
2441
2442 get_number_value(AttrVal,Nr,Attr,Pos) :-
2443 (AttrVal = number(Nr) -> true
2444 ; AttrVal = string(StrAttrVal),
2445 atom_codes(StrAttrVal,AttrValC),
2446 parse_expr(AttrValC,TypedExpr,gen_parse_errors_for(Pos)),
2447 determine_type_of_visb_formula(TypedExpr,UsedTIds,Class)
2448 % Class = requires_nothing, requires_constants, requires_variables
2449 ->
2450 (Class = requires_variables
2451 -> ajoin(['The JSON formula for the attribute"',Attr,
2452 '" must not depend on variables:'],Msg),
2453 add_error(visb_visualiser,Msg,StrAttrVal,Pos),fail
2454 ; Class = requires_constants,
2455 \+ is_concrete_constants_state_id(_)
2456 -> ajoin(['The JSON formula for the attribute"',Attr,
2457 '" depends on constants which have not been set up (via SETUP_CONSTANTS):'],Msg),
2458 add_error(visb_visualiser,Msg,StrAttrVal,Pos),fail
2459 ; Class = requires_constants,
2460 multiple_concrete_constants_exist,
2461 ajoin(['The JSON formula for the attribute"',Attr,
2462 '" depends on constants and multiple solutions for SETUP_CONSTANTS exist:'],Msg),
2463 add_warning(visb_visualiser,Msg,StrAttrVal,Pos),fail
2464 ; get_texpr_type(TypedExpr,Type),
2465 is_number_type(Type)
2466 -> eval_static_def(Class,'VisB attribute',Attr,TypedExpr,UsedTIds,ResVal,Pos),
2467 get_number_from_bvalue(ResVal,Nr)
2468 ; get_texpr_type(TypedExpr,Type),
2469 % it could produce a string which is a number; we could try and convert to a number
2470 ajoin(['The type ',Type,' of the JSON value formula for the attribute "',Attr,
2471 '" is not a number:'],Msg),
2472 add_error(visb_visualiser,Msg,StrAttrVal,Pos),fail
2473 )
2474 ; ajoin(['The JSON value for the attribute "',Attr,'" cannot be parsed as a number:'],Msg),
2475 add_error(visb_visualiser,Msg,AttrVal,Pos),fail).
2476
2477 is_number_type(integer).
2478 is_number_type(real).
2479 :- use_module(probsrc(kernel_reals),[is_real/2]).
2480 :- use_module(probsrc(custom_explicit_sets),[singleton_set/2]).
2481 get_number_from_bvalue(int(Nr),Res) :- !, Res=Nr.
2482 get_number_from_bvalue(Term,Res) :- is_real(Term,Nr),!,Res=Nr.
2483
2484 get_pos_from_list(json(List),File,Pos) :- !, get_pos_from_list(List,File,Pos).
2485 get_pos_from_list([H|T],File,RPos) :-
2486 H='='(_,_,From-_),
2487 last([H|T],
2488 '='(_,_,_-To)),
2489 !,
2490 RPos=src_position_with_filename_and_ec(From,1,To,1,File).
2491 get_pos_from_list(_,File,File). % should we provide another term?
2492
2493 % ----------------------------------
2494
2495 :- use_module(probsrc(b_global_sets),[add_prob_deferred_set_elements_to_store/3]).
2496 :- use_module(probsrc(tools),[b_string_escape_codes/2]).
2497
2498 % computing updates to SVG for a given StateId:
2499 % predicate to obtain required setAttribute changes to visualise StateId
2500 % looks up visb_item facts but also evaluates VISB_SVG_UPDATE definitions
2501 get_change_attribute_for_state(StateId,SvgID,SvgAttribute,Value) :-
2502 set_error_context(checking_context('VisB:','computing attributes for state')),
2503 get_expanded_bstate(StateId,ExpandedBState),
2504 set_context_state(StateId,get_change_attribute_for_state), % also sets it for external functions
2505 % TODO: also set history so that get_current_history in external_functions is more reliable
2506 call_cleanup(get_change_aux(StateId,ExpandedBState,SvgID,SvgAttribute,Value),
2507 (clear_context_state,clear_error_context)).
2508
2509 get_change_aux(StateId,ExpandedBState,SvgID,SvgAttribute,Value) :-
2510 get_aux2(StateId,ExpandedBState,SvgID0,SvgAttribute0,Value0,DefPos),
2511 post_process_visb_item(SvgID0,SvgAttribute0,Value0,DefPos,SvgID,SvgAttribute,Value).
2512 get_aux2(StateId,ExpandedBState,SvgID,SvgAttribute,Value,DefPos) :-
2513 % first get updates from DEFINITIONS which usually return sets of records
2514 get_svg_object_updates_from_definitions(ExpandedBState,SvgID,SvgAttribute,Value,DefPos),
2515 debug_format(19,' VISB_SVG_UPDATE ~w:~w = ~w (in state ~w)~n',[SvgID,SvgAttribute,Value,StateId]).
2516 get_aux2(StateId,ExpandedBState,SvgID,SvgAttribute,Value,Pos) :-
2517 % TODO: check if visibility item exists, and if value is false: do not compute the rest
2518 get_visb_item_formula(SvgID,SvgAttribute,Formula,Pos,ExpandedBState),
2519 % TODO: if UsedIds=[] only set attribute once, if it requires_only_constants : ditto
2520 evaluate_visb_formula(Formula,'VisB item',SvgID,ExpandedBState,FValue,Pos),
2521 %b_value_to_string(FValue,Value),
2522 extract_attr_value(SvgAttribute,FValue,Value,Pos),
2523 debug_format(19,' VisB item ~w:~w = ~w (in state ~w)~n',[SvgID,SvgAttribute,Value,StateId]).
2524
2525 % post-process certain items, like title to adapt the value and id:
2526 % SVG does not support a title attribute; we need a title child and set its text attribute
2527 post_process_visb_item(SvgID,title,Value,Pos,NewID,text,NewValue) :-
2528 (visb_svg_object_debug_info(SvgID,DebugInfo) -> ajoin([Value,'\n',DebugInfo],NewValue) ; NewValue=Value),
2529 (visb_svg_parent(SvgID,TitleID),
2530 visb_svg_object(TitleID,title,_,_,_)
2531 -> NewID=TitleID,
2532 debug_format(9,'Redirecting title update for ~w to child object ~w~n',[SvgID,TitleID])
2533 ; visb_svg_object(SvgID,_SVG_Class,_RestAttrs,_Desc,_Pos1)
2534 -> % this is an object we created
2535 add_warning(visb_visualiser,'Could not find title child object, be sure to define a static title attribute for SVG object: ',SvgID,Pos),
2536 fail
2537 ; add_warning(visb_visualiser,'SVG does not natively support title attributes: ',SvgID,Pos),
2538 fail
2539 ),!.
2540 post_process_visb_item(SvgID,Attr,Value,_,SvgID,Attr,Value).
2541
2542 % ------------------
2543
2544 % convert B value to Json String
2545 b_value_to_string(string(SValue),Res) :- !, Res=SValue. % What about quoting,...?
2546 b_value_to_string(FValue,Res) :-
2547 translate_bvalue_to_codes(FValue,ValCodes),
2548 atom_codes(Res,ValCodes).
2549
2550 % attributes for which we convert pairs to the concatenation of strings
2551 is_id_or_text_attribute(id).
2552 is_id_or_text_attribute('group_id'). % works much like a parent_id; also can be used to attach animate to e.g. a rect
2553 is_id_or_text_attribute('trigger_id').
2554 is_id_or_text_attribute('trigger-id').
2555 is_id_or_text_attribute(A) :- is_text_attribute(A).
2556 % children
2557 is_text_attribute('text').
2558 is_text_attribute('transform').
2559 is_text_attribute('event'). % for VISB_SVG_EVENTS
2560 is_text_attribute('predicate'). % for VISB_SVG_EVENTS
2561 is_text_attribute('svg_class').
2562
2563
2564 b_value_to_id_string(Val,String) :- b_val_to_id_string_aux(Val,add_underscore,String).
2565 b_value_to_text_string(Val,String) :- b_val_to_id_string_aux(Val,no_underscore,String).
2566
2567 % a special string conversion which e.g., allows to use things like ("ab",2) as id which gets translated to ab2
2568 % also useful for text attributes
2569 b_val_to_id_string_aux(string(SValue),_,Res) :- !, Res=SValue.
2570 b_val_to_id_string_aux((A,B),Add,Res) :- !,
2571 b_val_to_id_string_aux(A,Add,VA), b_val_to_id_string_aux(B,Add,VB),
2572 (Add=add_underscore
2573 -> atom_concat('_',VB,VB1) % introduce separator; in case we have things like numbers so that (12,3) /= (1,23)
2574 ; VB1=VB % for fields like predicate, transform, ... we do not want additional underscores
2575 ),
2576 atom_concat(VA,VB1,Res).
2577 b_val_to_id_string_aux(Set,Add,Res) :- singleton_set(Set,El),!, b_val_to_id_string_aux(El,Add,Res).
2578 % TODO: maybe convert sequence of values using conc
2579 b_val_to_id_string_aux(FValue,_,Res) :-
2580 translate_bvalue_to_codes(FValue,ValCodes),
2581 atom_codes(Res,ValCodes).
2582
2583 % get either a regular VisB item or an item associated with a VisB event and its enabled status
2584 get_visb_item_formula(SvgID,SvgAttribute,Formula,Pos,_ExpandedBState) :-
2585 visb_item(SvgID,SvgAttribute,Formula,_UsedIds,_Desc,Pos,_). % regular VisB item
2586 get_visb_item_formula(SvgID,SvgAttribute,Formula,Pos,ExpandedBState) :- % item within VisB event
2587 visb_event_enable_list(OpName,TypedPred,EnableList,_,ItemPos),
2588 debug_format(19,'Checking enabledness of VisB event ~w~n',[OpName]),
2589 (check_enabled(OpName,TypedPred,ExpandedBState,ItemPos)
2590 -> Formula=EnabledValExpr
2591 ; Formula=DisabledValExpr
2592 ),
2593 member(visb_enable_item(SvgID,SvgAttribute,EnabledValExpr,DisabledValExpr,Pos), EnableList).
2594
2595 check_enabled(OpName,Pred,ExpandedBState,Pos) :-
2596 special_operation(OpName),!,
2597 special_operation_enabled(OpName,Pred,ExpandedBState,Pos).
2598 check_enabled(OpName,Pred,ExpandedBState,Pos) :-
2599 b_is_operation_name(OpName),
2600 % TODO: see if we can use GUARD without execution
2601 % TODO: not yet working for XTL mode
2602 execute_operation_by_predicate_in_state_with_pos(ExpandedBState,OpName,Pred,_OpTerm,_NewState,Pos).
2603
2604
2605 get_expanded_bstate(StateId,ExpandedBState) :-
2606 \+ b_or_z_mode,!,
2607 StateId \= root,
2608 % in XTL mode we need to access the state via external functions like STATE_PROPERTY
2609 get_static_visb_state([],ExpandedBState).
2610 get_expanded_bstate(StateId,ExpandedBState) :-
2611 visited_expression(StateId,State),
2612 state_corresponds_to_initialised_b_machine(State,BState),
2613 debug_format(19,'Adding VisB definitions to state: ~w~n',[StateId]),
2614 add_prob_deferred_set_elements_to_store(BState,BState2,visible), % add prob_ids
2615 findall(visb_definition(DefID,Type,DefFormula,Class,VPos,Special),
2616 visb_definition(DefID,Type,DefFormula,Class,VPos,Special),DefList),
2617 eval_defs(DefList,BState2,ExpandedBState).
2618
2619
2620 :- use_module(probsrc(b_interpreter), [ b_compute_expression_nowf/7,b_compute_explicit_epression_no_wf/7]).
2621
2622 evaluate_static_visb_formula(Formula,Kind,Nr,InState,ResValue,Pos) :-
2623 get_static_visb_state(InState,StaticState),
2624 evaluate_visb_formula(Formula,Kind,Nr,StaticState,ResValue,Pos).
2625
2626 evaluate_visb_formula(Formula,Kind,Nr,BState2,ResValue,Pos) :-
2627 % add_message(visb,'Evaluating: ',Kind:Nr,Pos), debug:nl_time, %set_prolog_flag(profiling,on), print_profile,
2628 (b_compute_explicit_epression_no_wf(Formula,[],BState2,ResValue,Kind,Nr,Pos) -> true
2629 ; add_error(visb_visualiser,'Evaluation of VisB formula failed:',Formula,Pos),
2630 fail).
2631
2632 % evaluate VisB definitions in order one by one, adding values to state
2633 eval_defs([],State,State).
2634 eval_defs([visb_definition(ID,_,TypedExpr,_Class,VPos,Special)|T],State0,State2) :-
2635 (Special \= regular_def
2636 -> State1=State0 % ignore special defs; they are processed separately
2637 ; b_compute_expression_nowf(TypedExpr,[],State0,ResValue,'VisB definition',ID,VPos),
2638 State1 = [bind(ID,ResValue)|State0], % store value for later definitions and VisB items
2639 (debug_mode(off) -> true
2640 ; translate_bvalue_to_codes_with_limit(ResValue,2000,RC),
2641 formatsilent(' VisB definition ~w == ~s~n',[ID,RC]))
2642 ),
2643 eval_defs(T,State1,State2).
2644
2645 % check if we have a static value for a VisB definition:
2646 visb_def_static_value(DefID,Value) :-
2647 visb_definition(DefID,_,b(value(Value),_,_),Class,_,SpecialClass),
2648 SpecialClass = regular_def,
2649 (Class = requires_nothing ; Class = requires_constants). % probably we do not need to check this, as we have value/1
2650
2651 get_static_visb_state(InState,FullState) :-
2652 findall(bind(DefID,Value),visb_def_static_value(DefID,Value),FullState,InState).
2653 % TO DO: get state with deferred_set_elements,...
2654
2655 % ----------------------------------
2656
2657 % generate a stand-alone HTML file with a visualisation for all states in the list
2658
2659 generate_visb_html(StateIds,File,Options) :-
2660 safe_open_file(File,write,Stream,[encoding(utf8)]),
2661 generate_html_to_stream(StateIds,Stream,[html_file/File|Options]),
2662 close(Stream).
2663
2664 generate_visb_html_to_codes(StateIds,Options,Codes) :-
2665 with_open_stream_to_codes(
2666 generate_html_to_stream(StateIds,Stream,Options),
2667 Stream,Codes,[]).
2668
2669
2670 % generate an HTML file to visualise the given StateId
2671 generate_html_to_stream(StateIds,Stream,Options) :-
2672 set_id_namespace_prefix_for_states(StateIds,Options),
2673 write_visb_template('visb_template_header.html',Stream),
2674 (member(show_svg_downloads,Options) -> write_visb_template('visb_template_svg_downloads.html',Stream) ; true),
2675 format(Stream,' <script>~n',[]),
2676 retractall(js_generated_function(_)),
2677 length(StateIds,Len),
2678 format(Stream,' const differences = [~n',[]),
2679 maplist(gen_visb_visualise_function(Stream,Options,Len,StateIds),StateIds),
2680 write_visb_template('visb_template_replayTrace.html',Stream),
2681 format(Stream,' </script>~n~n',[]),
2682 gen_registerHovers_scipt(Stream,Options),
2683 write_visb_template('visb_template_middle.html',Stream),
2684 (no_svg_available
2685 -> format(Stream,' <button type="button" class="collapsible-style">No SVG Visualisation Available</button>~n',[])
2686 ; % generate SVG section
2687 (member(no_header,Options) -> true
2688 ; format(Stream,' <button type="button" class="collapsible collapsible-style active">SVG Visualisation</button>~n',[])
2689 ),
2690 format(Stream,' <div style="position: relative;">~n',[]), % container for SVG download buttons
2691 format(Stream,' <div text-align="left" id="visb_svg_outer_container" class="svg-outer-container">~n',[]),
2692 format(Stream,' <div id="visb_svg_inner_container" class="svg-inner-container">~n',[]),
2693 %format(Stream,' <fieldset> <legend>Visualisation:</legend>~n',[]), % comment in to draw a border
2694 (StateIds = [SingleStateId] -> GenForState=SingleStateId ; GenForState=root),
2695 copy_svg_file_and_gen_objects(Stream,GenForState,_SVGinlined),
2696 % TO DO: avoid creating JS code below if _SVGinlined
2697 %format(Stream,' </fieldset>~n',[]),
2698 format(Stream,' </div>~n',[]), % inner container
2699 format(Stream,' </div>~n',[]), % outer container
2700 format(Stream,' <button id="btnResetScale" class="visualisation-button" onclick="resetScale()">Reset View</button>~n',[]),
2701 (member(show_svg_downloads,Options) ->
2702 format(Stream,' <button onclick="downloadSVG()">Save SVG (Current State)</button>~n',[]),
2703 format(Stream,' <button onclick="downloadAllSVGs()">Save all SVGs</button>~n',[])
2704 ; true),
2705 format(Stream,' </div>~n',[]) % container for SVG download buttons
2706 ),
2707 (Len>1, memberchk(show_sequence_chart,Options) % don't export PlantUML for list of state IDs (sequence chart depends on trace)
2708 -> (create_temp_puml_files(Len,Files),
2709 uml_generator:write_uml_sequence_chart_all_states(Files), % generate .puml files
2710 tools_commands:gen_plantuml_output(Files,svg,[]) % generate .svg files
2711 -> format(Stream,' <button type="button" class="collapsible collapsible-style active">Sequence Chart Visualisation</button>~n',[]),
2712 format(Stream,' <div class="seq-chart-container">~n',[]),
2713 reverse(Files,RFiles),
2714 write_temp_puml_outputs(1,RFiles,Stream), % write SVG contents to HTML
2715 format(Stream,' </div>~n',[])
2716 ; add_warning(visb_visualiser,'HTML export: did not write the Sequence Diagram Visualisation due to an error in the PlantUML call.'),
2717 format(Stream,' <button type="button" class="collapsible-style">No Sequence Chart Visualisation Available</button>~n',[])
2718 )
2719 ; true),
2720 (Len>1
2721 -> %format(Stream,'~n<h3>Run Trace</h3>~n',[]),
2722 format(Stream,' <button type="button" class="collapsible-style">Replay Trace</button>~n',[]),
2723 format(Stream,' <div class="coll-content-vis">~n',[]),
2724 format(Stream,' <button id="btnPrev" onclick="backStep()" title="Go back one step">« Back</button>~n',[]),
2725 format(Stream,' <button id="btnNext" onclick="forwardStep()" title="Go forward one step">Forward »</button>~n',[]),
2726 format(Stream,' <button onclick="runAll(10)" title="Fast replay of entire trace">Run Trace (10 ms delay)</button>~n',[]),
2727 format(Stream,' <button onclick="runAll(500)" title="Slow replay of entire trace">Run Trace (500 ms delay)</button>~n',[]),
2728 format(Stream,' <button onclick="runAll(parseInt(delayInput.value))" title="Custom replay of entire trace">Run Trace with Delay (ms):</button>~n',[]),
2729 format(Stream,' <input id="delayInput" type="number" value="1000" min="0" step="100" onkeydown="if(event.key===\'Enter\') runAll(parseInt(this.value))">~n',[]),
2730 % We could decide to provide an option/preference for generating the visb_debug_messages field:
2731 % (check that ProB2-UI also generates this text field)
2732 format(Stream,' <br><label id="visb_debug_messages" class="visb-messages"> </label>~n',[]),
2733 format(Stream,' </div>~n',[]),
2734 format(Stream,' <progress id="trace_meter" min="0" max="~w" value="0"></progress>~n',[Len]) % progress of trace replay; note <meter> element also works
2735 ; true
2736 ),
2737 % generate a table with variables, constants, ...
2738 gen_state_table(Stream,Options,StateIds),
2739 gen_source_code_section(Stream,Options),
2740 % generate a table with the saved trace steps:
2741 (Len>1 -> gen_trace_table(Stream,StateIds) ; true),
2742 write_version_info(Stream,Options),
2743 (last(StateIds,_)
2744 -> format(Stream,' <script> replayStep(~w); </script>~n',[Len])
2745 % show the visualisation of the last state by default
2746 ; true % trace is empty, there is no last item
2747 ),
2748 write_visb_template('visb_template_footer.html',Stream),
2749 clear_id_namespace_prefix.
2750
2751 write_file_to_stream(File,Stream) :-
2752 safe_open_file(File,read,StreamIn,[encoding(utf8)]),
2753 copy_stream(StreamIn,Stream),
2754 close(StreamIn).
2755
2756 create_temp_puml_files(Len,[]) :- Len<1, !.
2757 create_temp_puml_files(Len,[Path|T]) :-
2758 system_call:get_temporary_filename('for_html.puml',Path),
2759 NewLen is Len-1,
2760 create_temp_puml_files(NewLen,T).
2761
2762 write_temp_puml_outputs(_,[],_).
2763 write_temp_puml_outputs(Nr,[File|T],Stream) :-
2764 tools:split_filename(File,FileRoot,_Ext),
2765 ajoin([FileRoot,'.svg'],SvgFile),
2766 format(Stream,' <div id="seq_chart_~w" style="display:none">~n',[Nr]), % container for seq. charts
2767 write_file_to_stream(SvgFile,Stream),
2768 format(Stream,' </div>~n',[]), % container for seq. charts
2769 NNr is Nr+1,
2770 write_temp_puml_outputs(NNr,T,Stream).
2771
2772 % -----------------
2773
2774 :- use_module(library(system),[ datime/1]).
2775 :- use_module(probsrc(tools_strings),[number_codes_min_length/3]).
2776 :- use_module(probsrc(tools),[gen_relative_path/3]).
2777 :- use_module(probsrc(version),[version_str/1]).
2778 :- use_module(probsrc(specfile),[currently_opened_file/1, get_internal_representation/1]).
2779 write_version_info(_,Options) :-
2780 member(no_version_info,Options),!.
2781 write_version_info(Stream,Options) :-
2782 version_str(Str),datime(datime(Yr,Mon,Day,Hr,Min,_Sec)),
2783 number_codes_min_length(Min,2,MC),
2784 format(Stream,' <button type="button" class="collapsible-style" title="Information about ProB and model">Info</button>~n',[]),
2785 format(Stream,'<div class="coll-content-vis visb-messages">~n',[]),
2786 format(Stream,'Generated on ~w/~w/~w at ~w:~s using <a href="https://prob.hhu.de/">ProB</a> version ~w~n',[Day,Mon,Yr,Hr,MC,Str]),
2787 (currently_opened_file(File)
2788 -> (File=package(Type) ->
2789 format(Stream,'<br>Main specification package: ~w~n',[Type])
2790 ; atom(File), get_relative_path(File,Options,Suffix) ->
2791 format(Stream,'<br>Main specification file: ~w',[Suffix]),
2792 format_file_info(Stream,File)
2793 ; format(Stream,'<br>Unknown main specification file: ~w~n',[File])
2794 )
2795 ; true),
2796 (b_machine_name(MainName)
2797 -> format(Stream,'<br>Main specification name: ~w~n',[MainName]) ; true),
2798 (visb_file_loaded(JSONFile,_,ModLocTime),
2799 JSONFile \= ''
2800 -> get_relative_path(JSONFile,Options,JSuffix),
2801 format(Stream,'<br>Main VisB JSON file: ~w',[JSuffix]),
2802 format_modified_info(Stream,ModLocTime),
2803 (get_non_empty_svg_file(SVGFile,ModLocTime2)
2804 -> get_relative_path(SVGFile,Options,SSuffix),
2805 format(Stream,'<br>VisB SVG file: ~w',[SSuffix]),
2806 format_modified_info(Stream,ModLocTime2)
2807 ; true
2808 )
2809 ; true).
2810
2811 get_non_empty_svg_file(SVGFile,ModLocTime2) :-
2812 visb_svg_file(RelFile,SVGFile,_,_,ModLocTime2),
2813 RelFile \= ''.
2814
2815 format_file_info(Stream,File) :-
2816 catch(file_property(File, modify_localtime, ModLocTime),
2817 E,
2818 (add_message(visb_visualiser,'Could not obtain modification time for file: ',E), fail)),
2819 !,
2820 format_modified_info(Stream,ModLocTime).
2821 format_file_info(Stream,_) :- nl(Stream).
2822
2823 format_modified_info(Stream,ModLocTime) :-
2824 format(Stream,' (modified on ',[]),
2825 format_datime(Stream,ModLocTime),
2826 format(Stream,')~n',[]).
2827
2828 format_datime(Stream,datime(Yr,Mon,Day,Hr,Min,_Sec)) :-
2829 number_codes_min_length(Min,2,MC),
2830 format(Stream,'~w/~w/~w at ~w:~s',[Day,Mon,Yr,Hr,MC]).
2831
2832 get_relative_path(File,Options,RelPath) :-
2833 member(html_file/HF,Options),
2834 absolute_file_name(File,AF,[]),
2835 absolute_file_name(HF,AHF,[]),
2836 !,
2837 gen_relative_path(AF,AHF,RelPath). % only print relative information
2838 get_relative_path(File,_,File).
2839
2840
2841 % -----------------
2842
2843 % gen a table with all the individual steps of the trace
2844 gen_trace_table(Stream,StateIds) :-
2845 length(StateIds,Len),
2846 %format(Stream,'~n<h3>Trace (length=~w)</h3>~n',[Len]),
2847 format(Stream,' <button type="button" class="collapsible collapsible-style active">Trace (length=~w)</button>~n',[Len]),
2848 format(Stream,'<div class="coll-content-vis">~n',[]),
2849 (member(Obj,StateIds), get_state_and_action(Obj,_,_,DescStr), DescStr \= ''
2850 -> Opt=with_description ; Opt=no_description),
2851 gen_trace_table2(Stream,StateIds,Opt).
2852
2853 gen_trace_table2(Stream,StateIds,no_description) :-
2854 format(Stream,' <table> <tr> <th>Nr</th> <th>Event</th> <th>Target State ID</th> </tr>~n',[]),
2855 nth1(Nr,StateIds,Obj),
2856 get_state_and_action(Obj,StateId,ActionStr,_),
2857 ((visited_state_corresponds_to_initialised_b_machine(StateId) ; xtl_mode) % allow onclick to all rows in xtl_mode
2858 -> (invariant_violated(StateId) -> BtnStyle='style="background-color:rgb(255,179,179);border-radius:6px" ' ; BtnStyle=''),
2859 format(Stream,'~n <tr id="row~w" onclick="replayStep(~w)"><td>~w</td><td style="cursor:pointer">~w</td><td><button ~wonclick="replayStep(~w);">State ~w</button></td></tr>~n',
2860 [Nr,Nr,Nr,ActionStr,BtnStyle,Nr,StateId])
2861 ; format(Stream,'~n <tr id="row~w"><td>~w</td><td style="cursor:not-allowed">~w</td><td>State ~w</td></tr>~n',
2862 [Nr,Nr,ActionStr,StateId])
2863 ),
2864 fail.
2865 gen_trace_table2(Stream,StateIds,with_description) :-
2866 format(Stream,' <table> <tr> <th>Nr</th> <th>Event</th> <th>Description</th> <th>Target State ID</th> </tr>~n',[]),
2867 nth1(Nr,StateIds,Obj),
2868 get_state_and_action(Obj,StateId,ActionStr,DescStr),
2869 atom_codes(ActionStr,ActionCodes),html_escape_codes(ActionCodes,EAS),
2870 atom_codes(DescStr,DescCodes),html_escape_codes(DescCodes,EDS),
2871 ((visited_state_corresponds_to_initialised_b_machine(StateId) ; xtl_mode) % allow onclick to all rows in xtl_mode
2872 -> (invariant_violated(StateId) -> BtnStyle='style="background-color:rgb(255,179,179);border-radius:6px" ' ; BtnStyle=''),
2873 format(Stream,'~n <tr id="row~w" onclick="replayStep(~w)"><td>~w</td><td style="cursor:pointer">~s</td><td>~s</td><td><button ~wonclick="replayStep(~w);">State ~w</button></td></tr>~n',
2874 [Nr,Nr,Nr,EAS,EDS,BtnStyle, Nr,StateId])
2875 ; format(Stream,'~n <tr id="row~w"><td>~w</td><td style="cursor:not-allowed">~s</td><td>~s</td><td>State ~w</td></tr>~n',
2876 [Nr,Nr,EAS,EDS,StateId])
2877 ),
2878 fail.
2879 gen_trace_table2(Stream,_,_) :-
2880 format(Stream,' </table>~n </div>~n',[]).
2881
2882
2883 % utility to allow passing information about name of event/operation/action leading to state
2884 get_state_and_action(change_to_state_via_action(StateId,ActionStr,DescStr),StateId,ActionStr,DescStr) :- !.
2885 get_state_and_action(StateId,StateId,'','').
2886
2887 % -----------------
2888
2889 % inline provided svg file into html file:
2890 % second argument is either root or a particular state id for which the SVG file is to be created
2891 % the last argument is static_svg_inlined if all SVG objects were "inlined" into a single
2892 % SVG object (rather than via JavaScript functions to create the objects)
2893 copy_svg_file_and_gen_objects(Stream,_,static_svg_not_inlined) :- visb_svg_file(_,File,_,_,_), file_exists(File),
2894 !,
2895 write_file_to_stream(File,Stream),
2896 ( get_visb_contents_def(Contents,DefName,DefPos,static_svg_not_inlined),
2897 ajoin(['Copying ',DefName,' *after* SVG file: '],Msg),
2898 add_message(visb_visualiser,Msg,File,DefPos),
2899 format(Stream,'~w~n',[Contents]),
2900 fail
2901 ; true
2902 ),
2903 gen_new_svg_objects(Stream).
2904 copy_svg_file_and_gen_objects(_,_,_) :-
2905 visb_svg_file(File,AFile,_,Pos,_),
2906 File \= '',
2907 add_error(visb_visualiser,'The specified VisB SVG file does not exist:',AFile,Pos),
2908 fail.
2909 copy_svg_file_and_gen_objects(Stream,SingleStateId,static_svg_inlined) :- % copy an empty SVG stub
2910 visb_file_loaded(_,_,_),!,
2911 write_default_svg_contents(Stream,inline_objects(SingleStateId)).
2912 copy_svg_file_and_gen_objects(_,_,static_svg_not_inlined). % no SVG required; we have no items or events: probably just want HTML export of variables,...
2913
2914 % get_code is faster than get_char or read_line for larger SVG files
2915 copy_stream(StreamIn,StreamOut) :-
2916 get_code(StreamIn, Code),
2917 (Code = -1 -> true
2918 ; put_code(StreamOut,Code),
2919 copy_stream(StreamIn,StreamOut)
2920 ).
2921
2922 % TODO: precompile and always assert as visb_special_definition (we could also evaluate it; could use template strings):
2923 get_visb_contents_def(Contents,DefName,DefPos,InlineObjects) :-
2924 get_and_eval_special_definition('VISB_SVG_CONTENTS',DefName,visb_contents,DefPos,ResValue,InlineObjects),
2925 b_value_to_string(ResValue,Contents).
2926 get_visb_contents_def(Contents,default_svg_contents,unknown,_InlineObjects) :-
2927 % default content, for VISB_CLICK_META_INFOS'jsVars
2928 Contents = '<script>let visb_vars = {};</script>'.
2929
2930 % get a definition either from B DEFINITIONS section, or if not present from the VisB JSON special definition list
2931 get_and_eval_special_definition(Prefix,DefName,JSONBackup,DefPos,ResValue,InlineObjects) :-
2932 (b_sorted_b_definition_prefixed(expression,Prefix,DefName,DefPos),
2933 b_get_typed_definition(DefName,[variables_and_additional_defs],TBody)
2934 ;
2935 visb_special_definition(JSONBackup,DefName,_Type,TBody,_Class,DefPos)
2936 ),
2937 % TODO: warn if we use static SVG
2938 get_typed_static_definition_with_constants_state(DefName,TBody,
2939 Body,DefPos,ConstantsState,InlineObjects,no_separation),
2940 evaluate_visb_formula(Body,DefName,'',ConstantsState,ResValue,DefPos).
2941
2942 write_default_svg_contents(Stream,InlineObjects) :-
2943 (visb_empty_svg_box_height_width(H,W,ViewBox) -> true ; H=400, W=400, ViewBox=''),
2944 format(Stream,'<svg xmlns=\"http://www.w3.org/2000/svg\"~n',[]),
2945 (ViewBox=''
2946 -> format(Stream,' width="~w" height="~w" viewBox="0 0 ~w ~w" >~n',[W,H,W,H])
2947 ; format(Stream,' width="~w" height="~w" viewBox="~w" >~n',[W,H,ViewBox])
2948 ),
2949 ( get_visb_contents_def(Contents,_,_,InlineObjects),
2950 format(Stream,'~w~n',[Contents]),
2951 fail
2952 ; true),
2953 (InlineObjects=inline_objects(StateID) -> inline_new_svg_objects(Stream,StateID) ; true),
2954 format(Stream,'</svg>~n',[]).
2955
2956 % get SVG file contents in case no SVG file is provided by user
2957 get_visb_default_svg_file_contents(Codes) :-
2958 with_open_stream_to_codes(
2959 write_default_svg_contents(Stream,inline_objects(root)),
2960 % allow inlining for groups and title children in ProB2-UI
2961 Stream,
2962 Codes, []).
2963
2964 % -----------------
2965
2966 % create a script to add all additional SVG objects
2967 gen_new_svg_objects(_) :- \+ visb_svg_object(_,_,_,_,_),!.
2968 gen_new_svg_objects(Stream) :-
2969 format(Stream, '<script>~n',[]),
2970 format(Stream, ' const svg = document.querySelector("svg");~n',[]),
2971 format(Stream, ' const svgns = "http://www.w3.org/2000/svg";~n',[]),
2972 (gen_new_svg_object(Stream,svg_root,_),fail ; true),
2973 format(Stream, '</script>~n',[]).
2974
2975 % generate JS script to create an individual new object
2976 gen_new_svg_object(Stream,ParentID,SVGID) :-
2977 visb_svg_object(SVGID,SVG_Class,AttrList,_,_Pos),
2978 (ParentID=svg_root
2979 -> (visb_svg_child(SVGID,RealParentID) % only generate root svg objects that have no parents
2980 -> visb_svg_child_of_object_from_svg_file(SVGID) % unless the parent will not be created here in this loop
2981 ; RealParentID=ParentID
2982 )
2983 ; RealParentID=ParentID),
2984 add_svg_id_prefix(SVGID,SVGID2),
2985 format(Stream,' if(document.getElementById("~w") == null) {~n',[SVGID2]),
2986 format(Stream,' var new___obj = document.createElementNS(svgns,"~w");~n',[SVG_Class]),
2987 format(Stream,' new___obj.setAttribute("~w","~w");~n',[id,SVGID2]),
2988 maplist(gen_new_svg_attr(Stream,SVGID2),AttrList),
2989 (RealParentID \= svg_root
2990 -> format(Stream,' document.getElementById("~w").appendChild(new___obj);~n',[RealParentID])
2991 ; format(Stream,' svg.appendChild(new___obj);~n',[])
2992 ),
2993 format(Stream,' }~n',[]),
2994 (visb_svg_parent(SVGID,ChildID), % we can now generate the children
2995 gen_new_svg_object(Stream,SVGID,ChildID),
2996 fail
2997 ; true).
2998
2999 gen_new_svg_attr(Stream,_SVGID,svg_attribute(text,Val)) :- !,
3000 format(Stream,' new___obj.textContent = "~w";~n',[Val]).
3001 gen_new_svg_attr(Stream,_SVGID,svg_attribute(Attr,Val)) :-
3002 format(Stream,' new___obj.setAttribute("~w","~w");~n',[Attr,Val]).
3003
3004 % instead of creating a script to create new SVG objects,
3005 % create an inlined textual XML representation of the objects
3006 % this can be used to obtain a static SVG file which can be modified in an editor
3007 % and then later used instead of the VISB_SVG_OBJECTS definitions
3008 inline_new_svg_objects(Stream,StateId) :-
3009 get_dynamic_svgid_attributes_for_state(StateId,DynUpdateList), % compute updates only once
3010 visb_svg_object(SVGID,_,_,_,_), % lookup static SVG object
3011 \+ visb_svg_child(SVGID,_), % children will be created in the scope of their parent
3012 inline_new_svg_object(Stream,StateId,DynUpdateList,0,unknown,SVGID),
3013 fail.
3014 inline_new_svg_objects(_,_).
3015
3016 inline_new_svg_object(Stream,StateId,DynUpdateList,IndentLevel,ParentPos,SVGID) :-
3017 (visb_svg_object(SVGID,SVG_Class,StaticAttrList,_,Pos) -> true % lookup static SVG object
3018 ; add_warning(visb_visualiser,'Unknown SVG child object: ',SVGID,ParentPos),fail
3019 ),
3020 add_svg_id_prefix(SVGID,SVGID2), % for Jupyter
3021 indent_ws(Stream,IndentLevel),
3022 format(Stream,' <~w id="~w"',[SVG_Class,SVGID2]),
3023 (member(svgid_updates(SVGID,DynAttrList),DynUpdateList) % TODO: use avl_fetch
3024 -> override_attributes(StaticAttrList,DynAttrList,AttrList)
3025 ; AttrList=StaticAttrList),
3026 maplist(format_new_svg_attr(Stream,SVGID,Pos,TextContent),AttrList),
3027 (TextContent=''
3028 -> EscapedTextContent="" % set Text variable to empty if unbound
3029 ; do_not_escape_text_for_class(SVG_Class) -> atom_codes(TextContent,EscapedTextContent)
3030 ; atom_codes(TextContent,TCC), html_escape_codes(TCC,EscapedTextContent)),
3031 format(Stream,'>~s',[EscapedTextContent]), % Note: this text is not inside quotes, we need HTML escape
3032 IL1 is IndentLevel+1,
3033 ( visb_svg_parent(SVGID,Child),
3034 nl(Stream),
3035 inline_new_svg_object(Stream,StateId,DynUpdateList,IL1,Pos,Child),
3036 fail
3037 ; true),
3038 format(Stream,'</~w>~n',[SVG_Class]), % end marker
3039 fail.
3040 inline_new_svg_object(_,_,_,_,_,_).
3041
3042 % for foreignObjects the text may contain HTML tags which should not be escaped:
3043 do_not_escape_text_for_class(foreignObject).
3044 do_not_escape_text_for_class(script). % otherwise " quotes will be escaped to "
3045
3046 indent_ws(_,X) :- X<1,!.
3047 indent_ws(Stream,X) :- write(Stream,' '), X1 is X-1, indent_ws(Stream,X1).
3048
3049 % combinde svg_attribute/2 terms from two sorted lists, giving precedence to second list
3050 override_attributes([],L,R) :- !, R=L.
3051 override_attributes(L,[],R) :- !, R=L.
3052 override_attributes([svg_attribute(Attr1,Val1)|T1],[svg_attribute(Attr2,Val2)|T2],[svg_attribute(Attr3,Val3)|T3]) :-
3053 (Attr1=Attr2
3054 -> Attr3=Attr1, Val3=Val2, % dynamic value Val2 takes precedence
3055 override_attributes(T1,T2,T3)
3056 ; Attr1 @< Attr2 -> Attr3=Attr1, Val3=Val1, override_attributes(T1,[svg_attribute(Attr2,Val2)|T2],T3)
3057 ; Attr3=Attr2, Val3=Val2, override_attributes([svg_attribute(Attr1,Val1)|T1],T2,T3)
3058 ).
3059
3060 % get dynamic svg_attribute/2 list for a given state and SVG ID
3061 get_dynamic_svgid_attributes_for_state(root,List) :- !, List=[].
3062 get_dynamic_svgid_attributes_for_state(StateId,UpdateList) :-
3063 get_visb_attributes_for_state(StateId,List),
3064 sort(List,SList),
3065 group_set_attr(SList,'$$UNKNOWN$$',_,UpdateList).
3066
3067 group_set_attr([],_,[],[]).
3068 group_set_attr([set_attr(SvgID,Attr,Val)|T],SvgID,[svg_attribute(Attr,Val)|T1],T2) :- !,
3069 group_set_attr(T,SvgID,T1,T2).
3070 group_set_attr([set_attr(SvgID,Attr,Val)|T],_OldID,[],[svgid_updates(SvgID,L)|T2]) :- % a new SVGId is encountered
3071 group_set_attr([set_attr(SvgID,Attr,Val)|T],SvgID,L,T2).
3072
3073 % print svg attribute and extract text attribute
3074 format_new_svg_attr(Stream,SVGID,Pos,TextContent,svg_attribute(Attr,Val)) :- % TODO: text content
3075 (Attr=text
3076 -> (TextContent=Val -> true % TextContent is inially a variable and can be unified once
3077 ; add_warning(inline_new_svg_objects,'Multiple text attributes for: ',SVGID,Pos),
3078 add_debug_message(inline_new_svg_objects,' * Using text 1: ',TextContent),
3079 add_debug_message(inline_new_svg_objects,' * Ignoring text 2: ',Val)
3080 )
3081 ; number(Val) ->
3082 format(Stream,' ~w="~w"',[Attr,Val])
3083 ; escape_value_to_codes_for_js(Val,ECodes) ->
3084 format(Stream,' ~w="~s"',[Attr,ECodes])
3085 ; compound(Val), functor(Val,F,N) ->
3086 ajoin(['Cannot escape ',Attr,' *compound* ',F,'/',N,' value for ', SVGID,': '],Msg),
3087 add_error(visb_visualiser,Msg,Val,Pos),
3088 format(Stream,' ~w="~w"',[Attr,Val])
3089 ; ajoin(['Cannot escape ',Attr,' value for ', SVGID,': '],Msg),
3090 add_error(visb_visualiser,Msg,Val,Pos),
3091 format(Stream,' ~w="~w"',[Attr,Val])
3092 ).
3093
3094
3095 :- dynamic id_namespace_prefix/1.
3096 % prefix that can be useful for Jupyter notebooks so that for each state we have a different namespace
3097 % can also be useful for exporting a trace into a single HTML
3098 % TODO: does not work with JSON and SVG files
3099
3100 :- use_module(probsrc(gensym),[gensym/2]).
3101 set_id_namespace_prefix_for_states(_,Options) :-
3102 member(id_namespace_prefix(Pre),Options),!,
3103 (Pre = auto
3104 -> gensym('visb',ID), % for Jupyter this relies on the fact the gensym is *not* reset when loading another spec
3105 atom_concat(ID,'.',Prefix)
3106 ; Prefix=Pre
3107 ), set_id_namespace_prefix(Prefix).
3108 set_id_namespace_prefix_for_states(_,_).
3109
3110 set_id_namespace_prefix(Prefix) :- clear_id_namespace_prefix,
3111 assert(id_namespace_prefix(Prefix)).
3112 clear_id_namespace_prefix :- retractall(id_namespace_prefix(_)).
3113
3114 % add a namespace prefix to an SVG ID
3115 add_svg_id_prefix(SvgID,Res) :- id_namespace_prefix(Prefix),!,
3116 % option where we prefix all Ids with a namespace for Jupyter to combine multiple SVGs in single HTML page
3117 atom_concat(Prefix,SvgID,Res).
3118 add_svg_id_prefix(SvgID,SvgID).
3119
3120 % only add for known objects
3121 opt_add_svg_id_prefix(SvgID,Res) :- id_namespace_prefix(Prefix),
3122 visb_svg_object(SvgID,_,_,_,_),!, % only add prefix for SVG objects we know about (that were created by VisB)
3123 % option where we prefix all Ids with a namespace for Jupyter to combine multiple SVGs in single HTML page
3124 atom_concat(Prefix,SvgID,Res).
3125 opt_add_svg_id_prefix(SvgID,SvgID).
3126
3127 % -----------------
3128
3129 :- dynamic js_generated_function/1.
3130 :- dynamic last_attribute_values/3.
3131
3132 % define a visualise JS function to set the attributes for the given StateId
3133 gen_visb_visualise_function(Stream,Options,Len,StateIds,Obj) :-
3134 get_state_and_action(Obj,StateId,ActionStr,DescStr),
3135 nth1(Nr,StateIds,Obj),
3136 \+ js_generated_function(Nr), !,
3137 assertz(js_generated_function(Nr)),
3138 (Nr > 1 ->
3139 PrevNr is Nr-1, nth1(PrevNr,StateIds,PrevObj), get_state_and_action(PrevObj,PrevStateId,_,_)
3140 ; PrevStateId = -1),
3141 visb_visualise_function_aux(Stream,Options,Len,StateId,PrevStateId,Nr,ActionStr,DescStr),
3142 (Nr == Len ->
3143 retractall(last_attribute_values(_,_,_)),
3144 format(Stream,' ]~n',[])
3145 ; true).
3146 gen_visb_visualise_function(_,_,_,_,_).
3147
3148 :- use_module(extrasrc(bvisual2), [bv_get_top_level/1,bv_get_value_unlimited/3]).
3149 :- use_module(probsrc(tools),[string_escape/2]).
3150 visb_visualise_function_aux(Stream,_,Len,StateId,_,Nr,ActionStr,DescStr) :-
3151 format(Stream,' [~n',[]),
3152 (Len>1 -> format(Stream,' {id: "trace_meter", attr: "value", val: "~w"},~n',[Nr]) ; true),
3153 (escape_value_to_codes_for_js(ActionStr,EAS), escape_value_to_codes_for_js(DescStr,EDS) ->
3154 % was only string_escape before; however, this turns e.g. |-> into ↦ which we don't want (we are in JS part here)
3155 format(Stream,' {id: "visb_debug_messages", attr: "text", val: "Step ~w/~w, State ID: ~w, Event: ~s ~s"},~n',[Nr,Len,StateId,EAS,EDS])
3156 ; string_escape(ActionStr,SEAS), string_escape(DescStr,SEDS), % fallback
3157 format(Stream,' {id: "visb_debug_messages", attr: "text", val: "Step ~w/~w, State ID: ~w, Event: ~w ~w"},~n',[Nr,Len,StateId,SEAS,SEDS])
3158 ),
3159 get_change_attribute_for_state(StateId,SvgID,SvgAttribute,Value),
3160 \+ last_attribute_values(SvgID,SvgAttribute,Value),
3161 retractall(last_attribute_values(SvgID,SvgAttribute,_)),
3162 assertz(last_attribute_values(SvgID,SvgAttribute,Value)),
3163 opt_add_svg_id_prefix(SvgID,SvgID2),
3164 (escape_value_to_codes_for_js(Value,ECodes)
3165 -> format(Stream,' {id: "~w", attr: "~w", val: "~s"},~n',[SvgID2,SvgAttribute,ECodes])
3166 ; format(Stream,' {id: "~w", attr: "~w", val: "~w"},~n',[SvgID2,SvgAttribute,Value])
3167 ),
3168 fail.
3169 visb_visualise_function_aux(Stream,Options,Len,StateId,PrevStateId,_,_,_) :-
3170 b_or_z_mode,
3171 member(show_variables(VarList),Options),
3172
3173 visited_expression(StateId,State),
3174 (visited_expression(PrevStateId,PrevState) -> true ; PrevState=root),
3175
3176 show_var_in_visb(VarList,ID),
3177 get_state_value_change(StateId,State,ID,Options,ResValCodes),
3178
3179 % current value:
3180 ajoin(['bVar_',ID],SvgID),
3181 change_svg_attribute_differences_aux(Stream,SvgID,'text',ResValCodes),
3182
3183 Len > 1, % don't add previous value and change markers for state-only HTML
3184 (state_corresponds_to_fully_setup_b_machine(PrevState,_), % don't show prev values before initialisation
3185 get_state_value_change(PrevStateId,PrevState,ID,Options,PrevResValCodes)
3186 -> true
3187 ; PrevResValCodes = "?"),
3188
3189 % mark row if value has changed in the last step
3190 ajoin(['row_bVar_',ID],SvgRowID),
3191 (ResValCodes = PrevResValCodes -> RowColor = white; RowColor = '#fffacd'),
3192 change_svg_attribute_differences_aux(Stream,SvgRowID,'bgcolor',RowColor),
3193
3194 % previous value:
3195 ajoin(['bVarPrev_',ID],SvgPrevID),
3196 change_svg_attribute_differences_aux(Stream,SvgPrevID,'text',PrevResValCodes),
3197
3198 fail.
3199 visb_visualise_function_aux(Stream,_Options,Len,StateId,PrevStateId,_,_,_) :-
3200 xtl_mode,
3201
3202 bv_get_top_level(IDs),
3203 member(ID,IDs),
3204 (bv_get_value_unlimited(ID,StateId,v(Val))
3205 -> atom_codes(Val,ResValCodes)
3206 ; ResValCodes = ""),
3207
3208 % current value:
3209 ajoin(['bVar_',ID],SvgID),
3210 change_svg_attribute_differences_aux(Stream,SvgID,'text',ResValCodes),
3211
3212 Len > 1, % don't add previous value and change markers for state-only HTML
3213 (PrevStateId \= root,
3214 bv_get_value_unlimited(ID,PrevStateId,v(PrevVal))
3215 -> atom_codes(PrevVal,PrevResValCodes)
3216 ; PrevResValCodes = ""),
3217
3218 % mark row if value has changed in the last step
3219 ajoin(['row_bVar_',ID],SvgRowID),
3220 (ResValCodes = PrevResValCodes -> RowColor = white; RowColor = '#fffacd'),
3221 change_svg_attribute_differences_aux(Stream,SvgRowID,'bgcolor',RowColor),
3222
3223 % previous value:
3224 ajoin(['bVarPrev_',ID],SvgPrevID),
3225 change_svg_attribute_differences_aux(Stream,SvgPrevID,'text',PrevResValCodes),
3226
3227 fail.
3228 visb_visualise_function_aux(Stream,Options,_,StateId,_,_,_,_) :-
3229 member(show_events(OpList),Options),
3230 get_state_value_enabled_operation_status(StateId,OpID,Enabled,ResValCodes,TransStr),
3231 show_var_in_visb(OpList,OpID),
3232 ajoin(['bOperation_',OpID],SvgID),
3233 \+ last_attribute_values(SvgID,'text',ResValCodes),
3234 retractall(last_attribute_values(SvgID,'text',_)),
3235 assertz(last_attribute_values(SvgID,'text',ResValCodes)),
3236 format(Stream,' {id: "~w", attr: "text", val: "~s"},~n',[SvgID,ResValCodes]),
3237 (Enabled=true -> BGCol=white ; BGCol='#f1f1f1'),
3238 format(Stream,' {id: "row_~w", attr: "bgcolor", val: "~s"},~n',[SvgID,BGCol]),
3239 escape_value_to_codes_for_js(TransStr,ETS),
3240 format(Stream,' {id: "name_~w", attr: "text", val: "~s"},~n',[SvgID,ETS]),
3241 % TO DO: highlight next event in trace, but then function needs one more parameter
3242 fail.
3243 visb_visualise_function_aux(Stream,Options,Len,_,_,Nr,_,_) :-
3244 (Len>1, member(show_sequence_chart,Options)
3245 -> format(Stream,' {id: "seq_chart_~w", attr: "style", val: "display:block"},~n',[Nr]),
3246 (Nr>1
3247 -> PNr is Nr-1, format(Stream,' {id: "seq_chart_~w", attr: "style", val: "display:none"},~n',[PNr])
3248 ; gen_seq_charts_setup(Stream,Len))), % all sequence charts except the first should be invisible
3249 fail.
3250 visb_visualise_function_aux(Stream,_,Len,_,_,Nr,_,_) :-
3251 Nr == Len ->
3252 format(Stream,' ]~n',[])
3253 ; format(Stream,' ],~n',[]).
3254
3255 gen_seq_charts_setup(_,Len) :- Len<2, !.
3256 gen_seq_charts_setup(Stream,Len) :-
3257 format(Stream,' {id: "seq_chart_~w", attr: "style", val: "display:none"},~n',[Len]),
3258 NLen is Len-1,
3259 gen_seq_charts_setup(Stream,NLen).
3260
3261 escape_value_to_codes_for_js(Atom,ECodes) :- atom(Atom),
3262 atom_codes(Atom,Codes), b_string_escape_codes(Codes,ECodes).
3263
3264 change_svg_attribute_differences_aux(Stream,ID,Attr,ValueCodes) :-
3265 (last_attribute_values(ID,Attr,ValueCodes)
3266 -> true
3267 ; retractall(last_attribute_values(ID,Attr,_)),
3268 assertz(last_attribute_values(ID,Attr,ValueCodes)),
3269 format(Stream,' {id: "~w", attr: "~w", val: "~s"},~n',[ID,Attr,ValueCodes])
3270 ).
3271
3272
3273
3274 % generate JS script to register hovers
3275 gen_registerHovers_scipt(Stream,Options) :- \+ visb_has_hovers(_),
3276 nonmember(debugging_hovers,Options),
3277 !, % no hover exists
3278 format(Stream,' <script> function registerHovers() {} </script>~n',[]).
3279 gen_registerHovers_scipt(Stream,Options) :-
3280 (member(debugging_hovers,Options) -> GenDebug=true ; GenDebug=false), % gen debugging hovers
3281 % Jquery is no longer required:
3282 %format(Stream,' <script src="https://ajax.googleapis.com/ajax/libs/jquery/3.6.0/jquery.min.js"></script>~n',[]),
3283 format(Stream,' <script>~n',[]),
3284 format(Stream,' function registerHovers() {~n',[]),
3285 format(Stream,' var obj;~n',[]),
3286 visb_has_hovers(SVGID), % only generate hover function if necessary; TODO: examine other IDs for GenDebug
3287 opt_add_svg_id_prefix(SVGID,SVGID2),
3288 format(Stream,' obj = document.getElementById("~w");~n',[SVGID2]),
3289 format(Stream,' obj.onmouseover = function(ev){~n',[]),
3290 (visb_hover(SVGID,ID,Attr,EnterVal,_,_),
3291 opt_add_svg_id_prefix(ID,ID2),
3292 (GenDebug=false -> true
3293 ; format(Stream,' setAttr("~w","~w","SVG ID: ~w")~n',[visb_debug_messages,text,SVGID2])),
3294 format(Stream,' setAttr("~w","~w","~w")~n',[ID2,Attr,EnterVal]), fail ;
3295 format(Stream,' };~n',[])
3296 ),
3297 format(Stream,' obj.onmouseout = function(){~n',[]),
3298 (visb_hover(SVGID,ID,Attr,_,LeaveVal,_),
3299 opt_add_svg_id_prefix(ID,ID2),
3300 (GenDebug=false -> true
3301 ; format(Stream,' setAttr("~w","~w","~w")~n',[visb_debug_messages,text,'...'])
3302 ),
3303 format(Stream,' setAttr("~w","~w","~w")~n',[ID2,Attr,LeaveVal]), fail ;
3304 format(Stream,' };~n',[])
3305 ),
3306 fail.
3307 gen_registerHovers_scipt(Stream,_) :-
3308 format(Stream,' }~n </script>~n',[]).
3309
3310
3311 % ----------------------------------
3312
3313 :- use_module(probsrc(translate),[set_unicode_mode/0, unset_unicode_mode/0]).
3314 :- use_module(probsrc(state_space), [get_action_trace_with_limit/2, get_state_id_trace/1]).
3315
3316 generate_visb_html_for_history_with_source(File) :-
3317 generate_visb_html_for_history(File,
3318 [show_constants(all),show_sets(all),show_variables(all),show_events(all),show_invariants,show_source]).
3319 generate_visb_html_for_history_with_vars(File) :-
3320 generate_visb_html_for_history(File,[show_constants(all),show_sets(all),show_variables(all),show_events(all)]).
3321 generate_visb_html_for_history(File) :-
3322 generate_visb_html_for_history(File,[]).
3323 generate_visb_html_for_history(File,Options) :-
3324 start_ms_timer(Timer),
3325 get_state_id_trace(T),
3326 T = [root|StateIds],
3327 set_unicode_mode,
3328 call_cleanup(get_action_trace_with_limit(120,Actions), % TODO: also get description of JSON traces
3329 unset_unicode_mode),
3330 reverse(Actions,FActions),
3331 combine_state_and_actions(StateIds,[root|StateIds],FActions,List),
3332 generate_visb_html(List,File,Options),
3333 stop_ms_walltimer_with_msg(Timer,'exporting history to VisB HTML file: ').
3334
3335 :- use_module(probsrc(specfile),[get_operation_description_for_transition/4]).
3336 combine_state_and_actions([],_,[],[]).
3337 combine_state_and_actions([StateId|TS],[PrevId|TP],[action(ActionStr,ATerm)|TA],
3338 [change_to_state_via_action(StateId,ActionStr,Desc)|TRes]) :-
3339 (get_operation_description_for_transition(PrevId,ATerm,StateId,D) -> Desc=D ; Desc=''),
3340 combine_state_and_actions(TS,TP,TA,TRes).
3341
3342 generate_visb_html_for_current_state(File) :-
3343 generate_visb_html_for_current_state(File,[show_variables(all)]).
3344 generate_visb_html_for_current_state(File,Options) :-
3345 start_ms_timer(Timer),
3346 current_state_id(ID),
3347 generate_visb_html([ID],File,Options),
3348 stop_ms_walltimer_with_msg(Timer,'exporting current state to VisB HTML file: ').
3349 generate_visb_html_codes_for_states(StateIds,Options,Codes) :-
3350 generate_visb_html_to_codes(StateIds,Options,Codes). % write to codes list
3351
3352 % ------------------------------
3353
3354 :- use_module(probsrc(specfile),[b_or_z_mode/0]).
3355 :- use_module(probsrc(bmachine), [b_get_machine_variables/1, b_get_machine_constants/1, b_top_level_operation/1]).
3356 :- use_module(probsrc(bsyntaxtree), [get_texpr_id/2]).
3357 :- use_module(extrasrc(bvisual2), [bv_top_level_set/2]).
3358 :- use_module(probsrc(specfile),[get_specification_description/2]).
3359 :- use_module(probsrc(tools_strings), [atom_tail_to_lower_case/2]).
3360
3361 show_typed_var_in_visb(all,_) :- !.
3362 show_typed_var_in_visb(VarList,b(identifier(ID),_,_)) :- !, show_var_in_visb(VarList,ID).
3363 show_var_in_visb(VarList,ID ) :- (VarList=all -> true ; member(ID,VarList) -> true).
3364
3365 % generate a table for the state (we could use bvisual2)
3366 gen_state_table(Stream,Options,StateIds) :-
3367 b_or_z_mode,
3368 member(show_variables(VarList),Options),
3369 b_get_machine_variables(TypedVars),
3370 % is this useful if Len > 1, but StateIds are not from a trace? (see also below for formulas)
3371 (length(StateIds,Len), Len > 1 -> NOptions = [show_prev_value|Options] ; NOptions = Options),
3372 gen_state_table_aux(Stream,NOptions,'Variables',TypedVars,VarList,[],'Value','bVar_'),fail.
3373 gen_state_table(Stream,Options,StateIds) :-
3374 b_or_z_mode,
3375 member(show_variables(VarList),Options),
3376 b_get_machine_expressions(AExprs,Options), AExprs \= [],
3377 (length(StateIds,Len), Len > 1 -> NOptions = [show_prev_value|Options] ; NOptions = Options),
3378 gen_state_table_aux(Stream,NOptions,'Formulas',AExprs,VarList,[],'Value','bVar_'),fail.
3379 gen_state_table(Stream,Options,StateIds) :-
3380 b_or_z_mode,
3381 member(show_constants(IDList),Options),
3382 b_get_machine_constants(TypedVars),
3383 last(StateIds,Last), % we assume there is only one constant valuation in the trace; TO DO: generalise
3384 get_state_and_action(Last,LastId,_,_),
3385 visited_expression(LastId,BState),
3386 expand_to_constants_and_variables(BState,ConstState,_),
3387 gen_state_table_aux(Stream,Options,'Constants',TypedVars,IDList,ConstState,'Value','bConstant_'),fail.
3388 gen_state_table(Stream,Options,_) :-
3389 b_or_z_mode,
3390 member(show_sets(IDList),Options),
3391 findall(TSet,bv_top_level_set(TSet,_),TypedVars),
3392 findall(bind(Set,Val),(bv_top_level_set(TSet,Val),get_texpr_id(TSet,Set)),BState),
3393 gen_state_table_aux(Stream,Options,'Sets',TypedVars,IDList,BState,'Value','bSet_'),fail.
3394 % TO DO: maybe show also top-level guards specfile_possible_trans_name or get_top_level_guard
3395 gen_state_table(Stream,Options,_StateIds) :-
3396 b_or_z_mode,
3397 member(show_events(IDList),Options),
3398 get_specification_description(operations,SN),
3399 atom_tail_to_lower_case(SN,SectionName),
3400 findall(b(identifier(OpName),subst,[]),b_top_level_operation(OpName),TypedVars),
3401 % TODO: op(Params,Results) instead of subst
3402 gen_state_table_aux(Stream,Options,SectionName,TypedVars,IDList,[],'Enabled','bOperation_'),fail.
3403 gen_state_table(Stream,Options,StateIds) :-
3404 xtl_mode,
3405 (length(StateIds,Len), Len > 1 -> NOptions = [show_prev_value|Options] ; NOptions = Options),
3406 bv_get_top_level(IDs),
3407 findall(b(identifier(ID),string,[]), member(ID,IDs), Props),
3408 gen_state_table_aux(Stream,NOptions,'Properties',Props,IDs,[],'Value','bVar_'), fail.
3409 gen_state_table(_Stream,_,_).
3410
3411
3412 gen_source_code_section(Stream,Options) :-
3413 member(show_source,Options), % we could also include original sources, rather than just internal rep.
3414 !,
3415 Section = 'Source',
3416 format(Stream,' <button type="button" class="collapsible collapsible-style" title="Inspect source code of internal representation of ProB of model">~w</button>~n',[Section]),
3417 format(Stream,'<div class="coll-content-hid">~n',[]),
3418 get_internal_representation(PP),
3419 format(Stream,'<pre>~s</pre>~n',[PP]),
3420 format(Stream,'</div>~n',[]).
3421 gen_source_code_section(_Stream,_).
3422
3423
3424 :- use_module(probsrc(bsyntaxtree),[get_texpr_description/2, get_texpr_type/2]).
3425 % creates a HTML table with header name Section and including one row per ID in TypedVars;
3426 % id of value for ID is prefixed with IDPrefix
3427 % VarListToShow is either all or a list of ids
3428 gen_state_table_aux(Stream,Options,Section,TypedVars,VarListToShow,BState,ValueStr,IDPrefix) :-
3429 include(show_typed_var_in_visb(VarListToShow),TypedVars,SVars), % check which ids should be shown
3430 length(SVars,SLen), SLen>0,
3431 length(TypedVars,Len),
3432 (SLen=Len
3433 -> format(Stream,' <button type="button" class="collapsible collapsible-style">~w (~w)</button>~n',[Section,SLen])
3434 ; format(Stream,' <button type="button" class="collapsible collapsible-style">~w (~w/~w)</button>~n',
3435 [Section,SLen,Len])
3436 ),
3437 format(Stream,'<div class="coll-content-hid">~n',[]),
3438 (member(show_prev_value,Options) % add extra column for previous value of variables (and animation expressions)
3439 -> format(Stream,' <table> <tr> <th>Nr</th> <th>Name</th> <th>Value</th> <th>Previous Value</th> </tr>~n',[])
3440 ; format(Stream,' <table> <tr> <th>Nr</th> <th>Name</th> <th>~w</th> </tr>~n',[ValueStr])),
3441 ( nth1(Nr,SVars,IDorExprToShow),
3442 get_state_table_name_and_expr(IDorExprToShow,ID,LongID,TExpr),
3443 (get_state_value_codes_for_id(BState,ID,Options,_,ValCodes)
3444 -> html_escape_codes(ValCodes,EVC) % Value provided in BState; may be overriden in trace export
3445 ; EVC = "?"),
3446 get_table_hover_message_codes(ID,TExpr,HoverMsgC),
3447 (member(show_prev_value,Options) % add previous value of variables (and animation expressions)
3448 -> % for variables the values are added later in JS
3449 % do we want to show the previous value in the state only HTML?
3450 format(Stream,'~n <tr id="row_~w~w" title="~s"> <td>~w</td> <td id="name_~w~w">~w</td> <td id="~w~w">?</td> <td id="bVarPrev_~w">?</td> </tr>~n',
3451 [IDPrefix,ID, HoverMsgC, Nr, IDPrefix,ID,LongID, IDPrefix,ID, ID ])
3452 ;
3453 format(Stream,'~n <tr id="row_~w~w" title="~s"> <td>~w</td> <td id="name_~w~w">~w</td> <td id="~w~w">~s</td> </tr>~n',
3454 [IDPrefix,ID, HoverMsgC, Nr, IDPrefix,ID,LongID, IDPrefix,ID,EVC])),
3455 fail
3456 ;
3457 format(Stream,' </table>~n </div>~n',[])
3458 ).
3459
3460 %get_state_table_name_and_expr(bexpr(Kind,TExpr),Name,LongName,Expr) :- !, % we have special expression to show
3461 % Name=Kind,LongName=Kind,Expr=TExpr.
3462 get_state_table_name_and_expr(bexpr(Kind,TExpr),ID,LongName,Expr) :- !, % we have special expression to show
3463 ID=Kind, % ID for SVG updates, ...
3464 translate_bexpression_with_limit(TExpr,200,TS),
3465 ajoin([Kind,' == ',TS],LongName),
3466 Expr=TExpr.
3467 get_state_table_name_and_expr(TID,ID,ID,TID) :- get_texpr_id(TID,ID). % normal case: variable name
3468
3469
3470 :- use_module(probsrc(bmachine),[b_get_machine_animation_expression/2, b_get_operation_variant/3, b_nth1_invariant/3]).
3471
3472 visb_machine_animation_expression(variant,AEName,Variant,_) :-
3473 b_get_operation_variant(Name,ConvOrAnt,Variant),
3474 ajoin(['Variant for ',Name, ' (',ConvOrAnt,')'],AEName).
3475 visb_machine_animation_expression(animation_expression,Name,TExpr,_) :-
3476 b_get_machine_animation_expression(Name,TExpr).
3477 visb_machine_animation_expression(invariant,Name,TPred,Options) :-
3478 member(show_invariants,Options),
3479 b_nth1_invariant(Nr,TPred,_),
3480 ajoin(['INVARIANT-',Nr],Name).
3481 % TODO: we should also adapt get_state_value_change to return true when invariant_violated is false for the state
3482 % we could also only include this section when there is an invariant violation in the trace?
3483
3484 b_get_machine_expressions(List,Options) :-
3485 findall(bexpr(AE_Name,AExpr),visb_machine_animation_expression(_,AE_Name,AExpr,Options),List).
3486 % 'ANIMATION_EXPRESSION' or invariants or variants
3487
3488 :- use_module(probsrc(bmachine),[b_get_machine_operation_signature/2]).
3489 % get hover message for entries in variables/constants/... rows:
3490 get_table_hover_message_codes(ID,TExpr,EscHoverMsg) :-
3491 get_texpr_type(TExpr,Type),
3492 (Type=subst,b_get_machine_operation_signature(ID,TS)
3493 -> ajoin(['Operation: ',TS],HoverMsg)
3494 ; pretty_type(Type,TS),
3495 (get_texpr_description(TExpr,Desc)
3496 -> ajoin(['Type: ',TS,'\nDesc: ',Desc],HoverMsg)
3497 ; ajoin(['Type: ',TS],HoverMsg)
3498 )
3499 ),
3500 atom_codes(HoverMsg,HoverCodes),
3501 html_escape_codes(HoverCodes,EscHoverMsg).
3502
3503 % get the values that should be displayed in the variables table
3504 get_state_value_change(StateId,State,ID,Options,ECodes) :-
3505 extract_variables_from_state(State,VariableBState),
3506 ( get_state_value_codes_for_id(VariableBState,ID,Options,Val,ValCodes) % look up variable values
3507 ; visb_machine_animation_expression(_,_,_,Options) ->
3508 state_corresponds_to_fully_setup_b_machine(State,FullState),
3509 get_state_value_codes_for_anim_expr(StateId,FullState,ID,Options,Val,ValCodes) % evaluate animation expressions
3510 ),
3511 escape_if_necessary(Val,ValCodes,ECodes). % change " to \" for JavaScript
3512 % formatsilent('Value for ~w~nunescaped: "~s",~n escaped: "~s"~n',[ID,ValCodes,ECodes]).
3513
3514 % avoid unnecessary escaping traversals:
3515 escape_if_necessary([],ValCodes,Res) :- !, Res=ValCodes.
3516 escape_if_necessary(int(_),ValCodes,Res) :- !, Res=ValCodes.
3517 escape_if_necessary(pred_true,ValCodes,Res) :- !, Res=ValCodes.
3518 escape_if_necessary(pred_false,ValCodes,Res) :- !, Res=ValCodes.
3519 escape_if_necessary(_,ValCodes,ECodes) :- b_string_escape_codes(ValCodes,ECodes).
3520
3521
3522 get_state_value_codes_for_id(BState,ID,Options,Val,ValCodes) :-
3523 member(bind(ID,Val),BState),
3524 translate_values_for_state_table(Val,Options,ValCodes).
3525
3526 % translate a value for display in state table (not yet escaped)
3527 translate_values_for_state_table(Val,Options,ValCodes) :-
3528 (member(limit_for_values(Nr),Options)
3529 -> translate_bvalue_to_codes_with_limit(Val,Nr,ValCodes)
3530 ; get_preference(expand_avl_upto,Max), Max<0
3531 -> translate_bvalue_to_codes(Val,ValCodes) % unlimited
3532 ; translate_bvalue_to_codes_with_limit(Val,10000,ValCodes)
3533 ).
3534
3535 :- use_module(probsrc(bsyntaxtree), [safe_create_texpr/3]).
3536 get_state_value_codes_for_anim_expr(StateId,BState,AE_Name,Options,ResValue,ValCodes) :-
3537 visb_machine_animation_expression(Kind,AE_Name,AExpr,Options),
3538 (Kind=invariant
3539 -> ((invariant_not_yet_checked(StateId) ; invariant_violated(StateId))
3540 -> (safe_create_texpr(convert_bool(AExpr),boolean,TExpr),
3541 evaluate_visb_formula(TExpr,AE_Name,'',BState,ResValue,unknown)
3542 -> translate_pred_val(ResValue,ValCodes)
3543 ; ResValue=pred_unknown, ValCodes = "?" % WD error?
3544 )
3545 ; ResValue=pred_true, translate_pred_val(pred_true,ValCodes) % no need to evaluate invariant
3546 )
3547 ; evaluate_visb_formula(AExpr,AE_Name,'',BState,ResValue,unknown),
3548 translate_values_for_state_table(ResValue,Options,ValCodes)
3549 ).
3550 translate_pred_val(pred_true,[8868]). % see translate:unicode_translation(truth,X).
3551 translate_pred_val(pred_false,[8869]). % see translate:unicode_translation(falsity,X).
3552
3553 :- use_module(probsrc(bmachine),[b_get_machine_operation_max/2]).
3554 :- use_module(probsrc(state_space),[time_out_for_node/3,max_reached_for_node/1]).
3555 :- use_module(probsrc(translate),[translate_event_with_src_and_target_id/5]).
3556 get_state_value_enabled_operation_status(StateId,OpName,Enabled,EnabledValue,TransStr) :-
3557 b_top_level_operation(OpName),
3558 findall(TransID, (transition(StateId,OpTerm,TransID,_NewStateId),
3559 match_operation(OpTerm,OpName)), TransList),
3560 length(TransList,Len),
3561 (Len>0
3562 -> Enabled=true,
3563 EnabledValue = "\x2705\", % green check mark, TRUE alternatives \x2705\ \x2713\ \x2714\
3564 (TransList=[TID], transition(StateId,OpTerm,TID,NewStateId),
3565 translate_event_with_src_and_target_id(OpTerm,StateId,NewStateId,200,TransStr)
3566 -> true
3567 ; ajoin([OpName,' (',Len,'\xd7\)'],TransStr) %
3568 )
3569 ; time_out_for_node(StateId,OpName,TypeOfTimeOut) ->
3570 Enabled=TypeOfTimeOut,
3571 EnabledValue = [8987], % four o'clock symbol
3572 TransStr = OpName
3573 %ajoin(['No transition found due to: ',TypeOfTimeOut],HoverMsg)
3574 ; get_preference(maxNrOfEnablingsPerOperation,0) ->
3575 Enabled=not_computed,
3576 EnabledValue = [10067], % red question mark
3577 TransStr = OpName
3578 %'No transitions were computed because MAX_OPERATIONS = 0' = HoverMsg
3579 ; b_get_machine_operation_max(OpName,0) ->
3580 Enabled=not_computed,
3581 EnabledValue = [10067], % red question mark
3582 TransStr = OpName
3583 %ajoin(['No transitions were computed because MAX_OPERATIONS_',OpName,' = 0'],HoverMsg)
3584 ; Enabled=false,
3585 EnabledValue = [9940], % stop sign, FALSE, alternatives \x10102\
3586 TransStr = OpName
3587 %ajoin(['Not enabled'],HoverMsg)
3588 ). % TO DO: show whether this is the next step in the trace
3589
3590 % --------------------------
3591
3592 % debugging features to inspect all created SVG objects
3593 tcltk_get_visb_objects(list([Header|AllObjects])) :-
3594 Header = list(['SVG-ID','svg_class','Attribute','Value']),
3595 findall(list([SvgID,SvgClass,Attr,Value]),
3596 (visb_svg_obj_with_parent(SvgID,SvgClass,AttrList,true),
3597 (member(svg_attribute(Attr,Value),AttrList) ;
3598 visb_svg_parent(SvgID,Value), Attr=children)
3599 ), Childs),
3600 findall(list([SvgID,SvgClass,Attr,Value]),
3601 (visb_svg_obj_with_parent(SvgID,SvgClass,AttrList,false),
3602 member(svg_attribute(Attr,Value),AttrList)
3603 ),AllObjects, Childs).
3604
3605 % debugging features to inspect all created SVG objects
3606 tcltk_get_visb_hovers(list([Header|AllObjects])) :-
3607 Header = list(['SVG-ID','ID','Attribute','EnterValue', 'ExitValue']),
3608 findall(list([SvgID,ID,Attr,EnterVal,ExitVal]),
3609 visb_hover(SvgID,ID,Attr,EnterVal,ExitVal,_Pos), AllObjects).
3610
3611 % debugging features to inspect items
3612 tcltk_get_visb_items(Res) :-
3613 current_state_id(ID),
3614 tcltk_get_visb_items(ID,Res).
3615 tcltk_get_visb_items(_StateId,Res) :-
3616 \+ visb_file_is_loaded(_),!,
3617 Res = list(['No VisB JSON file loaded']).
3618 tcltk_get_visb_items(StateId,list([Header|AllItems])) :-
3619 Header = list(['SVG-ID','Attribute','Value']),
3620 get_preference(translation_limit_for_table_commands,Limit),
3621 findall(list([SvgID,SvgAttribute,Val]),
3622 get_change_attribute_for_state(StateId,SvgID,SvgAttribute,Val),
3623 Items),
3624 findall(list([DefID,'VisB Definition',DValS]),
3625 (get_expanded_bstate(StateId,ExpandedBState),
3626 reverse(ExpandedBState,RS),
3627 member(bind(DefID,DVal),RS),
3628 visb_definition(DefID,_,_,_,_,_),
3629 translate_bvalue_with_limit(DVal,Limit,DValS)),
3630 AllItems, Items).
3631
3632 :- use_module(probsrc(translate),[translate_event_with_limit/3]).
3633 tcltk_get_visb_events(Res) :-
3634 current_state_id(ID),
3635 tcltk_get_visb_events(ID,Res).
3636 tcltk_get_visb_events(_StateId,Res) :-
3637 \+ visb_file_is_loaded(_),!,
3638 Res = list(['No VisB JSON file loaded']).
3639 tcltk_get_visb_events(StateId,list([Header|AllItems])) :-
3640 Header = list(['SVG-ID','Event','Target']),
3641 get_preference(translation_limit_for_table_commands,Limit),
3642 findall(list([SvgID,EventStr,NewStateId]),
3643 (perform_visb_click_event(SvgID,[],StateId,_Event,OpTerm,NewStateId,Res),
3644 (Res=[] -> EventStr='disabled' ; translate_event_with_limit(OpTerm,Limit,EventStr))
3645 ),
3646 AllItems).
3647 % --------------------------
3648
3649 % for ProB2-UI
3650
3651 :- use_module(probsrc(translate),[translate_bexpression_with_limit/3]).
3652 get_visb_items(List) :-
3653 findall(visb_item(SvgID,Attr,TS,Desc,Pos),
3654 (visb_item(SvgID,Attr,TypedExpr,_Used,Desc,Pos,_),
3655 translate_bexpression_with_limit(TypedExpr,1000,TS)), List).
3656
3657 get_visb_attributes_for_state(StateId,List) :-
3658 % some external functions like ENABLED are evaluated in current state; it might be useful to set_current_state
3659 (visb_file_is_loaded(_) -> true
3660 ; add_warning(visb_visualiser,'No VisB visualisation loaded, cannot get attributes for state: ',StateId)),
3661 findall(set_attr(SvgID,SvgAttribute,Val),
3662 get_change_attribute_for_state(StateId,SvgID,SvgAttribute,Val),
3663 List).
3664
3665 % for ProB2-UI
3666 get_visb_click_events(List) :-
3667 findall(execute_event(SvgID,Event,Preds),
3668 get_visb_event(SvgID,Event,Preds), List).
3669 get_visb_event(SvgID,Event,Preds) :- visb_event(SvgID,Event,Preds,_,_File,_Pos).
3670 get_visb_event(SvgID,'',[]) :- % add a virtual empty event for SVG Ids with hovers but no events
3671 visb_has_hovers(SvgID),
3672 \+ visb_event(SvgID,_,_,_,_File,_Pos).
3673
3674
3675 :- use_module(probsrc(state_space), [extend_trace_by_transition_ids/1]).
3676 % perform a click on a VisB SVG ID in the animator
3677 tcltk_perform_visb_click_event(SvgID) :- current_state_id(StateId),
3678 (perform_visb_click_event(SvgID,[],StateId,TransitionIDs)
3679 -> formatsilent('Clicking on ~w in state ~w resulted in transition id sequence ~w~n',[SvgID,StateId,TransitionIDs]),
3680 extend_trace_by_transition_ids(TransitionIDs)
3681 ; add_error(visb_visualiser,'Cannot perform VisB click on: ',SvgID)
3682 ).
3683
3684 % computes the effect of clicking on an SvgID in StateId
3685 % it returns either empty list if the visb_event is not feasible or a list of transition ids
3686 % it fails if SvgID has no events associated with it
3687 perform_visb_click_event(SvgID,MetaInfos,StateId,ResTransitionIds) :-
3688 perform_visb_click_event(SvgID,MetaInfos,StateId,_,_,_,ResTransitionIds).
3689 perform_visb_click_event(SvgID,MetaInfos,StateId,OpName,OpTerm,NewStateId,ResTransitionIds) :-
3690 get_expanded_bstate(StateId,ExpandedBState),
3691 set_error_context(checking_context('VisB:','performing click event')),
3692 set_context_state(StateId,perform_visb_click_event),
3693 get_svgid_with_events(SvgID,_),
3694 call_cleanup(perform_aux(SvgID,StateId,ExpandedBState,OpName,OpTerm,NewStateId,ResTransitionIds,MetaInfos),
3695 (clear_context_state,clear_error_context)).
3696
3697 get_svgid_with_events(SvgID,FirstOpName) :- visb_event(SvgID,FirstOpName,_,_,_File,_Pos).
3698
3699
3700 :- use_module(probsrc(tools),[safe_read_term_from_atom/2]).
3701 :- use_module(probsrc(state_space),[transition/4]).
3702 perform_aux(SvgID,StateId,_ExpandedBState,OpName,OpTerm,NewStateId,ResTransitionIds,_MetaInfos) :-
3703 \+ b_or_z_mode,
3704 % just look up transition/4 entries in state space
3705 % TODO: maybe provide this possibility for B models, even if using explicit parameter values is more robust
3706 get_visb_event_operation(SvgID,OpName,Preds,_Pred,Pos),
3707 safe_read_term_from_atom(OpName,OpTerm0),
3708 (xtl_mode -> check_xtl_direct_transition_candidate(OpTerm0,Preds,Pos), OpTerm=OpTerm0 ; true), !,
3709 % for XTL: use exec by pred for arity 0, otherwise try to find transition term in state space
3710 if((transition(StateId,OpTerm,TransID,NewStateId),
3711 match_operation(OpTerm,OpName)), % match is relevant if \+xtl_mode
3712 ResTransitionIds = [TransID],
3713 return_disabled(SvgID,StateId,OpName,OpTerm,NewStateId,ResTransitionIds)
3714 ).
3715 perform_aux(SvgID,StateId,ExpandedBState,OpName,OpTerm,NewStateId,ResTransitionIds,MetaInfos) :-
3716 %state_space:portray_state_space,
3717 if(execute_visb_event_by_predicate(SvgID,StateId,ExpandedBState,OpName,OpTerm,NewStateId,TransIds,MetaInfos),
3718 ResTransitionIds = TransIds,
3719 return_disabled(SvgID,StateId,OpName,OpTerm,NewStateId,ResTransitionIds)).
3720
3721 check_xtl_direct_transition_candidate(OpTerm,Preds,Pos) :-
3722 nonvar(OpTerm), % upper case event names are interpreted as Prolog variables -> use exec by pred (or FIXME)
3723 functor(OpTerm,_,Ar), Ar>0, % use exec by pred for arity 0, otherwise try to find transition term in state space
3724 (Preds \= []
3725 -> add_warning(visb_visualiser,'Ignoring predicates for VisB XTL event with explicit transition term (use predicate to provide parameter values): ',OpTerm,Pos)
3726 ; true).
3727
3728 return_disabled(SvgID,StateId,OpName,OpTerm,NewStateId,ResTransitionIds) :-
3729 OpTerm = disabled, NewStateId = StateId,
3730 get_svgid_with_events(SvgID,OpName),
3731 ResTransitionIds = []. % visb_event not enabled
3732
3733 :- use_module(probsrc(tools_strings),[match_atom/2]).
3734 :- use_module(probsrc(specfile),[get_operation_name/2]).
3735 match_operation(OpTerm,OpTerm) :- !.
3736 match_operation(OpTerm,OpName) :- atom(OpName),
3737 (get_operation_name(OpTerm,OpName)
3738 ; match_atom(OpName,OpTerm) % match an atom string with a compound term
3739 ),!.
3740
3741 execute_visb_event_by_predicate(SvgID,StateId,ExpandedBState,OpName,OpTerm,NewStateId,TransIds,MetaInfos) :-
3742 get_visb_event_operation(SvgID,OpName,_,Pred,Pos),
3743 build_visb_click_meta_object(MetaInfos,BMetaInfos),
3744 bsyntaxtree:replace_id_by_expr(Pred,'VISB_CLICK_META_INFOS',BMetaInfos,NPred),
3745 exec_aux(SvgID,StateId,ExpandedBState,OpName,NPred,Pos,OpTerm,NewStateId,TransIds).
3746
3747 build_visb_click_meta_object(MetaInfos,BMetaInfos) :-
3748 (member(alt_key,MetaInfos) -> AltKey = pred_true ; AltKey = pred_false),
3749 (member(ctrl_key,MetaInfos) -> CtrlKey = pred_true ; CtrlKey = pred_false),
3750 (member(meta_key,MetaInfos) -> MetaKey = pred_true ; MetaKey = pred_false),
3751 (member(pageX(PageX),MetaInfos) -> true ; PageX = 0), % fallback
3752 (member(pageY(PageY),MetaInfos) -> true ; PageY = 0), % fallback
3753 (member(shift_key,MetaInfos) -> ShiftKey = pred_true ; ShiftKey = pred_false),
3754 findall(','(string(Var),string(VarValue)), member(js_var(Var,VarValue), MetaInfos), JSVars),
3755
3756 visb_click_meta_b_type(BType),
3757 BMetaInfos = b(value(rec([
3758 field(altKey,AltKey),
3759 field(ctrlKey,CtrlKey),
3760 field(jsVars,JSVars),
3761 field(metaKey,MetaKey),
3762 field(pageX,int(PageX)),
3763 field(pageY,int(PageY)),
3764 field(shiftKey,ShiftKey)
3765 ])),BType,[visb_generated]).
3766
3767 visb_click_meta_b_type(record([
3768 field(altKey,boolean),
3769 field(ctrlKey,boolean),
3770 field(jsVars,set(couple(string,string))),
3771 field(metaKey,boolean),
3772 field(pageX,integer),
3773 field(pageY,integer),
3774 field(shiftKey,boolean)
3775 ])).
3776
3777 :- use_module(probsrc(tcltk_interface),[compute_all_transitions_if_necessary/2]).
3778 :- use_module(library(random),[random_member/2]).
3779 :- use_module(extrasrc(mcts_game_play), [mcts_auto_play/4, mcts_auto_play_available/0]).
3780 :- use_module(probsrc(tools_timeout), [time_out_with_factor_call/3]).
3781 exec_aux(SvgID,StateId,ExpandedBState,OpName,Pred,Pos,OpTerm,NewStateId,[TransId]) :-
3782 (b_or_z_mode -> b_is_operation_name(OpName) ; true), !, % note: ignores special definitions below if not B mode
3783 time_out_with_factor_call(
3784 exec_op_by_pred_aux(StateId,ExpandedBState,OpName,Pred,OpTerm,NewState,Pos),
3785 5, % min_max_time_out(10,100,15000)
3786 (ajoin(['TIME-OUT for VisB click on SVG ID ', SvgID,' while executing operation by predicate: '],Msg),
3787 add_warning(visb_visualiser,Msg,OpName,Pos),fail)),
3788 patch_state(NewState,StateId,PatchedNewState),
3789 tcltk_interface:add_trans_id(StateId,OpTerm,PatchedNewState,NewStateId,TransId).
3790 %translate:print_bstate(PatchedNewState),nl.
3791 exec_aux(SvgID,StateId,_ExpandedBState,'MCTS_AUTO_PLAY',_Pred,Pos,OpTerm,NewStateId,[TransId]) :- !,
3792 mcts_auto_play_available,
3793 % TODO: allow to set SimRuns, TimeOut in Pred
3794 add_debug_message(visb_visualiser,'Performing MCTS_AUTO_PLAY for click on: ',SvgID,Pos),
3795 mcts_auto_play(StateId,OpTerm,TransId,NewStateId).
3796 exec_aux(_SvgID,StateId,_ExpandedBState,'RANDOM_ANIMATE',_Pred,_Pos,OpTerm,NewStateId,[TransId]) :- !,
3797 compute_all_transitions_if_necessary(StateId,false),
3798 write(ra(_Pred)),nl,
3799 findall(rtr(OpTerm,TransId,NewStateId),transition(StateId,OpTerm,TransId,NewStateId),List),
3800 random_member(rtr(OpTerm,TransId,NewStateId),List).
3801 % see tcltk_interface:tcltk_random_perform2 and allow Kind: fully_random, no_self_loops, heuristics, ...
3802 % split with ; ?
3803 exec_aux(SvgID,StateId,ExpandedBState,'RANDOM_ANIMATE_UNTIL_LTL',LTLExpr,Pos,OpTerm,NewStateId,TransIds) :- !,
3804 OpTerm = 'RANDOM_ANIMATE_UNTIL_LTL',
3805 (get_texpr_type(LTLExpr,string),
3806 evaluate_visb_formula(LTLExpr,'RANDOM_ANIMATE_UNTIL_LTL',SvgID,ExpandedBState,Value,Pos),
3807 Value = string(LTLFormula)
3808 -> tcltk_interface:tcltk_animate_until(LTLFormula,StateId,1000,ltl_state_property,_Steps,_Res,NewStateId,TransIds)
3809 ; add_error(visb_visualiser,'Argument to RANDOM_ANIMATE_UNTIL_LTL must provide LTL formula as string:',StateId)
3810 ).
3811
3812 :- use_module(probsrc(b_state_model_check),[execute_operation_by_predicate_in_state_with_pos/6,
3813 xtl_execute_operation_by_predicate_in_state/7]).
3814 exec_op_by_pred_aux(StateId,ExpandedBState,OpName,Pred,OpTerm,NewState,Pos) :- xtl_mode,!,
3815 visited_expression(StateId,RawState),
3816 xtl_execute_operation_by_predicate_in_state(ExpandedBState,RawState,OpName,Pred,OpTerm,NewState,Pos).
3817 exec_op_by_pred_aux(_StateId,ExpandedBState,OpName,Pred,OpTerm,NewState,Pos) :-
3818 execute_operation_by_predicate_in_state_with_pos(ExpandedBState,OpName,Pred,OpTerm,NewState,Pos).
3819
3820 :- use_module(probsrc(bmachine), [b_is_variable/1,b_machine_has_constants/0]).
3821
3822 is_var_binding(bind(Var,_)) :- b_or_z_mode, b_is_variable(Var).
3823
3824
3825 % remove constants and VisB Definition entries from state:
3826 patch_state(NewState,_StateId,PatchedState) :-
3827 \+ b_or_z_mode, !, PatchedState=NewState. % XTL state is raw state
3828 patch_state(NewState,StateId,PatchedState) :-
3829 get_constants_id_for_state_id(StateId,ConstId),!,
3830 PatchedState = const_and_vars(ConstId,VarsState),
3831 include(is_var_binding,NewState,VarsState).
3832 patch_state(NewState,StateId,VarsState) :-
3833 (b_machine_has_constants
3834 -> add_error(visb_visualiser,'Could not extract constants id for state:',StateId),
3835 VarsState=NewState
3836 ; include(is_var_binding,NewState,VarsState)).
3837
3838 % the next predicate gets all operations/events associated with SvgID in the order in which they were found
3839 % note that there is only one visb_event (the last one); all others are auxiliary
3840 get_visb_event_operation(SvgID,OpName,Preds,TypedPred,Pos) :- % check if there are more events registered:
3841 auxiliary_visb_event(SvgID,OpName,Preds,TypedPred,Pos).
3842 get_visb_event_operation(SvgID,OpName,Preds,TypedPred,Pos) :-
3843 visb_event(SvgID,OpName,Preds,TypedPred,_File,Pos).
3844
3845 % ---------------
3846
3847 get_visb_hovers(List) :-
3848 findall(hover(SvgID,ID,Attr,EnterVal,ExitVal),
3849 visb_hover(SvgID,ID,Attr,EnterVal,ExitVal,_), List).
3850
3851 get_visb_svg_objects(List) :-
3852 % TODO: remove objects inlined in get_visb_default_svg_file_contents
3853 topological_sort_svg_objects(SvgIDs),
3854 findall(visb_svg_object(SvgID,SvgClass,AttrList),
3855 (member(SvgID,SvgIDs),
3856 visb_svg_obj_with_parent(SvgID,SvgClass,AttrList,_)), List).
3857
3858 visb_svg_obj_with_parent(SvgID,SvgClass,AttrList,IsChild) :-
3859 visb_svg_object(SvgID,SvgClass,List,_Desc,_Pos),
3860 (visb_svg_child(SvgID,ParentId)
3861 -> IsChild=true, AttrList = [svg_attribute(parentId,ParentId)|List] % add parentId attribute for ProB2-UI
3862 ; IsChild=false, AttrList = List).
3863
3864
3865 :- use_module(probsrc(tools),[top_sort/3]).
3866 :- use_module(library(ugraphs),[vertices_edges_to_ugraph/3]).
3867 topological_sort_svg_objects(SortedSVGObjects) :-
3868 findall(SvgID,visb_svg_object(SvgID,_,_,_,_),Vertices),
3869 findall(V-W,visb_svg_parent(V,W),Edges),
3870 vertices_edges_to_ugraph(Vertices,Edges,Graph),
3871 (top_sort(Graph,SortedSVGObjects,UnsortedNr)
3872 -> (UnsortedNr = 0 -> true
3873 ; add_warning(visb_visualiser,'Cycle in SVG_OBJECTS parent/child graph, unsorted objects: ',UnsortedNr)
3874 )
3875 ; SortedSVGObjects=Vertices,
3876 add_error(visb_visualiser,'Topological sorting of SVG_OBJECTS failed: ',Vertices)
3877 ).
3878
3879 % ------------------
3880
3881 :- use_module(probsrc(bmachine),[b_absolute_file_name_relative_to_main_machine/2]).
3882 extended_static_check_default_visb_file :-
3883 (get_default_visb_file(VisBFile,Pos)
3884 % TODO: we could check if we have an visb_history(JSONFile,_,_) option
3885 -> extended_static_check_visb_file(VisBFile,Pos)
3886 ; true).
3887
3888 extended_static_check_visb_file('',_InclusionPos) :- !,
3889 load_visb_file('').
3890 extended_static_check_visb_file(VisBFile,InclusionPos) :-
3891 b_absolute_file_name_relative_to_main_machine(VisBFile,AFile),
3892 (file_exists(AFile)
3893 -> load_visb_file(AFile)
3894 ; add_warning(lint,'VISB_JSON_FILE does not exist: ',AFile,InclusionPos)
3895 ).
3896
3897 % ---------------------------
3898
3899 % portray all VisB items in DEFINITION B syntax
3900 get_visb_ids(SIds) :-
3901 findall(Id,visb_id(Id),Ids),
3902 sort(Ids,SIds).
3903
3904 visb_id(ID) :- visb_svg_object(ID,_,_,_,_). % see svg_id_exists
3905 visb_id(ID) :- visb_item(ID,_,_,_,_,_,_), \+ visb_svg_object(ID,_,_,_,_).
3906 visb_id(ID) :- visb_event(ID,_,_,_,_,_), \+ visb_svg_object(ID,_,_,_,_).
3907 visb_id(ID) :- visb_hover(ID,_,_,_,_,_), \+ visb_svg_object(ID,_,_,_,_).
3908
3909 :- public portray_visb/0.
3910 portray_visb:-
3911 get_visb_ids(SIds), nth1(Nr,SIds,ID),
3912 %visb_svg_object(ID,SVG_Class,NewRestAttrs,Desc,Pos1),
3913 findall(field(Attr,b(value(StaticVal),any,[])),
3914 (visb_svg_object(ID,SVG_Class,StaticAttrs,Desc,_Pos1),
3915 ( Attr=svg_class,StaticVal=string(SVG_Class)
3916 ; Attr=comment,StaticVal=string(Desc)
3917 ; member(svg_attribute(Attr,StaticVal),StaticAttrs))
3918 ),
3919 StaticValues),
3920 findall(field(Attr,TypedExpr),
3921 visb_item(ID,Attr,TypedExpr,_UsedIds,_Desc,_PosStartOfItem,_Meta), % meta can contain override
3922 Updates,StaticValues),
3923 % TODO: incorporate events and hovers
3924 UpdateRec = b(rec(Fields),any,[]),
3925 gen_string(ID,IDS),
3926 Fields = [field(id,IDS) | Updates],
3927 (StaticValues=[] -> format('~nVISB_SVG_UPDATES~w == ',[Nr]) ; format('~nVISB_SVG_OBJECTS~w == ',[Nr])),
3928 translate:print_bexpr(UpdateRec), write(';'), nl,
3929 fail.
3930 portray_visb.
3931 gen_string(ID,b(string(ID),string,[])).
3932 % use_module(visbsrc(visb_visualiser)), visb_visualiser:portray_visb.