1 % (c) 2018-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5
6 :- module(tools_matching,
7 [fuzzy_match_codes_lower_case/2,
8 fuzzy_match_codes/2,
9 codes_to_lower_case/2, % to lower case, also performs Unicode simplifications
10 get_current_keywords/1, get_current_expr_keywords/1,
11 is_b_keyword/2, is_rules_dsl_keyword/2,
12 get_all_svg_classes/1, is_svg_shape_class/1,
13 get_all_svg_attributes/1, is_svg_number_attribute/2, is_svg_color_attribute/1,
14 is_svg_attribute/1, is_virtual_svg_attribute/1,
15 is_svg_color_name/1,
16 is_html_tag/1, is_html_attribute/1,
17 get_all_dot_attributes/1, is_dot_attribute/1,
18 dot2svg_attribute/2, dotshape2svg_class/2,
19 get_possible_preferences/1, get_possible_preferences_matches_msg/2,
20 get_possible_top_level_event_matches_msg/2,
21 get_possible_operation_matches_msg/2,
22 get_possible_fuzzy_matches_msg/3,
23 get_possible_completions_msg/3,
24 get_possible_fuzzy_matches_and_completions_msg/3 % both in one
25 ]).
26
27 :- use_module(error_manager).
28 :- use_module(self_check).
29 :- use_module(library(lists)).
30
31 :- use_module(module_information).
32
33 :- module_info(group,infrastructure).
34 :- module_info(description,'A few utilities for fuzzy matching and completion.').
35
36 :- set_prolog_flag(double_quotes, codes).
37
38
39 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("a","A")).
40 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("aBcD","ABCd")).
41 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("aBcD","ABxCd")).
42 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("aBxcD","ABCd")).
43 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("aBcD","ABCdx")).
44 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("aBcDx","ABCd")).
45 :- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("a_Bc_D","AB__Cd")).
46 %:- assert_must_succeed(tools_matching:fuzzy_match_codes_lower_case("äÄ","aA")).
47 :- assert_must_fail(tools_matching:fuzzy_match_codes_lower_case("abc","cba")).
48
49
50 fuzzy_match_codes_lower_case(Codes1,Codes2) :-
51 codes_to_lower_case(Codes1,LCodes1),
52 codes_to_lower_case(Codes2,LCodes2),
53 ? fuzzy_match_codes(LCodes1,LCodes2).
54
55 :- assert_must_succeed(tools_matching:fuzzy_match_codes("aBcD","aBcD")).
56 :- assert_must_succeed(tools_matching:fuzzy_match_codes("aBxcD","aBcD")).
57 :- assert_must_succeed(tools_matching:fuzzy_match_codes("aBcD","aBcxD")).
58 :- assert_must_succeed(tools_matching:fuzzy_match_codes("aBcD","aBcDx")).
59 :- assert_must_succeed(tools_matching:fuzzy_match_codes("xaBcD","aBcD")).
60 :- assert_must_succeed(tools_matching:fuzzy_match_codes("aBcD","xaBcD")).
61 :- assert_must_succeed(tools_matching:fuzzy_match_codes("version","verison")).
62 :- assert_must_fail(tools_matching:fuzzy_match_codes("abc","ABC")).
63
64 fuzzy_match_codes([],[]).
65 ?fuzzy_match_codes([H|T1],[H|T2]) :- !,fuzzy_match_codes(T1,T2).
66 fuzzy_match_codes([_|T],[_|T]) :- !. % one character rewritten
67 fuzzy_match_codes([H1|T1],L2) :- possible_skip_char(H1),!, % underscore _
68 ? fuzzy_match_codes(T1,L2).
69 fuzzy_match_codes(L1,[H2|T2]) :- possible_skip_char(H2),!,
70 ? fuzzy_match_codes(L1,T2).
71 fuzzy_match_codes([_|T],T) :- !. % one character too much
72 fuzzy_match_codes(T,[_|T]) :- !. % one character too few
73 fuzzy_match_codes([H1,H2|T],[H2,H1|T]) :- !. % swapping of two characters
74
75
76 %:- assert_must_succeed(tools_matching:codes_to_lower_case("äÄöAa","aaoaa")).
77
78 codes_to_lower_case([],[]).
79 codes_to_lower_case([C|T],[LC|LT]) :- code_to_lower_case(C,LC), codes_to_lower_case(T,LT).
80
81 % TO DO: normalise more UNICODE symbols, ...
82
83 code_to_lower_case(Char,LC_Char) :- Char >= 65, Char =< 90,!, LC_Char is Char+32.
84 code_to_lower_case(Char,LC_Char) :- Char >= 8320, Char =< 8329,!, LC_Char is Char-8272. % Unicode Subscripts
85 code_to_lower_case(8242,R) :- !, R=8242. % Unicode Prime
86 code_to_lower_case(8216,R) :- !, R=8242.
87 code_to_lower_case(8217,R) :- !, R=8242.
88 code_to_lower_case(Char,R) :- Char >= 192, Char =< 197,!, R=97. % upper-case a
89 code_to_lower_case(Char,R) :- Char >= 224, Char =< 229,!, R=97. % lower-case a
90 code_to_lower_case(Char,R) :- Char >= 200, Char =< 203,!, R=101. % upper-case e
91 code_to_lower_case(Char,R) :- Char >= 232, Char =< 235,!, R=101. % lower-case e
92 code_to_lower_case(Char,R) :- Char >= 204, Char =< 207,!, R=105. % upper-case i
93 code_to_lower_case(Char,R) :- Char >= 236, Char =< 239,!, R=105. % lower-case i
94 code_to_lower_case(Char,R) :- Char >= 210, Char =< 214,!, R=111. % upper-case o
95 code_to_lower_case(Char,R) :- Char >= 242, Char =< 246,!, R=111. % lower-case o
96 code_to_lower_case(Char,R) :- Char >= 217, Char =< 220,!, R=117. % upper-case u
97 code_to_lower_case(Char,R) :- Char >= 249, Char =< 252,!, R=117. % lower-case u
98 code_to_lower_case(253,R) :- !, R=121. % ý -> y
99 code_to_lower_case(209,R) :- !, R=110. % Ñ -> n
100 code_to_lower_case(241,R) :- !, R=110. % ñ -> n
101 code_to_lower_case(231,R) :- !, R=99. % ç -> c
102 code_to_lower_case(223,R) :- !, R=115. % ß -> s
103 code_to_lower_case(C,C).
104
105 % use_module(library(between)), between(150,255,R), atom_codes(A,[R]), format("~w : ~w~n",[R,A]),fail.
106
107 possible_skip_char(95). % _
108
109 :- use_module(specfile,[b_or_z_mode/0, csp_mode/0, xtl_mode/0, animation_minor_mode/1, classical_b_mode/0]).
110
111 get_current_expr_keywords(List) :-
112 get_current_keywords([expr,external_funs,pragma,predicate],List).
113 get_current_keywords(List) :-
114 get_current_keywords([expr,external_funs,pragma,predicate,prob_definitions,section,subst],List).
115
116 get_current_keywords(Types,List) :- b_or_z_mode,!,
117 (animation_minor_mode(Minor)
118 -> (classical_b_mode
119 % e.g., for rules_dsl allow both B and rules_dsl keywords at the moment, TODO: remove sections
120 % TODO: we should also ensure this is active for VisB expressions or when the REPL is classical B mode
121 -> get_keywords(Minor,Types,List1),
122 get_keywords(b,Types,List2),
123 append(List1,List2,List)
124 ; get_keywords(Minor,Types,List))
125 ; get_keywords(b,Types,List)).
126 get_current_keywords(_,List) :- csp_mode,!,
127 findall(Def,csp_keyword(Def),List).
128 get_current_keywords(_,List) :- xtl_mode,!,
129 findall(Def,xtl_keyword(Def),List).
130 get_current_keywords(_,[]).
131
132 % -----------------
133
134 csp_keyword(and).
135 csp_keyword(card).
136 csp_keyword(channel).
137 csp_keyword(datatype).
138 csp_keyword(diff).
139 csp_keyword(elem).
140 csp_keyword(empty).
141 csp_keyword(false).
142 csp_keyword(head).
143 csp_keyword(inter).
144 csp_keyword(length).
145 csp_keyword(let).
146 csp_keyword(member).
147 csp_keyword(mod).
148 csp_keyword(nametype).
149 csp_keyword(not).
150 csp_keyword(null).
151 csp_keyword(or).
152 csp_keyword(set).
153 csp_keyword(subtype).
154 csp_keyword(tail).
155 csp_keyword(true).
156 csp_keyword(union).
157 csp_keyword(within).
158 csp_keyword('CHAOS').
159 csp_keyword('Inter').
160 csp_keyword('Seq').
161 csp_keyword('Set').
162 csp_keyword('SKIP').
163 csp_keyword('STOP').
164 csp_keyword('Union').
165
166
167 xtl_keyword(prop).
168 xtl_keyword(start).
169 xtl_keyword(symb_trans).
170 xtl_keyword(symb_trans_enabled).
171 xtl_keyword(trans).
172 xtl_keyword(trans_prop).
173 xtl_keyword(animation_image).
174 xtl_keyword(animation_image_click_transition).
175 xtl_keyword(animation_image_right_click_transition).
176 xtl_keyword(animation_function_result).
177 xtl_keyword(heuristic_function_active).
178 xtl_keyword(heuristic_function_result).
179 xtl_keyword(prob_game_info).
180 xtl_keyword(prob_pragma_string).
181 xtl_keyword(nr_state_properties).
182
183 % -----------------
184
185 get_keywords(Mode,Types,List) :-
186 (Mode=b,select(prob_definitions,Types,Types1)
187 -> findall(Def,prob_special_def(Def),Ids1)
188 ; Ids1=[], Types1=Types
189 ),
190 ? (Mode=b,select(external_funs,Types1,Types2)
191 -> findall(Def,prob_external_fun(Def),Ids2,Ids1)
192 ; Ids2=Ids1, Types2=Types1
193 ),
194 findall(ID,(keyword(ID,Type,Modes), member(Mode,Modes), member(Type,Types2)),Ids,Ids2),
195 sort(Ids,List).
196
197 :- use_module(external_function_declarations,[external_function_library/2]).
198 ?prob_external_fun(Fun) :- external_function_library(Fun,File),
199 member(File,['LibraryStrings.def']). % ideally we want to only show the included libraries
200
201 prob_special_def(Def) :- special_definitions(Def,_).
202 prob_special_def(Def) :- set_pref_keyword(Def,_).
203 prob_special_def(Def) :- operation_pref_keyword(Def).
204
205 special_definitions('ASSERT_CTL',model_check).
206 special_definitions('ASSERT_LTL',model_check).
207 special_definitions('GOAL',model_check).
208 special_definitions('HEURISTIC_FUNCTION',model_check).
209 special_definitions('SCOPE',model_check).
210 special_definitions('CUSTOM_GRAPH',dot).
211 special_definitions('CUSTOM_GRAPH_EDGES',dot).
212 special_definitions('CUSTOM_GRAPH_NODES',dot).
213 special_definitions('VISB_DEFINITIONS_FILE',visb).
214 special_definitions('VISB_JSON_FILE',visb).
215 special_definitions('VISB_SVG_BOX',visb).
216 special_definitions('VISB_SVG_CONTENTS',visb).
217 special_definitions('VISB_SVG_EVENTS',visb).
218 special_definitions('VISB_SVG_FILE',visb).
219 special_definitions('VISB_SVG_HOVERS',visb).
220 special_definitions('VISB_SVG_OBJECTS',visb).
221 special_definitions('VISB_SVG_UPDATES',visb).
222 % this is a local identifier available inside event predicates: VISB_CLICK_META_INFOS
223 special_definitions('ANIMATION_CLICK',tkanim).
224 special_definitions('ANIMATION_EXPRESSION',tkanim).
225 special_definitions('ANIMATION_FUNCTION',tkanim).
226 special_definitions('ANIMATION_FUNCTION_DEFAULT',tkanim).
227 special_definitions('ANIMATION_IMG',tkanim).
228 special_definitions('ANIMATION_RIGHT_CLICK',tkanim).
229 special_definitions('ANIMATION_STR',tkanim).
230 special_definitions('ANIMATION_STR_JUSTIFY_LEFT',tkanim).
231 special_definitions('ANIMATION_STR_JUSTIFY_RIGHT',tkanim).
232 special_definitions('GAME_MCTS_RUNS',mcts).
233 special_definitions('GAME_MCTS_TIMEOUT',mcts).
234 special_definitions('GAME_MCTS_CACHE_LAST_TREE',mcts).
235 special_definitions('GAME_OVER',mcts).
236 special_definitions('GAME_PLAYER',mcts).
237 special_definitions('GAME_VALUE',mcts).
238 special_definitions('PROB_REQUIRED_VERSION',general).
239 % TODO: scope_, FORCE_SYMMETRY_, for sets
240
241 :- use_module(bmachine,[b_top_level_operation/1]).
242 operation_pref_keyword(OpPrefAtom) :-
243 b_top_level_operation(Top),
244 op_prefix(Prefix),
245 atom_concat(Prefix,Top,OpPrefAtom).
246 op_prefix('MAX_OPERATIONS_').
247 op_prefix('OPERATION_REUSE_OFF_').
248 op_prefix('SEQUENCE_CHART_').
249 op_prefix('DESCRIPTION_FOR_').
250
251 set_pref_keyword(SetPrefAtom,Pref) :-
252 get_possible_preferences(Prefs),
253 member(Pref,Prefs),
254 atom_concat('SET_PREF_',Pref,SetPrefAtom).
255
256 is_b_keyword(ID,Type) :- keyword(ID,Type,L), member(b,L).
257 is_rules_dsl_keyword(ID,Type) :- keyword(ID,Type,L), member(rules_dsl,L).
258
259 % list of language specific and context specific keywords
260 keyword(not,predicate,[b,eventb]).
261 keyword(or,predicate,[b,eventb]).
262 keyword('true',expr,[eventb]). % truth in Rodin parser
263 keyword('false',expr,[eventb]). % falsity in Rodin parser
264 keyword('TRUE',expr,[b,eventb,tla]).
265 keyword('FALSE',expr,[b,eventb,tla]).
266 keyword('BOOL',expr,[b,eventb]).
267 keyword('bool',expr,[b,eventb]).
268 keyword('POW',expr,[b,eventb]).
269 keyword('POW1',expr,[b,eventb]).
270 keyword('FIN',expr,[b]). % not available in Event-B
271 keyword('FIN1',expr,[b]). % ditto
272 keyword('union',expr,[b,eventb]).
273 keyword('inter',expr,[b,eventb]).
274 keyword('UNION',expr,[b,eventb]).
275 keyword('INTER',expr,[b,eventb]).
276 keyword('INTEGER',expr,[b]).
277 keyword('NATURAL',expr,[b]).
278 keyword('NATURAL1',expr,[b]).
279 keyword('INT',expr,[b,eventb]).
280 keyword('NAT',expr,[b,eventb]).
281 keyword('NAT1',expr,[b,eventb]).
282 keyword('MININT',expr,[b]).
283 keyword('MAXINT',expr,[b]).
284 keyword('min',expr,[b,eventb]).
285 keyword('max',expr,[b,eventb]).
286 keyword('SIGMA',expr,[b]).
287 keyword('PI',expr,[b]).
288 keyword('STRING',expr,[b,tla]).
289 keyword('card',expr,[b,eventb]).
290 keyword('finite',expr,[eventb]).
291 keyword('@finite',expr,[b]).
292 keyword('dom',expr,[b,eventb]).
293 keyword('ran',expr,[b,eventb]).
294 keyword('id',expr,[b,eventb]).
295 keyword('@partition',expr,[b]).
296 keyword('partition',expr,[eventb]).
297 keyword('prj1',expr,[b,eventb]).
298 keyword('prj2',expr,[b,eventb]).
299 keyword('@prj1',expr,[b]).
300 keyword('@prj2',expr,[b]).
301 keyword('pred',expr,[b,eventb]).
302 keyword('succ',expr,[b,eventb]).
303 keyword('closure',expr,[b]).
304 keyword('closure1',expr,[b]).
305 keyword('iterate',expr,[b]).
306 keyword('fnc',expr,[b]). % also Event-B ?
307 keyword('rel',expr,[b]).
308
309 keyword('seq',expr,[b]).
310 keyword('seq1',expr,[b]).
311 keyword('iseq',expr,[b]).
312 keyword('iseq1',expr,[b]).
313 keyword('perm',expr,[b]).
314 keyword('size',expr,[b]).
315 keyword('rev',expr,[b]).
316 keyword('first',expr,[b]).
317 keyword('last',expr,[b]).
318 keyword('front',expr,[b]).
319 keyword('tail',expr,[b]).
320 keyword('conc',expr,[b]).
321 keyword('struct',expr,[b]).
322 keyword('rec',expr,[b]).
323 keyword('STRING',expr,[b]).
324
325 % TREE keywords
326 keyword('arity',expr,[b]).
327 keyword('bin',expr,[b]).
328 keyword('btree',expr,[b]).
329 keyword('const',expr,[b]).
330 keyword('father',expr,[b]).
331 keyword('infix',expr,[b]).
332 keyword('left',expr,[b]).
333 keyword('mirror',expr,[b]).
334 keyword('prefix',expr,[b]).
335 keyword('postfix',expr,[b]).
336 keyword('rank',expr,[b]).
337 keyword('right',expr,[b]).
338 keyword('sizet',expr,[b]).
339 keyword('son',expr,[b]).
340 keyword('sons',expr,[b]).
341 keyword('subtree',expr,[b]).
342 keyword('top',expr,[b]).
343 keyword('tree',expr,[b]).
344
345
346 % REAL keywords
347 keyword('floor',expr,[b]).
348 keyword('ceiling',expr,[b]).
349 keyword('real',expr,[b]).
350 keyword('REAL',expr,[b]).
351 keyword('FLOAT',expr,[b]).
352
353 % ---
354
355 keyword('btrue',predicate,[b]).
356 keyword('bfalse',predicate,[b]).
357
358 keyword('skip',subst,[b]).
359 keyword('ANY',subst,[b]).
360 keyword('ASSERT',subst,[b]).
361 keyword('BEGIN',subst,[b]).
362 keyword('CASE',subst,[b,tla]).
363 keyword('CHOICE',subst,[b]).
364 keyword('DO',subst,[b]).
365 keyword('EITHER',subst,[b]).
366 keyword('OR',subst,[b]).
367 keyword('OF',subst,[b]).
368 keyword('PRE',subst,[b]).
369 keyword('SELECT',subst,[b]).
370 keyword('WHERE',subst,[b]).
371 keyword('WHILE',subst,[b]).
372 keyword('WITH',subst,[b,tla]).
373
374 % --
375
376 keyword('ABSTRACT_CONSTANTS',section,[b]).
377 keyword('ABSTRACT_VARIABLES',section,[b]).
378 keyword('ASSERTIONS',section,[b]).
379 keyword('CONCRETE_CONSTANTS',section,[b]).
380 keyword('CONCRETE_VARIABLES',section,[b]).
381 keyword('CONSTANTS',section,[b,tla]).
382 keyword('CONSTRAINTS',section,[b]).
383 keyword('DEFINITIONS',section,[b]).
384 keyword('EVENT',section,[b]).
385 keyword('EXTENDS',section,[b,tla]).
386 keyword('FREETYPES',section,[b]).
387 keyword('IMPLEMENTATION',section,[b]).
388 keyword('IMPORTS',section,[b]).
389 keyword('INCLUDES',section,[b]).
390 keyword('INITIALISATION',section,[b]).
391 keyword('INITIALIZATION',section,[b]).
392 keyword('INVARIANT',section,[b]).
393 keyword('LOCAL_OPERATIONS',section,[b]).
394 keyword('MACHINE',section,[b]).
395 keyword('MODEL',section,[b]).
396 keyword('OPERATIONS',section,[b]).
397 keyword('PROMOTES',section,[b]).
398 keyword('PROPERTIES',section,[b]).
399 keyword('REFINEMENT',section,[b]).
400 keyword('REFINES',section,[b]).
401 keyword('SEES',section,[b]).
402 keyword('SETS',section,[b]).
403 keyword('SYSTEM',section,[b]).
404 keyword('USES',section,[b]).
405 keyword('VALUES',section,[b]).
406 keyword('VARIABLES',section,[b,tla]).
407 keyword('VARIANT',section,[b]).
408
409 % rules-dsl sections
410 keyword('ACTIVATION',section,[rules_dsl]).
411 keyword('BODY',section,[rules_dsl]).
412 keyword('CLASSIFICATION',section,[rules_dsl]).
413 keyword('COMPUTATION',section,[rules_dsl]).
414 keyword('COUNTEREXAMPLE',section,[rules_dsl]).
415 keyword('DEPENDS_ON_COMPUTATION',section,[rules_dsl]).
416 keyword('DEPENDS_ON_RULE',section,[rules_dsl]).
417 keyword('DEFINE',section,[rules_dsl]).
418 keyword('DUMMY_VALUE',section,[rules_dsl]).
419 keyword('ERROR_TYPE',section,[rules_dsl]).
420 keyword('ERROR_TYPES',section,[rules_dsl]).
421 keyword('FOR',section,[rules_dsl]).
422 keyword('FUNCTION',section,[rules_dsl]).
423 keyword('ON_SUCCESS',section,[rules_dsl]).
424 keyword('POSTCONDITION',section,[rules_dsl]).
425 keyword('PRECONDITION',section,[rules_dsl]).
426 keyword('REFERENCES',section,[rules_dsl]).
427 keyword('REPLACES',section,[rules_dsl]).
428 keyword('RULE_FAIL',section,[rules_dsl]).
429 keyword('RULE_FORALL',section,[rules_dsl]).
430 keyword('RULE',section,[rules_dsl]).
431 keyword('RULEID',section,[rules_dsl]).
432 keyword('RULES_MACHINE',section,[rules_dsl]).
433 keyword('TAGS',section,[rules_dsl]).
434 keyword('TYPE',section,[rules_dsl]).
435 keyword('UNCHECKED',section,[rules_dsl]).
436 keyword('VALUE',section,[rules_dsl]).
437
438
439 % TODO: check if these below are available within expressions:
440 keyword('DISABLED_RULE',section,[rules_dsl]).
441 keyword('FAILED_RULE',section,[rules_dsl]).
442 keyword('FAILED_RULE_ERROR_TYPE',section,[rules_dsl]).
443 keyword('FAILED_RULE_ALL_ERROR_TYPES',section,[rules_dsl]).
444 keyword('GET_RULE_COUNTEREXAMPLES',section,[rules_dsl]).
445 keyword('NOT_CHECKED_RULE',section,[rules_dsl]).
446 keyword('STRING_FORMAT',section,[rules_dsl]).
447 keyword('SUCCEEDED_RULE',section,[rules_dsl]).
448 keyword('SUCCEEDED_RULE_ERROR_TYPE',section,[rules_dsl]).
449
450
451 keyword('@desc',pragma,[b]).
452 keyword('@file',pragma,[b]).
453 keyword('@generated',pragma,[b]).
454 keyword('@import-package',pragma,[b]).
455 keyword('@label',pragma,[b]).
456 keyword('@package',pragma,[b]).
457 keyword('@symbolic',pragma,[b]).
458
459 % TLA sections
460 keyword('ASSUME',section,[tla]).
461 keyword('ASSUMPTION',section,[tla]).
462 keyword('AXIOM',section,[tla]).
463 keyword('CONSTANT',section,[tla]).
464 keyword('LOCAL',section,[tla]).
465 keyword('INSTANCE',section,[tla]).
466 keyword('MODULE',section,[tla]).
467 keyword('THEOREM',section,[tla]).
468
469 keyword('IF',_,[b,tla]).
470 keyword('THEN',_,[b,tla]).
471 keyword('ELSE',_,[b,tla]).
472 keyword('ELSIF',_,[b]).
473 keyword('LET',_,[b,tla]).
474 keyword('BE',_,[b]).
475 keyword('IN',_,[b,tla]).
476 keyword('END',_,[b,tla]).
477
478 % TLA expression keywords
479 keyword('BOOLEAN',expr,[tla]).
480 keyword('Cardinality',expr,[tla]).
481 keyword('CHOOSE',expr,[tla]).
482 keyword('DOMAIN',expr,[tla]).
483 keyword('ENABLED',expr,[tla]).
484 keyword('EXCEPT',expr,[tla]).
485 keyword('SUBSET',expr,[tla]).
486 keyword('UNCHANGED',expr,[tla]).
487 keyword('UNION',expr,[tla]).
488
489 % Alloy sections
490 keyword('abstract',section,[alloy]).
491 keyword('assert',section,[alloy]).
492 keyword('check',section,[alloy]).
493 keyword('extends',section,[alloy]).
494 keyword('fact',section,[alloy]).
495 keyword('fun',section,[alloy]).
496 keyword('module',section,[alloy]).
497 keyword('open',section,[alloy]).
498 keyword('pred',section,[alloy]).
499 keyword('run',section,[alloy]).
500 keyword('sig',section,[alloy]).
501
502
503 keyword('div',expr,[alloy]).
504 keyword('minus',expr,[alloy]).
505 keyword('else',expr,[alloy]).
506 keyword('iden',expr,[alloy]).
507 keyword('let',expr,[alloy]).
508 keyword('mul',expr,[alloy]).
509 keyword('plus',expr,[alloy]).
510 keyword('rem',expr,[alloy]).
511 keyword('sum',expr,[alloy]).
512 keyword('univ',expr,[alloy]).
513
514 keyword('all',predicate,[alloy]).
515 keyword('disjoint',predicate,[alloy]).
516 keyword('iff',predicate,[alloy]).
517 keyword('implies',predicate,[alloy]).
518 keyword('lone',predicate,[alloy]).
519 keyword('not',predicate,[alloy]).
520 keyword('no',predicate,[alloy]).
521 keyword('none',predicate,[alloy]).
522 keyword('one',predicate,[alloy]).
523 keyword('or',predicate,[alloy]).
524 keyword('some',predicate,[alloy]).
525 keyword('set',expr,[alloy]).
526
527 % SVG
528
529 get_all_svg_classes(SList) :- findall(A,is_svg_shape_class(A),List), sort(List,SList).
530
531 is_svg_shape_class(a).
532 is_svg_shape_class(animate). % can be a child of other elements
533 is_svg_shape_class(animateMotion). % can be a child of other elements
534 is_svg_shape_class(animateTransform). % can be a child of other elements
535 is_svg_shape_class(circle).
536 is_svg_shape_class(clipPath).
537 is_svg_shape_class(defs).
538 is_svg_shape_class(desc).
539 is_svg_shape_class(ellipse).
540 is_svg_shape_class(filter).
541 is_svg_shape_class(foreignObject). % can have HTML as children, body, table, tr, th, td
542 is_svg_shape_class(g). % group
543 is_svg_shape_class(image). % SVG files displayed with <image> cannot be interactive, include dynamic elements with <use>
544 is_svg_shape_class(line).
545 is_svg_shape_class(marker).
546 is_svg_shape_class(mask).
547 is_svg_shape_class(mpath).
548 is_svg_shape_class(path).
549 is_svg_shape_class(pattern).
550 is_svg_shape_class(polygon).
551 is_svg_shape_class(polyline).
552 is_svg_shape_class(rect).
553 is_svg_shape_class(script).
554 is_svg_shape_class(set).
555 is_svg_shape_class(style).
556 is_svg_shape_class(svg).
557 is_svg_shape_class(symbol).
558 is_svg_shape_class(text).
559 is_svg_shape_class(title). % useful when adding as children to other objects
560 is_svg_shape_class(tspan).
561 is_svg_shape_class(use).
562 is_svg_shape_class(view).
563 is_svg_shape_class(viewport).
564 % Note: one can also create <svg>, ... and HTML tags such as with document.createElementNS
565 % Note: script and title are also HTML tags
566
567 get_all_svg_attributes(SList) :- findall(A,is_svg_attribute(A),List), sort(List,SList).
568
569 % virtual attributes processed by VisB
570 is_virtual_svg_attribute(children).
571 is_virtual_svg_attribute(group_id). % also works like parent_id and can be used to attach animate objects
572 is_virtual_svg_attribute(hovers).
573 is_virtual_svg_attribute(svg_class).
574 is_virtual_svg_attribute(text).
575 is_virtual_svg_attribute(title).
576
577 % first list of svg attributes which are not number or color attributes
578 is_svg_attribute('alignment-baseline'). % auto | baseline | before-edge | text-before-edge | middle | central | after-edge | text-after-edge | ideographic | alphabetic | hanging | mathematical | top | center | bottom
579 is_svg_attribute(attributeName). % from animate / animateTransform
580 is_svg_attribute(attributeType). % from animate
581 is_svg_attribute(begin). % from animate
582 is_svg_attribute(children). % virtual attribute of VisB
583 is_svg_attribute(class).
584 is_svg_attribute('clip-path').
585 is_svg_attribute('clip-rule').
586 is_svg_attribute('color-rendering').
587 is_svg_attribute(cursor).
588 is_svg_attribute(d). % path
589 is_svg_attribute(display).
590 is_svg_attribute(dur). % from animate
591 is_svg_attribute('dominant-baseline'). % auto | text-bottom | alphabetic | ideographic | middle | central | mathematical | hanging | text-top
592 is_svg_attribute('fill-opacity').
593 is_svg_attribute('fill-rule').
594 is_svg_attribute('filter').
595 is_svg_attribute('flood-opacity').
596 is_svg_attribute('font-family').
597 % font-size is below under number attributes
598 is_svg_attribute('font-style'). % normal | italic | oblique
599 is_svg_attribute('font-variant').
600 is_svg_attribute('font-weight'). % normal | bold | bolder | lighter | <number>
601 is_svg_attribute(from).
602 is_svg_attribute(group_id). % virtual attribute of VisB
603 is_svg_attribute(hovers). % virtual attribute of VisB
604 is_svg_attribute('href'). % use
605 is_svg_attribute(id).
606 is_svg_attribute('lengthAdjust'). % spacing | spacingAndGlyphs for text
607 is_svg_attribute('marker-end').
608 is_svg_attribute('marker-start').
609 is_svg_attribute(mask).
610 % Note: name is a deprecated SVG attribute
611 is_svg_attribute(overflow). % for text, foreigObject, ...
612 is_svg_attribute(path).
613 is_svg_attribute('pointer-events').
614 is_svg_attribute(points). % polyline, polygon
615 is_svg_attribute(preserveAspectRatio).
616 is_svg_attribute(radius).
617 is_svg_attribute(repeatDur).
618 is_svg_attribute(repeatCount). % from animate
619 is_svg_attribute(restart).
620 is_svg_attribute(rotate).
621 is_svg_attribute(scale).
622 is_svg_attribute(seed).
623 is_svg_attribute('shape-rendering').
624 is_svg_attribute(startoffset).
625 is_svg_attribute(stdDeviation).
626 is_svg_attribute(stitchTiles).
627 is_svg_attribute(stroke).
628 is_svg_attribute('stroke-dasharray').
629 is_svg_attribute('stroke-dashoffset').
630 is_svg_attribute('stroke-linecap'). % butt (default), round, square
631 is_svg_attribute('stroke-linejoin').
632 is_svg_attribute('stroke-miterlimit').
633 is_svg_attribute(style).
634 is_svg_attribute(surfaceScale).
635 is_svg_attribute(svg_class). % virtual attribute of VisB
636 is_svg_attribute(systemLanguage).
637 is_svg_attribute(tableValues).
638 is_svg_attribute(text). % specially processed by VisB as well
639 is_svg_attribute('text-anchor'). % start | middle | end
640 is_svg_attribute('text-decoration'). % underline | line-through, ....
641 is_svg_attribute('text-rendering'). % auto | optimizeSpeed | optimizeLegibility | geometricPrecision
642 is_svg_attribute(textLength).
643 is_svg_attribute(title). % virtual attribute of VisB
644 is_svg_attribute(to).
645 is_svg_attribute(transform).
646 is_svg_attribute(type).
647 is_svg_attribute(values). % from animate
648 is_svg_attribute(visibility).
649 is_svg_attribute('vector-effect').
650 is_svg_attribute('word-spacing').
651 is_svg_attribute('xlink:href').
652 is_svg_attribute(X) :- is_svg_number_attribute(X,_).
653 is_svg_attribute(X) :- is_svg_color_attribute(X).
654 % TODO: complete
655
656 is_svg_color_attribute(color). % can be applied to any element; provides currentcolor value
657 is_svg_color_attribute(fill). % can be applied to [circle,ellipse,path,polygon,polyline,rect,text,tref,tspan]).
658 is_svg_color_attribute(stroke). % can also be applied to all shapes we use circle, ...
659 is_svg_color_attribute('flood-color').
660 is_svg_color_attribute('lighting-color').
661 is_svg_color_attribute('stop-color').
662
663 is_svg_number_attribute(cx,[circle, ellipse, radialGradient]).
664 is_svg_number_attribute(cy,[circle, ellipse, radialGradient]).
665 is_svg_number_attribute(dx,_).
666 is_svg_number_attribute(dy,_).
667 is_svg_number_attribute(opacity,_).
668 is_svg_number_attribute(pathLength,_).
669 is_svg_number_attribute(x,[foreignObject,image,pattern,rect,svg,text,tspan,use]). % many more: cursor, image, mask, ...
670 is_svg_number_attribute(y,[foreignObject,image,pattern,rect,svg,text,tspan,use]).
671 is_svg_number_attribute(x1,[line,linearGradient]).
672 is_svg_number_attribute(x2,[line,linearGradient]).
673 is_svg_number_attribute(y1,[line,linearGradient]).
674 is_svg_number_attribute(y2,[line,linearGradient]).
675 is_svg_number_attribute('font-size',_).
676 is_svg_number_attribute('stop-opacity',_).
677 is_svg_number_attribute('stroke-opacity',_).
678 is_svg_number_attribute('stroke-width',_).
679 is_svg_number_attribute(height,[foreignObject,image,pattern,rect,svg]). % others like mask ,...
680 is_svg_number_attribute(width, [foreignObject,image,pattern,rect,svg]).
681 is_svg_number_attribute(r,[circle, radialGradient]).
682 is_svg_number_attribute(rx,[ellipse,rect]).
683 is_svg_number_attribute(ry,[ellipse,rect]).
684 is_svg_number_attribute(tabindex,_).
685 is_svg_number_attribute(z,_).
686
687 is_svg_color_name(aliceblue).
688 is_svg_color_name(antiquewhite).
689 is_svg_color_name(aqua).
690 is_svg_color_name(aquamarine).
691 is_svg_color_name(azure).
692 is_svg_color_name(beige).
693 is_svg_color_name(bisque).
694 is_svg_color_name(black).
695 is_svg_color_name(blanchedalmond).
696 is_svg_color_name(blue).
697 is_svg_color_name(blueviolet).
698 is_svg_color_name(brown).
699 is_svg_color_name(burlywood).
700 is_svg_color_name(cadetblue).
701 is_svg_color_name(chartreuse).
702 is_svg_color_name(chocolate).
703 is_svg_color_name(coral).
704 is_svg_color_name(cornflowerblue).
705 is_svg_color_name(cornsilk).
706 is_svg_color_name(crimson).
707 is_svg_color_name(cyan).
708 is_svg_color_name(darkblue).
709 is_svg_color_name(darkcyan).
710 is_svg_color_name(darkgoldenrod).
711 is_svg_color_name(darkgray).
712 is_svg_color_name(darkgreen).
713 is_svg_color_name(darkgrey).
714 is_svg_color_name(darkkhaki).
715 is_svg_color_name(darkmagenta).
716 is_svg_color_name(darkolivegreen).
717 is_svg_color_name(darkorange).
718 is_svg_color_name(darkorchid).
719 is_svg_color_name(darkred).
720 is_svg_color_name(darksalmon).
721 is_svg_color_name(darkseagreen).
722 is_svg_color_name(darkslateblue).
723 is_svg_color_name(darkslategray).
724 is_svg_color_name(darkslategrey).
725 is_svg_color_name(darkturquoise).
726 is_svg_color_name(darkviolet).
727 is_svg_color_name(deeppink).
728 is_svg_color_name(deepskyblue).
729 is_svg_color_name(dimgray).
730 is_svg_color_name(dimgrey).
731 is_svg_color_name(dodgerblue).
732 is_svg_color_name(firebrick).
733 is_svg_color_name(floralwhite).
734 is_svg_color_name(forestgreen).
735 is_svg_color_name(fuchsia).
736 is_svg_color_name(gainsboro).
737 is_svg_color_name(ghostwhite).
738 is_svg_color_name(gold).
739 is_svg_color_name(goldenrod).
740 is_svg_color_name(gray).
741 is_svg_color_name(green).
742 is_svg_color_name(greenyellow).
743 is_svg_color_name(grey).
744 is_svg_color_name(honeydew).
745 is_svg_color_name(hotpink).
746 is_svg_color_name(indianred).
747 is_svg_color_name(indigo).
748 is_svg_color_name(ivory).
749 is_svg_color_name(khaki).
750 is_svg_color_name(lavender).
751 is_svg_color_name(lavenderblush).
752 is_svg_color_name(lawngreen).
753 is_svg_color_name(lemonchiffon).
754 is_svg_color_name(lightblue).
755 is_svg_color_name(lightcoral).
756 is_svg_color_name(lightcyan).
757 is_svg_color_name(lightgoldenrodyellow).
758 is_svg_color_name(lightgray).
759 is_svg_color_name(lightgreen).
760 is_svg_color_name(lightgrey).
761 is_svg_color_name(lightpink).
762 is_svg_color_name(lightsalmon).
763 is_svg_color_name(lightseagreen).
764 is_svg_color_name(lightskyblue).
765 is_svg_color_name(lightslategray).
766 is_svg_color_name(lightslategrey).
767 is_svg_color_name(lightsteelblue).
768 is_svg_color_name(lightyellow).
769 is_svg_color_name(lime).
770 is_svg_color_name(limegreen).
771 is_svg_color_name(linen).
772 is_svg_color_name(magenta).
773 is_svg_color_name(maroon).
774 is_svg_color_name(mediumaquamarine).
775 is_svg_color_name(mediumblue).
776 is_svg_color_name(mediumorchid).
777 is_svg_color_name(mediumpurple).
778 is_svg_color_name(mediumseagreen).
779 is_svg_color_name(mediumslateblue).
780 is_svg_color_name(mediumspringgreen).
781 is_svg_color_name(mediumturquoise).
782 is_svg_color_name(mediumvioletred).
783 is_svg_color_name(midnightblue).
784 is_svg_color_name(mintcream).
785 is_svg_color_name(mistyrose).
786 is_svg_color_name(moccasin).
787 is_svg_color_name(navajowhite).
788 is_svg_color_name(navy).
789 is_svg_color_name(oldlace).
790 is_svg_color_name(olive).
791 is_svg_color_name(olivedrab).
792 is_svg_color_name(orange).
793 is_svg_color_name(orangered).
794 is_svg_color_name(orchid).
795 is_svg_color_name(palegoldenrod).
796 is_svg_color_name(palegreen).
797 is_svg_color_name(paleturquoise).
798 is_svg_color_name(palevioletred).
799 is_svg_color_name(papayawhip).
800 is_svg_color_name(peachpuff).
801 is_svg_color_name(peru).
802 is_svg_color_name(pink).
803 is_svg_color_name(plum).
804 is_svg_color_name(powderblue).
805 is_svg_color_name(purple).
806 is_svg_color_name(red).
807 is_svg_color_name(rosybrown).
808 is_svg_color_name(royalblue).
809 is_svg_color_name(saddlebrown).
810 is_svg_color_name(salmon).
811 is_svg_color_name(sandybrown).
812 is_svg_color_name(seagreen).
813 is_svg_color_name(seashell).
814 is_svg_color_name(sienna).
815 is_svg_color_name(silver).
816 is_svg_color_name(skyblue).
817 is_svg_color_name(slateblue).
818 is_svg_color_name(slategray).
819 is_svg_color_name(slategrey).
820 is_svg_color_name(snow).
821 is_svg_color_name(springgreen).
822 is_svg_color_name(steelblue).
823 is_svg_color_name(tan).
824 is_svg_color_name(teal).
825 is_svg_color_name(thistle).
826 is_svg_color_name(tomato).
827 is_svg_color_name(turquoise).
828 is_svg_color_name(violet).
829 is_svg_color_name(wheat).
830 is_svg_color_name(white).
831 is_svg_color_name(whitesmoke).
832 is_svg_color_name(yellow).
833 is_svg_color_name(yellowgreen).
834
835 % ----------------------------
836
837 % DOT
838 get_all_dot_attributes(SList) :- findall(A,is_dot_attribute(A),List), sort(List,SList).
839
840 % list of known synonyms of Dot attributes and how to translate them to SVG object attributes
841 dot2svg_attribute(fillcolor,fill).
842 dot2svg_attribute(fillcolour,fill).
843 dot2svg_attribute(fontname,'font-family').
844 dot2svg_attribute(fontcolor,fill). % one should probably use fill to colour text
845 dot2svg_attribute(fontcolour,fill).
846 dot2svg_attribute('font-color',fill). % not really a dot attribute, but a
847 dot2svg_attribute('font-colour',fill).
848 dot2svg_attribute(visible,visibility). % typical error
849
850 % list of Dot shapes which are not valid SVG classes and which SVG concept they map to
851 dotshape2svg_class('Mcircle',circle).
852 dotshape2svg_class(doublecircle,circle).
853 dotshape2svg_class(egg,ellipse).
854 dotshape2svg_class(oval,ellipse).
855 dotshape2svg_class('Msquare',rect).
856 dotshape2svg_class(box,rect).
857 dotshape2svg_class(box3d,rect).
858 dotshape2svg_class(rectangle,rect).
859 dotshape2svg_class(square,rect).
860 dotshape2svg_class('Mdiamond',polygon).
861 dotshape2svg_class(diamond,polygon).
862 dotshape2svg_class(doubleoctagon,polygon).
863 dotshape2svg_class(hexagon,polygon).
864 dotshape2svg_class(house,polygon).
865 dotshape2svg_class(invhouse,polygon).
866 dotshape2svg_class(invhouse,polygon).
867 dotshape2svg_class(invtrapezium,polygon).
868 dotshape2svg_class(invtriangle,polygon).
869 dotshape2svg_class(octagon,polygon).
870 dotshape2svg_class(parallelogram,polygon).
871 dotshape2svg_class(pentagon,polygon).
872 dotshape2svg_class(septagon,polygon).
873 dotshape2svg_class(trapezium,polygon).
874 dotshape2svg_class(triangle,polygon).
875 dotshape2svg_class(tripleoctagon,polygon).
876 dotshape2svg_class(note,text).
877 dotshape2svg_class(plaintext,text).
878 dotshape2svg_class(larrow,polyline).
879 dotshape2svg_class(rarrow,polyline).
880
881
882 % see https://graphviz.org/docs/nodes/, comments taken from there
883 is_dot_attribute(area).
884 is_dot_attribute(class). % Classnames to attach to the node, edge, graph, or cluster's SVG element. For svg only.
885 is_dot_attribute(color). % Basic drawing color for graphics, not text.
886 is_dot_attribute(colorscheme). % A color scheme namespace: the context for interpreting color names.
887 is_dot_attribute(comment). % Comments are inserted into output.
888 is_dot_attribute(distortion). % Distortion factor for shape=polygon.
889 is_dot_attribute(fillcolor). % Color used to fill the background of a node or cluster.
890 is_dot_attribute(fixedsize).
891 is_dot_attribute(fontcolor). % Color used for text.
892 is_dot_attribute(fontname). % Font used for text.
893 is_dot_attribute(fontsize). % Font size, in points, used for text.
894 is_dot_attribute(gradientangle). % If a gradient fill is being used, this determines the angle of the fill.
895 is_dot_attribute(group). % Name for a group of nodes, for bundling edges avoiding crossings. For dot only.
896 is_dot_attribute(height). % Height of node, in inches.
897 is_dot_attribute(href). % Synonym for URL. For map, postscript, svg only.
898 is_dot_attribute(id). % Identifier for graph objects. For map, postscript, svg only.
899 is_dot_attribute(image).
900 is_dot_attribute(imagepos).
901 is_dot_attribute(imagescale).
902 is_dot_attribute(label). % Text label attached to objects.
903 is_dot_attribute(labelloc). % Vertical placement of labels for nodes, root graphs and clusters.
904 is_dot_attribute(layer). % Specifies layers in which the node, edge or cluster is present.
905 %is_dot_attribute(margin). % For graphs, this sets x and y margins of canvas, in inches.
906 is_dot_attribute(nojustify). % Whether to justify multiline text vs the previous text line (rather than the side of the container).
907 is_dot_attribute(ordering). % default, out, in Constrains the left-to-right ordering of node edges. For dot only.
908 is_dot_attribute(orientation).% node shape rotation angle, or graph orientation.
909 is_dot_attribute(penwidth). % Specifies the width of the pen, in points, used to draw lines and curves.
910 is_dot_attribute(peripheries). % Set number of peripheries used in polygonal shapes and cluster boundaries.
911 is_dot_attribute(pin).
912 is_dot_attribute(pos).
913 is_dot_attribute(rects).
914 is_dot_attribute(regular).
915 is_dot_attribute(root).
916 is_dot_attribute(samplepoints). % Gives the number of points used for a circle/ellipse node.
917 is_dot_attribute(shape). % Sets the shape of a node.
918 is_dot_attribute(shapefile).
919 is_dot_attribute(showboxes). % Print guide boxes for debugging. For dot only.
920 is_dot_attribute(style). % Set style information for components of the graph.
921 is_dot_attribute(skew). % Skew factor for shape=polygon.
922 is_dot_attribute(sides). % Number of sides when shape=polygon.
923 is_dot_attribute(sortv). % Sort order of graph components for ordering packmode packing.
924 is_dot_attribute(target). % If the object has a URL, this attribute determines which window of the browser is used for the URL. For map, svg only.
925 is_dot_attribute(tooltip). % Tooltip (mouse hover text) attached to the node, edge, cluster, or graph
926 is_dot_attribute('URL').
927 is_dot_attribute(vertices).
928 is_dot_attribute(width). % Width of node, in inches.
929 is_dot_attribute(xlabel). % External label for a node or edge.
930 is_dot_attribute(xlp). % Position of an exterior label, in points. For write only.
931 is_dot_attribute(z). % Z-coordinate value for 3D layouts and displays.
932
933 % additional edge attributes from https://graphviz.org/docs/edges/
934 is_dot_attribute(arrowhead). % Style of arrowhead on the head node of an edge.
935 is_dot_attribute(arrowsize). % Multiplicative scale factor for arrowheads.
936 is_dot_attribute(arrowtail). % Style of arrowhead on the tail node of an edge.
937 is_dot_attribute(constraint). % If false, the edge is not used in ranking the nodes. For dot only.
938 is_dot_attribute(decorate). % Whether to connect the edge label to the edge with a line.
939 is_dot_attribute(dir). % Edge type for drawing arrowheads. (forward, back, both, none)
940 is_dot_attribute(headlabel). % Text label to be placed near head of edge.
941 is_dot_attribute(headport). % Indicates where on the head node to attach the head of the edge.
942 is_dot_attribute(labelangle).
943 is_dot_attribute(labeldistance).
944 is_dot_attribute(labelfloat).
945 is_dot_attribute(labelfontcolor). % Color used for headlabel and taillabel.
946 is_dot_attribute(labelfontname). % Font for headlabel and taillabel.
947 is_dot_attribute(labelfontsize). % Font size of headlabel and taillabel.
948 is_dot_attribute(len).
949 is_dot_attribute(lhead). % Logical head of an edge. For dot only.
950 is_dot_attribute(minlen). % Minimum edge length (rank difference between head and tail). For dot only.
951 is_dot_attribute(taillabel). % Text label to be placed near tail of edge.
952 is_dot_attribute(tailport). % Indicates where on the tail node to attach the tail of the edge.
953 is_dot_attribute(weight). % Weight of edge. In dot, the heavier the weight, the shorter, straighter and more vertical the edge is.
954
955 % for graphs:
956 is_dot_attribute(bgcolor).
957 % https://graphviz.org/doc/info/colors.html#brewer
958 % ex: accent8, blue9, brbg11, bugn9, bupu9, dark28, gnbu9, greeens9, greys9, oranges9, set312, set39, spectral11
959 % does not work as graph attribute, needs to be set as default node/edge attribute or added to nodes/edges
960 is_dot_attribute(compound). % If true, allow edges between clusters. For dot only, relevant for lhead/ltail edge attrs
961 is_dot_attribute(concentrate). % If true, use edge concentrators.
962 is_dot_attribute(landscape). % If true, the graph is rendered in landscape mode.
963 is_dot_attribute(layout). % Which layout engine to use. dot, neato, circo, fdp, sfdp, twopi, patchwork, nop, nop2
964 is_dot_attribute(mode). % Technique for optimizing the layout
965 %is_dot_attribute(ordering). % declared for nodes above, Constrains the left-to-right ordering of node edges. For dot only. out, in
966 %is_dot_attribute(orientation). % declared for nodes above, node shape rotation angle, or graph orientation
967 is_dot_attribute(outputorder). % Specify order in which nodes and edges are drawn
968 is_dot_attribute(overlap). % Determines if and how node overlaps should be removed
969 is_dot_attribute(rankdir). % Sets direction of graph layout. For dot only. TB, BT, LR, RL
970 is_dot_attribute(ranksep). % Specifies separation between ranks. For dot, twopi only.
971 is_dot_attribute(ratio). % Sets the aspect ratio (drawing height/drawing width) for the drawing.
972 is_dot_attribute(scale). % Scales layout by the given factor after the initial layout
973 is_dot_attribute(size). % Maximum width and height of drawing, in inches
974 is_dot_attribute(splines).
975
976 is_dot_attribute(directed). % virtual attribute -> influences whether dot_graph_generator writes digraph or graph
977 is_dot_attribute(strict). % virtual attribute -> influences whether dot_graph_generator writes strict digraph/graph
978
979 % -------------
980
981
982 % HTML tags can e.g. appear as children of foreign_objects in SVG
983 is_html_tag(a).
984 is_html_tag(abbr).
985 is_html_tag(acronym).
986 is_html_tag(address).
987 is_html_tag(applet).
988 is_html_tag(area).
989 is_html_tag(article).
990 is_html_tag(aside).
991 is_html_tag(audio).
992 is_html_tag(b). % bold
993 is_html_tag(base).
994 is_html_tag(basefont).
995 is_html_tag(bdi).
996 is_html_tag(bdo).
997 is_html_tag(big).
998 is_html_tag(blockquote).
999 is_html_tag(body).
1000 is_html_tag(br).
1001 is_html_tag(button). % clickable button
1002 is_html_tag(canvas).
1003 is_html_tag(caption).
1004 is_html_tag(center).
1005 is_html_tag(cite).
1006 is_html_tag(code).
1007 is_html_tag(col).
1008 is_html_tag(colgroup).
1009 is_html_tag(data).
1010 is_html_tag(datalist).
1011 is_html_tag(dd).
1012 is_html_tag(del). % deleted text
1013 is_html_tag(details).
1014 is_html_tag(dialog). % dialog or window
1015 is_html_tag(div).
1016 is_html_tag(dfn).
1017 is_html_tag(dl). % description list
1018 is_html_tag(dt).
1019 is_html_tag(em).
1020 is_html_tag(embed).
1021 is_html_tag(fieldset).
1022 is_html_tag(figcaption).
1023 is_html_tag(figure).
1024 is_html_tag(font).
1025 is_html_tag(footer).
1026 is_html_tag(form).
1027 is_html_tag(frame).
1028 is_html_tag(frameset).
1029 is_html_tag(h1).
1030 is_html_tag(h2).
1031 is_html_tag(h3).
1032 is_html_tag(h4).
1033 is_html_tag(h5).
1034 is_html_tag(h6).
1035 is_html_tag(head).
1036 is_html_tag(header).
1037 is_html_tag(hgroup).
1038 is_html_tag(hr). % horizontal rule
1039 is_html_tag(i). % italic
1040 is_html_tag(html).
1041 is_html_tag(iframe).
1042 is_html_tag(img).
1043 is_html_tag(input). % input field
1044 is_html_tag(ins). % inserted text
1045 is_html_tag(kbd). % keyboard input
1046 is_html_tag(label).
1047 is_html_tag(legend).
1048 is_html_tag(li).
1049 is_html_tag(link).
1050 is_html_tag(main).
1051 is_html_tag(map).
1052 is_html_tag(mark). % highlight text
1053 is_html_tag(meta).
1054 is_html_tag(metre). % shows scalar measurement within a range
1055 is_html_tag(nav).
1056 is_html_tag(noframes).
1057 is_html_tag(noscript).
1058 is_html_tag(object).
1059 is_html_tag(ol). % ordered list
1060 is_html_tag(optgroup).
1061 is_html_tag(option). % option in a select list
1062 is_html_tag(output).
1063 is_html_tag(p).
1064 is_html_tag(param).
1065 is_html_tag(picture).
1066 is_html_tag(pre).
1067 is_html_tag(progress). % shows completion progress of a task
1068 is_html_tag(q).
1069 is_html_tag(rp).
1070 is_html_tag(rt).
1071 is_html_tag(ruby).
1072 is_html_tag(s). % strikethrough
1073 is_html_tag(samp). % sample output
1074 is_html_tag(script).
1075 is_html_tag(section).
1076 is_html_tag(select). % dropdown list
1077 is_html_tag(small).
1078 is_html_tag(source).
1079 is_html_tag(span).
1080 is_html_tag(strike).
1081 is_html_tag(strong).
1082 is_html_tag(style).
1083 is_html_tag(summary).
1084 is_html_tag(sub). % subscript
1085 is_html_tag(sup). % superscript
1086 is_html_tag(svg).
1087 is_html_tag(table).
1088 is_html_tag(tbody).
1089 is_html_tag(td). % table data
1090 is_html_tag(template).
1091 is_html_tag(textarea). % multiline text input
1092 is_html_tag(tfoot).
1093 is_html_tag(th). % table header
1094 is_html_tag(thead).
1095 is_html_tag(time). % shows specific period in time or a range of time
1096 is_html_tag(title).
1097 is_html_tag(tr). % table row
1098 is_html_tag(track).
1099 is_html_tag(tt). % not supported in HTML 5
1100 is_html_tag(u). % underline
1101 is_html_tag(ul). % unordered list
1102 is_html_tag(var). % variables
1103 is_html_tag(video).
1104 is_html_tag(wbr).
1105
1106 % completely incomplete list :
1107 is_html_attribute(accesskey).
1108 is_html_attribute(class).
1109 is_html_attribute(contenteditable).
1110 is_html_attribute(contextmenu).
1111 is_html_attribute(dir).
1112 is_html_attribute(disabled). % for option,...
1113 is_html_attribute(draggable).
1114 is_html_attribute(enterkeyhing).
1115 is_html_attribute(hidden).
1116 is_html_attribute(href).
1117 is_html_attribute(id).
1118 is_html_attribute(inert).
1119 is_html_attribute(inputmode).
1120 is_html_attribute(label). % for option,...
1121 is_html_attribute(lang).
1122 is_html_attribute(media).
1123 is_html_attribute(onchange). % for Event attribute, e.g., for select
1124 is_html_attribute(onerror).
1125 is_html_attribute(onhaschange).
1126 is_html_attribute(onload).
1127 is_html_attribute(onmessage).
1128 is_html_attribute(popover).
1129 is_html_attribute(rel).
1130 is_html_attribute(selected). % for option,...
1131 is_html_attribute(spellcheck).
1132 is_html_attribute(style).
1133 is_html_attribute(tabindex).
1134 is_html_attribute(target). % for a
1135 is_html_attribute(title).
1136 is_html_attribute(translate).
1137 is_html_attribute(type). % for a
1138 is_html_attribute(value). % for option,...
1139
1140 % -------------
1141
1142 % some errors one could make, with a possible corrected id/keyword:
1143
1144 %suggested_alternative_id('RGAUSS','RNORMAL').
1145 %suggested_alternative_id('GAUSS','RNORMAL').
1146
1147 % -------------
1148
1149
1150 % translate_keywords:classical_b_keyword(K), \+ tools_matching:keyword(K,_,_). % Note: items is not a B keyword
1151 % TO DO: complete keywords for Alloy, TLA, Z minor modes; possibly add VisB/SVG and CUSTOM_GRAPH/GraphViz attributes
1152
1153 :- use_module(preferences,[eclipse_preference/2]).
1154 get_possible_preferences(SPrefs) :-
1155 findall(Pref,eclipse_preference(Pref,_),P),
1156 sort(P,SPrefs).
1157
1158 get_possible_preferences_matches_msg(String,FuzzyMatchMsg) :-
1159 get_possible_preferences(Prefs),
1160 if(get_possible_fuzzy_matches_and_completions_msg(String,Prefs,FuzzyMatchMsg),
1161 true,
1162 get_possible_inner_matches_msg(String,Prefs,FuzzyMatchMsg)). % also look for inner matches
1163
1164 :- use_module(specfile,[get_possible_language_specific_top_level_event/3]).
1165 :- use_module(bmachine,[b_is_operation_name/1, b_get_machine_operation/4]).
1166 get_possible_top_level_event_matches_msg(String,FuzzyMatchMsg) :-
1167 findall(Op,get_possible_language_specific_top_level_event(Op,_,_),Ops), sort(Ops,SOps),
1168 if(get_possible_fuzzy_matches_and_completions_msg(String,SOps,FuzzyMatchMsg),
1169 true,
1170 get_possible_inner_matches_msg(String,SOps,FuzzyMatchMsg)). % also look for inner matches
1171
1172 % also matches subsidiary (not top-level) operations
1173 get_possible_operation_matches_msg(OpName,FuzzyMatchMsg) :-
1174 findall(Name,b_get_machine_operation(Name,_Results,_Parameters,_),Ops), sort(Ops,SOps),
1175 if(get_possible_fuzzy_matches_and_completions_msg(OpName,SOps,FuzzyMatchMsg),
1176 true,
1177 if(get_possible_inner_matches_msg(OpName,SOps,FuzzyMatchMsg,no_norm,suffix_only), % first look for stricter matches
1178 true,
1179 get_possible_inner_matches_msg(OpName,SOps,FuzzyMatchMsg))).
1180
1181 get_possible_fuzzy_matches_and_completions_msg(String,AllIds,FuzzyMatchMsg) :-
1182 (get_possible_fuzzy_matches_msg(String,AllIds,FuzzyMatchMsg) ;
1183 get_possible_completions_msg(String,AllIds,FuzzyMatchMsg)).
1184
1185 get_possible_fuzzy_matches(ID,AllIDs,FuzzyMatches) :- atom(ID),!,
1186 atom_codes(ID,IDCodes),
1187 findall(Target,(member(Target,AllIDs),atom_codes(Target,TargetCodes),
1188 fuzzy_match_codes_lower_case(IDCodes,TargetCodes)),FuzzyMatches).
1189 get_possible_fuzzy_matches(ID,_,_) :-
1190 add_internal_error('Not an atom: ',get_possible_fuzzy_matches(ID,_,_)),fail.
1191
1192 % get possible matches as atom which can be used after phrase: Did you mean:
1193 get_possible_fuzzy_matches_msg(ID,AllIDs,Msg) :-
1194 get_possible_fuzzy_matches(ID,AllIDs,FuzzyMatches),
1195 get_match_msg(FuzzyMatches,Msg).
1196
1197 get_match_msg(FuzzyMatches,Msg) :-
1198 length(FuzzyMatches,Nr), Nr>0,
1199 get_msg(FuzzyMatches,Nr,Msg).
1200
1201 :- use_module(tools_strings,[ajoin/2,ajoin_with_sep/3]).
1202 get_msg([Match],1,Res) :- !, Res=Match.
1203 get_msg(List,Nr,Msg) :- Nr < 6, !,
1204 ajoin_with_sep(List,',',Msg).
1205 get_msg([First|_],Nr,Msg) :- N1 is Nr-1,
1206 ajoin([First,' (',N1,' more matches)'],Msg).
1207
1208
1209
1210 % get possible completions as atom which can be used after phrase: Did you mean:
1211 get_possible_completions_msg(ID,SortedAllIDs,Msg) :-
1212 atom_codes(ID,IDCodes0),
1213 codes_to_lower_case(IDCodes0,IDCodes),
1214 findall(Target,(member(Target,SortedAllIDs),atom_codes(Target,TargetCodes),
1215 codes_to_lower_case(TargetCodes,TC2),
1216 prefix(TC2,IDCodes) % IDCodes is a prefix of the target
1217 ),Completions),
1218 get_match_msg(Completions,Msg).
1219
1220
1221 % get possible interior matches as atom which can be used after phrase: Did you mean:
1222 get_possible_inner_matches_msg(ID,SortedAllIDs,Msg) :-
1223 get_possible_inner_matches_msg(ID,SortedAllIDs,Msg,lower_case_norm,all).
1224
1225 % if LC=lower_case_norm we normalise target and source to lower_case before matching
1226 get_possible_inner_matches_msg(ID,SortedAllIDs,Msg,LC,SuffixOnly) :-
1227 atom_codes(ID,IDCodes0),
1228 length(IDCodes0,Len), Len>3, % only do this if the string is long enough
1229 (LC=lower_case_norm -> codes_to_lower_case(IDCodes0,IDCodes) ; IDCodes=IDCodes0),
1230 findall(Target,(member(Target,SortedAllIDs),atom_codes(Target,TargetCodes),
1231 (LC=lower_case_norm -> codes_to_lower_case(TargetCodes,TC2) ; TC2=TargetCodes),
1232 % format('Looking for ~s inside ~s or vice-versa~n',[IDCodes,TC2]),
1233 (SuffixOnly \= suffix_only,
1234 sublist(IDCodes,TC2,_Before,_,_) -> true % Target TC2 is a sublist of ID
1235 ; (SuffixOnly=suffix_only -> AfterLength=0 ; true),
1236 sublist(TC2,IDCodes,_Bef,_Len,AfterLength) % ID is a sublist of the target
1237 )
1238 ),Completions),
1239 get_match_msg(Completions,Msg).
1240
1241