1 % (c) 2009-2024 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(state_custom_dot_graph,[tcltk_generate_state_custom_dot_graph/1,
7 state_custom_dot_graph_available/0,
8 tcltk_generate_state_custom_dot_graph_for_expr/2,
9 is_valid_custom_dot_graph_record/1]).
10
11 :- use_module(probsrc(module_information)).
12 :- module_info(group,dot).
13 :- module_info(description,'This module provides a way to generate custom state graphs (using info from DEFINITIONS).').
14
15 :- use_module(dotsrc(dot_graph_generator)).
16
17 %:- use_module(self_check).
18 :- use_module(probsrc(error_manager)).
19
20 :- use_module(probsrc(state_space),[current_expression/2]).
21 :- use_module(probsrc(bsyntaxtree), [get_texpr_id/2]).
22 :- use_module(probsrc(specfile), [state_corresponds_to_fully_setup_b_machine/2]).
23 :- use_module(probsrc(debug), [debug_println/2, debug_format/3]).
24 :- use_module(probsrc(bmachine), [b_get_machine_custom_nodes_function/2,b_get_machine_custom_edges_function/2,
25 b_get_machine_custom_graph_function/2]).
26 :- use_module(probsrc(preferences),[valid_rgb_color/1, valid_dot_shape/1,
27 valid_dot_line_style/1, valid_dot_node_style/1]).
28 :- use_module(probsrc(tools),[start_ms_timer/1, stop_ms_timer_with_msg/2]).
29 :- use_module(library(lists),[exclude/3]).
30
31 :- set_prolog_flag(double_quotes, codes).
32
33
34 state_custom_dot_graph_available :-
35 b_get_machine_custom_graph_function(_,_) ;
36 % b_get_machine_custom_nodes_function(_,_) ;
37 b_get_machine_custom_edges_function(_,_).
38
39 reset_custom_defs :-
40 retractall(custom_nodes(_,_,_,_)),
41 retractall(custom_edges(_,_,_,_)),
42 retractall(custom_graph(_,_)),
43 retractall(custom_node_id(_,_)), retractall(nodectr(_)),
44 retractall(custom_trans_label(_,_)), retractall(trans_ctr(_)), assertz(trans_ctr(1)).
45
46 tcltk_generate_state_custom_dot_graph(File) :-
47 get_state_for_graph(BState),
48 (state_custom_dot_graph_available
49 -> true
50 ; add_error_and_fail(tcltk_generate_state_custom_dot_graph,
51 'No CUSTOM_GRAPH_EDGES or CUSTOM_GRAPH Function in DEFINITIONS')),
52 reset_custom_defs,
53 start_ms_timer(Timer),
54 eval_defs(BState),
55 gen_graph(File),
56 stop_ms_timer_with_msg(Timer,'custom graph: ').
57
58 :- use_module(probsrc(eval_let_store),[extend_state_with_probids_and_lets/2]).
59 :- use_module(probsrc(specfile), [get_current_state_for_b_formula/2]).
60 % provide a way to create a custom graph from an expression
61 % this expression should be a record with nodes, nedges fields, like a CUSTOM_GRAPH definition
62 tcltk_generate_state_custom_dot_graph_for_expr(GraphFunction,File) :-
63 get_current_state_for_b_formula(GraphFunction,BState),
64 extend_state_with_probids_and_lets(BState,BState1),
65 reset_custom_defs,
66 eval_custom_graph_function(GraphFunction,0,BState1),
67 gen_graph(File).
68
69 :- use_module(probsrc(preferences),[temporary_set_preference/3, reset_temporary_preference/2]).
70 gen_graph(File) :-
71 (custom_graph(_,GraphAttrs) -> true ; GraphAttrs=[]),
72 temporary_set_preference(dot_print_self_loops,true,Chng), % the user provides the edges function explicitly, show all edges
73 call_cleanup(gen_dot_graph(File,GraphAttrs,
74 use_new_dot_attr_pred(state_custom_dot_graph:cg_node_predicate),
75 use_new_dot_attr_pred(state_custom_dot_graph:cg_trans_predicate),
76 dot_no_same_rank,dot_no_subgraph),
77 reset_temporary_preference(dot_print_self_loops,Chng)).
78
79 get_state_for_graph(BState) :-
80 current_expression(_CurID,State),
81 state_corresponds_to_fully_setup_b_machine(State,BState),!.
82 get_state_for_graph(_) :- % we could look at type of definitions and use get_current_state_for_b_formula
83 add_error_and_fail(state_custom_dot_graph,'Only possible for initialised B machine.').
84
85 % check if something is a valid record for CUSTOM_GRAPH
86 % it must have a nodes and edges field
87 is_valid_custom_dot_graph_record(b(rec(Fields),_,_)) :-
88 member(field(NodesField,_),Fields), is_nodes_field(NodesField,_),!,
89 member(field(EdgesField,_),Fields), is_edges_field(EdgesField,_),!.
90
91 :- use_module(library(lists),[select/3]).
92 eval_defs(BState) :-
93 b_get_machine_custom_nodes_function(NodesFunction,Nr),
94 eval_definition_fun(NodesFunction, Nr, nodes, BState, Infos, NodesRes),
95 debug_println(19,custom_nodes(Nr,NodesRes)),
96 (select(label/EFID,Infos,RestInfos)
97 -> assertz(custom_nodes(EFID,Nr,RestInfos,NodesRes))
98 ; get_texpr_id(NodesFunction,EFID)
99 -> assertz(custom_nodes(EFID,Nr,Infos,NodesRes))
100 ; % we cannot derive name, then generate one
101 number_codes(Nr,NC), append("custom",NC,CC), atom_codes(Custom,CC),
102 assertz(custom_nodes(Custom,Nr,Infos,NodesRes))),
103 fail.
104 eval_defs(BState) :-
105 b_get_machine_custom_edges_function(EdgesFunction,Nr),
106 eval_definition_fun(EdgesFunction, Nr, edges, BState, Infos, EdgesRes),
107 debug_println(19,custom_edges(Nr,EdgesRes)),
108 (select(label/Label,Infos,RestInfos) -> true
109 ; get_texpr_id(EdgesFunction,Label) -> RestInfos=Infos
110 ; b_get_machine_custom_edges_function(_,Nr2), Nr2 \= Nr % other relation exists; makes sense to use label
111 -> number_codes(Nr,NC), append("custom",NC,CC),
112 atom_codes(Label,CC),RestInfos=Infos
113 ; Label='',RestInfos=Infos
114 ),
115 assertz(custom_edges(Label,Nr,RestInfos,EdgesRes)),
116 % print(edges(Label,Nr,RestInfos)),nl, translate:print_bvalue(EdgesRes),nl,nl,
117 fail.
118 eval_defs(BState) :-
119 b_get_machine_custom_graph_function(GraphFunction,Nr),
120 format('Detected single CUSTOM_GRAPH DEFINITION ~w~n',[Nr]),
121 eval_custom_graph_function(GraphFunction,Nr,BState),
122 fail.
123 eval_defs(_).
124
125 % Process a single CUSTOM_GRAPH record
126 % Example:
127 % rec(layout:"fdp",directed:TRUE,
128 % edges:rec(colorscheme:"purples9",
129 % edges:{x,y•x:2..50 & y:2..(x-1) & x mod y =0|
130 % rec(edge:y|->x, label:"div", color:1 + x mod 9)} ),
131 % nodes:rec(colorscheme:"set312", style:"filled",
132 % nodes:{x•x:2..50|rec(label:x,
133 % fillcolor: 1 + x mod 11) } ) );
134 eval_custom_graph_function(GraphFunction,Nr,BState) :-
135 eval_definition_fun(GraphFunction, Nr, graph, BState, GraphAttrs, rec(OtherFields)),
136 exclude(process_nodes_field([],GraphFunction),OtherFields,Infos1),
137 exclude(process_edges_field([],GraphFunction),Infos1,Infos2),
138 % instead of passing [] above, we could auto-detect GraphAttrs which are node or edge attributes
139 (Infos2 = [] ->
140 (Infos1=[]
141 -> add_message(state_custom_dot_graph,'No edges detected in CUSTOM_GRAPH: ',OtherFields,GraphFunction)
142 ; true)
143 ; add_warning(state_custom_dot_graph,'Unrecognized CUSTOM_GRAPH fields: ',Infos2,GraphFunction)),
144 (custom_graph(_,_)
145 -> add_warning(state_custom_dot_graph,'Duplicate CUSTOM_GRAPH definition: ',Nr,GraphFunction)
146 ; assertz(custom_graph(Nr,GraphAttrs))
147 ).
148
149 % process a single nodes:Nodes field and assert custom_nodes facts
150 process_nodes_field(DefaultAttrs,Span,field(NodeField,Nodes)) :-
151 is_nodes_field(NodeField,Nr),
152 assert_custom_nodes2(Nodes,DefaultAttrs,Span,Nr).
153
154 assert_custom_nodes2(Nodes,DefaultAttrs,Span,_Nr) :- Nodes = rec(_),
155 extract_record_fields(Nodes,_,DotAttributes,OtherFields),!,
156 % we have a nested record with default Attributes for the nodes
157 add_default_attrs(DefaultAttrs,DotAttributes,NewDefaultAttrs),
158 exclude(process_nodes_field(NewDefaultAttrs,Span),OtherFields,Infos1),
159 (Infos1 = [] -> true
160 ; add_warning(state_custom_dot_graph,'Unrecognized CUSTOM_GRAPH nodes fields: ',Infos1,Span)).
161 assert_custom_nodes2(Nodes,DefaultAttrs,_,Nr) :-
162 try_expand_custom_set_with_catch(Nodes, NodesRes,extract_dot_function),
163 assertz(custom_nodes('custom',Nr,DefaultAttrs,NodesRes)). %translate:print_bvalue(NodesRes),nl
164
165 is_nodes_field(nodes,0).
166 is_nodes_field(nodes0,0).
167 is_nodes_field(nodes1,1).
168 is_nodes_field(nodes2,2).
169 is_nodes_field(nodes3,3).
170 is_nodes_field(nodes4,4).
171 is_nodes_field(nodes5,5).
172 is_nodes_field(nodes6,6).
173 is_nodes_field(nodes7,7).
174 is_nodes_field(nodes8,8).
175 is_nodes_field(nodes9,9).
176
177 % process a single edges:Nodes field and assert custom_edges facts
178 process_edges_field(DefaultAttrs,Span,field(EdgesField,Edges)) :-
179 is_edges_field(EdgesField,Nr),
180 assert_custom_edges2(Edges,DefaultAttrs,Span,Nr).
181
182 assert_custom_edges2(Edges,DefaultAttrs,Span,_Nr) :- Edges = rec(_),
183 extract_record_fields(Edges,_,DotAttributes,OtherFields),!,
184 % we have a nested record with default Attributes for the edges
185 add_default_attrs(DefaultAttrs,DotAttributes,NewDefaultAttrs),
186 exclude(process_edges_field(NewDefaultAttrs,Span),OtherFields,Infos1),
187 (Infos1 = [] -> true
188 ; add_warning(state_custom_dot_graph,'Unrecognized CUSTOM_GRAPH edges fields: ',Infos1,Span)).
189 assert_custom_edges2(Edges,DefaultAttrs,_,Nr) :-
190 try_expand_custom_set_with_catch(Edges, EdgesRes,extract_dot_function),
191 (select(label/Label,DefaultAttrs,DA) -> true
192 ; Label='edge', DA=DefaultAttrs),
193 assertz(custom_edges(Label,Nr,DA,EdgesRes)).
194
195
196 is_edges_field(edges,0).
197 is_edges_field(edges0,0).
198 is_edges_field(edges1,1).
199 is_edges_field(edges2,2).
200 is_edges_field(edges3,3).
201 is_edges_field(edges4,4).
202 is_edges_field(edges5,5).
203 is_edges_field(edges6,6).
204 is_edges_field(edges7,7).
205 is_edges_field(edges8,8).
206 is_edges_field(edges9,9).
207
208 :- dynamic custom_nodes/4, custom_edges/4, custom_graph/2.
209
210 :- public cg_node_predicate/3.
211 :- use_module(probsrc(tools),[string_escape/2]).
212 % Custom Graph node predicate for dot_graph_generator.pl
213 cg_node_predicate(NodeID,SubGraph,Attributes) :- SubGraph=none,
214 custom_nodes(CustomID,_Nr,DefaultAttrs,Nodes),
215 debug_format(19,'Processing CUSTOM_GRAPH_NODES ~w~n',[CustomID]),
216 (var(Nodes) -> add_error(cg_node_predicate,'Variable custom_nodes: ',Nodes),fail ; true),
217 get_node_attributes(Nodes,DefaultAttrs,NodeVal,Attributes),
218 %tools:print_message(node(NodeVal,ColVal,Color,NodeID)),
219 gen_id(NodeVal,NodeID). %tools:print_message(nodeid(NodeID)).
220
221 get_node_attributes(CustomNodes,DefaultAttrs,NodeVal,[label/NodeDesc|Attrs]) :-
222 %(member(style/DefStyle,DefaultAttrs) -> true ; DefStyle=filled), % to do: extract multiple styles
223 %(member(shape/DefShape,DefaultAttrs) -> true ; DefShape=box),
224 member(Node,CustomNodes),
225 deconstruct_node(Node,DefaultAttrs,NodeVal,Attrs,Label),
226 %print(node(Label,NodeVal)),nl,
227 (Label\='$default' -> NodeDesc=Label
228 ; translate_value_and_escape(NodeVal,NodeDesc) -> true
229 ; NodeDesc = '???').
230
231
232 deconstruct_node(((NodeVal,string(Shape)),ColVal),DefaultAttrs,ResNodeVal,Attrs,'$default') :-
233 valid_dot_shape(Shape),
234 !, % we have a triple (Node,"box","colour") = ((Node,"box"),"colour")
235 ResNodeVal=NodeVal,
236 translate_bvalue_to_colour(ColVal,ResColVal),
237 add_default_attrs(DefaultAttrs,[color/ResColVal,shape/Shape],Attrs).
238 deconstruct_node((NodeVal,string(ColVal)),DefaultAttrs,ResNodeVal,Attrs,'$default') :-
239 valid_rgb_color(ColVal),
240 !, % we have a pair (Node,"colour")
241 ResNodeVal=NodeVal,
242 add_default_attrs(DefaultAttrs,[color/ColVal],Attrs).
243 deconstruct_node((NodeVal,string(Shape)),DefaultAttrs,ResNodeVal, Attrs,'$default') :-
244 valid_dot_shape(Shape),
245 !, % we have a pair (Node,"shape")
246 ResNodeVal=NodeVal,
247 add_default_attrs(DefaultAttrs,[shape/Shape],Attrs).
248 deconstruct_node(Record,DefaultAttrs,NodeVal,
249 Attrs,Label) :-
250 % New record style: this should probably be the default now
251 extract_record_fields(Record,AllFields,DotAttributes,RemainingVals),
252 DotAttributes = [_|_], % at least one field recognised
253 ( RemainingVals = [field(_,NodeVal)] -> true
254 ; member(field(value,NodeVal),RemainingVals) -> true
255 ; member(field(id,NodeVal),RemainingVals) -> true % like in VisB / SVG; note is also a valid dot_attribute_field
256 ; RemainingVals=[], member(label/_,DotAttributes)
257 -> member(field(label,NodeVal),AllFields) % get original value before translation to string
258 % but using label as node value may not be ideal for linking edges, better use separate value/id field
259 ; RemainingVals \= [] -> add_warning(state_custom_dot_graph,'Node has no label or value field:',Record,Record),
260 NodeVal = rec(RemainingVals)
261 ),
262 !,
263 % add default values if not specified:
264 ( select(label/LB,DotAttributes,Attrs0) -> Label=LB
265 ; select(description/LB,DotAttributes,Attrs0) -> Label=LB
266 ; Label = '$default', Attrs0=DotAttributes),
267 add_default_attrs(DefaultAttrs,Attrs0,Attrs).
268 deconstruct_node(NodeVal,DefaultAttrs,NodeVal,Attrs,'$default') :-
269 (DefaultAttrs=[]
270 -> format('CUSTOM_GRAPH_NODES value not recognised:~w~nUse rec(label:L,shape:"rect",...)~n',[NodeVal])
271 ; true % user has provided attributes in outer rec(...) construct
272 ),
273 add_default_attrs(DefaultAttrs,[],Attrs). % will remove none attributes
274 % shapes: triangle,ellipse,box,diamond,hexagon,octagon,house,invtriangle,invhouse,invtrapez,doubleoctagon,egg,parallelogram,pentagon,trapezium...
275
276 add_default_attrs([],Attrs,Attrs).
277 add_default_attrs([Attr/Val|T],Attrs,ResAttrs) :-
278 (member(Attr/_,Attrs) -> add_default_attrs(T,Attrs,ResAttrs)
279 ; Val=none, \+ none_valid(Attr) -> add_default_attrs(T,Attrs,ResAttrs) % Should we completely remove this line?
280 ; ResAttrs = [Attr/Val|RT],
281 add_default_attrs(T,Attrs,RT)).
282
283 % none is valid for arrowhead, arrowtail, ... and is different from default:
284 none_valid(arrowhead).
285 none_valid(arrowtail).
286
287 :- dynamic custom_node_id/2, nodectr/1.
288 nodectr(0).
289
290 get_ctr(Res) :- retract(nodectr(C)),!, C1 is C+1, assertz(nodectr(C1)), Res=C.
291 get_ctr(0) :- assertz(nodectr(1)).
292
293 % generate or lookup ID for node
294 gen_id(NodeVal,ID) :-
295 (custom_node_id(NodeVal,ID) -> true
296 ; get_ctr(C),
297 assertz(custom_node_id(NodeVal,C)),ID=C).
298
299 % TODO: hash NodeVal to improve performance for large graphs
300
301 % lookup ID and generate message if it does not exist
302 lookup_id(NodeVal,Kind,ID) :-
303 (custom_node_id(NodeVal,ID)
304 -> true
305 ; get_as_string(NodeVal,VS),
306 format(user_error,'The ~w node does not exist in CUSTOM_GRAPH_NODES: ~w~n',[Kind,VS]),
307 %format('Internal value: ~w~n',[NodeVal]), portray_nodes,
308 string_escape(VS,VSC),
309 assertz(custom_node_id(NodeVal,VSC)),
310 ID=VSC
311 ).
312
313 :- public portray_nodes/0.
314 portray_nodes :- format(' ~w : ~w (~w)~n',['ID','Value','internal value']),
315 custom_node_id(NodeVal,ID),
316 translate_bvalue(NodeVal,NS),
317 format(' ~w : ~w (~w)~n',[ID,NS,NodeVal]),fail.
318 portray_nodes.
319
320 :- dynamic custom_trans_label/2, trans_ctr/1.
321 trans_ctr(1).
322 gen_trans_color(Label,Col,_,IsColor) :- custom_trans_label(Label,C),!,Col=C,IsColor=false.
323 gen_trans_color(_Label,Col,Infos,IsColor) :- member(color/C,Infos),!,Col=C,IsColor=false.
324 gen_trans_color(Label,Col,_,IsColor) :- try_translate_bvalue_to_colour(Label,C),!,Col=C,IsColor=true.
325 gen_trans_color(Label,Col,_,IsColor) :- retract(trans_ctr(Ctr)), C1 is Ctr+1, assertz(trans_ctr(C1)),
326 translate_bvalue_to_colour(int(Ctr),C),
327 assertz(custom_trans_label(Label,C)), Col=C,IsColor=false.
328
329 :- public cg_trans_predicate/3.
330 % Custom graph transition predicate for dot_graph_generator.pl
331 cg_trans_predicate(NodeID,SuccID,DotAttributes) :-
332 custom_edges(DefaultLabel,_,Infos,Edges),
333 (member(color/DefaultCol,Infos) -> true ; DefaultCol=blue),
334 (var(Edges) -> add_error(trans_predicate,'Variable custom_edges: ',Edges),fail ; true),
335 member(Edge,Edges),
336 cg_trans_aux(Edge,(DefaultLabel,DefaultCol),Infos,FromNode,ToNode,Attrs),
337 add_default_attrs(Infos,Attrs,DotAttributes),
338 lookup_id(FromNode,source,NodeID),
339 lookup_id(ToNode,target,SuccID).
340
341 cg_trans_aux(Pair,DefaultLabelCol,Infos, FromNode,ToNode,[label/Label, color/Colour]) :-
342 get_pair(Pair,From1,To2),!,
343 trans_pred_aux(From1,DefaultLabelCol,Infos,To2,FromNode,ToNode,Label,Colour).
344 cg_trans_aux(Record,(DefaultLabel,DefaultCol),_Infos, FromNode,ToNode,Attrs) :-
345 extract_record_fields(Record,_,DotAttrs,Vals),
346 get_from_to(Vals,FromNode,ToNode),
347 add_default_attrs([color/DefaultCol,label/DefaultLabel],DotAttrs,Attrs).
348
349 :- use_module(probsrc(specfile), [animation_minor_mode/1]).
350 :- use_module(probsrc(custom_explicit_sets),[singleton_set/2]).
351 get_pair((From,To),From,To).
352 get_pair(Set,From,To) :- % process optional values, e.g., in Alloy
353 singleton_set(Set,El), !, El = (From,To).
354 get_pair(avl_set(A),From,To) :- % process TLA+ tuples <<from,to>> translated to -> {(1,From),(2,To)}
355 animation_minor_mode(tla),
356 try_expand_custom_set_with_catch(avl_set(A), FunctionRes,get_pair),
357 FunctionRes = [(int(1),From),(int(2),To)].
358
359
360 get_from_to(Vals,FromNode,ToNode) :- % either two field from:Fromnode, to:ToNode
361 member(field(from,FromNode),Vals),!,
362 member(field(to,ToNode),Vals).
363 get_from_to(Vals,FromNode,ToNode) :- % or a single edge field which is a pair
364 member(field(edge,(FromNode,ToNode)),Vals),!.
365
366
367 % we have a transition where the colour is specified (e.g., CUSTOM_GRAPH_EDGES == {n1,col,n2 | ... }
368 % we assume trans_predicate has been called first
369 trans_pred_aux((From,To),(Label,_Col),_Infos,string(Colour),From,To,Label,Colour) :-
370 To \= string(_), % we are not in one of the cases below where To is a label
371 valid_rgb_color(Colour),!.
372 % stems from something like CUSTOM_GRAPH_EDGES1 == graph*{"red"};
373 trans_pred_aux(FromValue,_Defaults,Infos,To,From,To,ELabel,Color) :-
374 % format(user_output,'from: ~w~nto: ~w~n~n',[FromValue,To]),
375 % ((From,LabelCol) |-> To) case
376 get_trans_label_and_color(FromValue,Infos,From,Color,ELabel), % the From Value contains color and label
377 !.
378 trans_pred_aux(From,_Defaults,Infos,(LabelVal,ToVal),From,To,ELabel,Color) :-
379 % (From |-> (LabelCol,To)) case
380 get_trans_label_and_color((ToVal,LabelVal),Infos,To,Color,ELabel), % the To Value contains color and label
381 !.
382 trans_pred_aux(From,(Label,Col),_Infos,To,From,To,Label,Col).
383 % no label or color specified in transition pair
384
385
386 % try and decompose a from value, detecting color and label string ((From,"label"),"color")
387 get_trans_label_and_color((FromVal,LabelVal),Infos,From,Color,ELabel) :-
388 gen_trans_color(LabelVal,Color,Infos,IsColor),
389 (IsColor
390 -> get_trans_label(FromVal,From,ELabel)
391 ; translate_value_and_escape(LabelVal,ELabel),
392 From=FromVal
393 ).
394
395 get_trans_label((From,string(LabelVal)),From,ELabel) :- string_escape(LabelVal,ELabel).
396 get_trans_label(From,From,''). % or should we use DefaultLabel
397
398 translate_value_and_escape(string(S),ELabel) :- !, string_escape(S,ELabel).
399 translate_value_and_escape(LabelVal,ELabel) :-
400 translate:translate_bvalue(LabelVal,Label),string_escape(Label,ELabel).
401
402 :- use_module(probsrc(b_interpreter),[b_compute_expression_nowf/6]).
403 :- use_module(probsrc(custom_explicit_sets),[try_expand_custom_set_with_catch/3]).
404 :- use_module(probsrc(bsyntaxtree),[get_texpr_info/2]).
405
406 % Kind = edges, nodes, graph
407 eval_definition_fun(AnimFunction, Nr, Kind, BState, SInfos, FunctionRes) :-
408 b_compute_expression_nowf(AnimFunction,[],BState,FunctionResCl,'custom state graph',Nr),
409 %nl, print('FunctionResult'(FunctionResCl)),nl,
410 get_texpr_info(AnimFunction,Pos),
411 extract_dot_function(FunctionResCl, Kind, Infos, FunctionRes,Pos),
412 sort(Infos,SInfos).
413
414 extract_dot_function(Value,graph,Attributes,FunctionRes,Pos) :- !, % for CUSTOM_GRAPH
415 extract_dot_graph_function(Value,Attributes,OtherFields,Pos),
416 FunctionRes=rec(OtherFields). % list of fields
417 extract_dot_function((Label,Value),Kind,Info,FunctionRes,Pos) :- % treat e.g. == ("red","F",F)
418 extract_dot_info(Label,Info,Info2),!,
419 extract_dot_function(Value,Kind,Info2,FunctionRes,Pos).
420 extract_dot_function((Value,Label),Kind,Info,FunctionRes,Pos) :-
421 extract_dot_info(Label,Info,Info2),!,
422 extract_dot_function(Value,Kind,Info2,FunctionRes,Pos).
423 extract_dot_function(Record,Kind,DefaultDotAttributes,FunctionRes,Pos) :-
424 % treat e.g. CUSTOM_GRAPH_NODES == rec(color:"blue", shape:"rect", nodes:e);
425 % or CUSTOM_GRAPH_EDGES == rec(color:"red", style:"dotted", edges:e);
426 % or CUSTOM_GRAPH_NODES == rec(color:"blue", label:"root", shape:"")
427 extract_record_fields(Record,_,DotAttributes,Vals),
428 !,
429 ( select(field(ValAttr,Value),Vals,RestVals),
430 member(ValAttr,[value, Kind]) % there is a value, edge, nodes field
431 % this a record setting attributes for a set of nodes/edges
432 -> DefaultDotAttributes = DotAttributes,
433 try_expand_custom_set_with_catch(Value, FunctionRes,extract_dot_function),
434 (RestVals=[] -> true ; add_message(state_custom_dot_graph,'Unrecognised DOT attributes: ',RestVals,Pos))
435 ; member(label/_,DotAttributes) % in case we have a label this represents a single record
436 -> FunctionRes = [Record], DefaultDotAttributes=[]
437 ; add_message(state_custom_graph,'CUSTOM_GRAPH record not ok (use fields color,shape,style,description and either label, edges or nodes): ',Vals,Pos),
438 fail
439 ).
440 extract_dot_function(Value,_Kind,[],FunctionRes,_) :-
441 % we try to see if it is a set of nodes (ideally as records) or edges
442 try_expand_custom_set_with_catch(Value,FunctionRes,extract_dot_function),!.
443 extract_dot_function(Value,_Kind,_,_,Pos) :-
444 add_warning(state_custom_dot_graph,'Illegal CUSTOM_GRAPH value (use rec(label:L,shape:,...) record or set of records): ',Value,Pos),
445 fail.
446
447 % treat single CUSTOM_GRAPH record:
448 extract_dot_graph_function(Record,Attributes,OtherFields,_) :-
449 extract_record_fields(Record,_,Attributes,OtherFields),!.
450 extract_dot_graph_function(Value,_,_,Pos) :-
451 add_warning(state_custom_dot_graph,'Illegal CUSTOM_GRAPH value, use record',Value,Pos),
452 fail.
453
454 :- use_module(probsrc(translate), [translate_bvalue/2]).
455 % extract dot information from a B value, if it looks like a color, shape, style or label
456 extract_dot_info((A,B),I0,I2) :- !, extract_dot_info(A,I0,I1), extract_dot_info(B,I1,I2).
457 extract_dot_info(string(Str),[Type/Str|T],T) :-
458 (infer_string_type(Str,Type) -> true ; Type=label).
459 extract_dot_info(Value,[label/Str|T],T) :- simple_label_value(Value),
460 translate_bvalue(Value,Str).
461 simple_label_value(fd(_,_)).
462
463 infer_string_type(Str,color) :- valid_rgb_color(Str).
464 infer_string_type(Str,shape) :- valid_dot_shape(Str).
465 infer_string_type(Str,style) :- valid_dot_line_style(Str).
466 infer_string_type(Str,style) :- valid_dot_node_style(Str).
467
468 % get record fields from record or partial function STRING +-> STRING
469 % and select dot attributes
470
471 extract_record_fields(Record,Fields,DotAttributes,OtherFields) :-
472 flexible_get_record_fields(Record,Fields),
473 extract_info_from_fields(Fields,DotAttributes,OtherFields).
474
475 :- use_module(library(lists),[maplist/3]).
476 :- use_module(probsrc(custom_explicit_sets),[try_expand_custom_set_with_catch/3, is_set_value/2]).
477 % similar to get_VISB_record_fields
478 flexible_get_record_fields(rec(Fields),Res) :- !, Res=Fields.
479 flexible_get_record_fields(StringFunction,Fields) :-
480 is_set_value(StringFunction,flexible_get_record_fields),
481 try_expand_custom_set_with_catch(StringFunction,Expanded,get_visb_DEFINITION_svg_object),
482 % TODO: check we have no duplicates
483 maplist(convert_to_field,Expanded,Fields).
484 convert_to_field((string(FieldName),Value),field(FieldName,Value)).
485
486 extract_info_from_fields([],[],[]).
487 extract_info_from_fields([field(FName,FVAL)|TF],[Type/Str|TI],Val) :-
488 dot_attribute_field(FName,Type),!,
489 ( \+ checked_attribute(Type) -> get_as_string_for_attr(Type,FVAL,Str)
490 ; get_label_value(Type,FVAL,Str) -> true
491 ; add_message(state_custom_dot_graph,'Unexpected value for dot attribute: ',Type/FVAL),
492 get_as_string(FVAL,Str)
493 ),
494 extract_info_from_fields(TF,TI,Val).
495 extract_info_from_fields([field(FName,FVAL)|TF],[FName/EStr|TI],Val) :-
496 \+ definitely_not_dot_attribute(FName),
497 get_as_string(FVAL,Str),
498 !,
499 add_message(state_custom_dot_graph,'Assuming this is a dot attribute: ',FName/Str),
500 string_escape(Str,EStr),
501 extract_info_from_fields(TF,TI,Val).
502 extract_info_from_fields([F|TF],Info,[F|TVal]) :-
503 extract_info_from_fields(TF,Info,TVal).
504
505 get_label_value(label,Val,Str) :- !, get_as_string(Val,Str).
506 get_label_value(description,string(Str),Str).
507 get_label_value(Type,string(Str),Str) :- infer_string_type(Str,Type).
508 get_label_value(color,Val,Str) :- get_color(Val,Str).
509
510 get_color(string(Str),Val) :- !, Val=Str.
511 get_color(int(Nr),Val) :- !, Val=Nr. % numbers can be valid DOT colors when colorscheme provided
512 get_color(Val,Col) :-
513 try_translate_bvalue_to_colour(Val,Col). % from dot_graph_generator
514
515 checked_attribute(description).
516 checked_attribute(color).
517 checked_attribute(shape).
518 checked_attribute(style).
519
520 definitely_not_dot_attribute(edge).
521 definitely_not_dot_attribute(from).
522 definitely_not_dot_attribute(nodes).
523 definitely_not_dot_attribute(to).
524 definitely_not_dot_attribute(value).
525 definitely_not_dot_attribute(E) :- is_edges_field(E,_).
526 definitely_not_dot_attribute(N) :- is_nodes_field(N,_).
527
528 :- use_module(probsrc(kernel_strings),[to_b_string/2]).
529 get_as_string(BValue,Str) :- to_b_string(BValue,string(Str)).
530
531 % cf b_value_to_id_string in VisB; allow to use pairs to concatenate strings
532 get_as_id_string(string(SValue),Res) :- !, Res=SValue.
533 get_as_id_string((A,B),Res) :- !,
534 get_as_id_string(A,VA), get_as_id_string(B,VB), atom_concat(VA,VB,Res).
535 % TODO: maybe convert sequence of values using conc
536 get_as_id_string(FValue,Res) :- get_as_string(FValue,Res).
537
538 get_as_string_for_attr(id,Val,Str) :- !, get_as_id_string(Val,Str). % like SVG ids in VisB
539 get_as_string_for_attr(_,Val,Str) :- !, get_as_string(Val,Str).
540
541 :- use_module(probsrc(tools_matching),[is_dot_attribute/1]).
542 dot_attribute_field(colour,color).
543 dot_attribute_field(fontcolour,fontcolor).
544 dot_attribute_field(description,description). % virtual attribute
545 dot_attribute_field(stroke,style). % used in SVG
546 dot_attribute_field(Name,Name) :- is_dot_attribute(Name).
547
548