1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8% 
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License. 
13% 
14% The Original Code is  CPViz Constraint Visualization System
15% The Initial Developer of the Original Code is  Helmut Simonis
16% Portions created by the Initial Developer are
17% Copyright (C) 2009-2010 Helmut Simonis
18% 
19% Contributor(s): 	Helmut Simonis, 4C, Univerity College Cork, Cork
20%			
21% 
22% END LICENSE BLOCK
23% ----------------------------------------------------------------------
24:-module(visualization).
25:-comment(author,"Helmut Simonis").
26:-comment(status,"experimental").
27:-comment(copyright,"2010, Helmut Simonis").
28:-comment(categories,["Development Tools","Visualisation"]).
29:-comment(summary,"Definition of the log format for constraint and"
30                  " variable visualizers").
31:-comment(description,"This library describes how variable and"
32                      " constraint visualizers record their"
33                      " information in the log files. It also provides"
34                      " predicates to start and stop the visualization"
35                      " process. The library is re-exported by visualize_tree, it does not need to be loaded independently").
36
37
38:-comment(create_visualization/2,[summary:"Prepare to generate"
39                                          " visualization output",
40                  args:["Options":"a list of option pairs of form option:value",
41                        "Handle":"a free variable, will be bound to an opaque data structure for the visualization"],
42                  amode:create_visualization(+,-),
43                  desc:html("<P>This predicate prepares the system for"
44                            " visualization output and create a data"
45                            " structure Handle which is used by all"
46                            " other visualization predicates. For"
47                            " every run, the predicate should only be"
48                            " called once. It can not be called again,"
49                            " until the current visualization is"
50                            " closed with close_visualization/1. The"
51                            " predicate only prepares the system, it"
52                            " does not record a execution state on its own."
53			    "</P><P>"
54			    "Possible options are:"
55			    "<DL>"
56			    "<DT>output</DT><DD>"
57			    "   atom/string (default 'OUTPUT'), name of directory where log files will be placed"
58			    "</DD>"
59			    "<DT>ignore_fixed</DT><DD>"
60			    "    yes/no (default yes), states if fixed assignments will be ignored and not create tree nodes"
61			    "</DD>"
62			    "</DL>"
63			    "</P>"),
64                  eg:ascii("top(N,L):-\n"
65                           "    length(L,N),\n"                
66                           "    L :: 1..N,\n"
67                           "    alldifferent(L),\n"
68                           "    create_visualization([],Handle),\n"
69                           "    add_visualizer(Handle,vector(L),[]),\n"
70                           "    number_variables(Handle,L,Terms),\n"
71                           "    root(Handle),\n"
72                           "    search(Terms,1,first_fail,tree_indomain(Handle,_),complete,[]),\n"
73                           "    solution(Handle),\n"
74                           "    close_visualization(Handle).\n"),
75                  see_also:[root/1,solution/1,try/4,failure/4,
76                            tree_indomain/3,draw_visualization/1,
77                            close_visualization/1]]).
78
79:-export(create_visualization/2).
80
81:-comment(add_visualizer/3,[summary:"Add a visualizer to the visualisation",
82                  args:["Handle":"an opaque data structure for the"
83                                 " visualization",
84                        "Visualizer":"a term, defining the visualizer",
85                        "Options":"a list of option:value pairs"
86                                  " describing the options to be"
87                                  " applied to the visualizer"],
88                  amode:add_visualizer(+,++,++),
89                  desc:html("<P>
90This predicate is used to add a visualizer to an existing
91visualization.  It can be called after the visualization has been
92created with a create_visualization/2 call.  The second argument is
93the description of the visualizer, either for variables or for
94constraints.
95</P><P>
96Variable visualizers display the state and/or evolution of a
97collection of variables.  At the moment this can be one of the
98following entries:
99
100<table border=1>
101<tr>
102<td>Variable Visualizer</td>  <td>Description</td>
103</tr>
104<tr>
105<td>vector(L)</td>  <td>The visualizer shows the current state of a
106collection of variables.  It marks which variables have been assigned,
107which values have been removed and which values remain in the domain.</td>
108</tr>
109<tr>
110<td>vector_waterfall(L)</td>  <td>This visualizer shows the changes of
111the collection of variables on the path from the root node to the
112current node.  It marks if a variable is assigned, changed (min and
113max, min, max or size only), or if it is not modified in each step.</td>
114</tr>
115<tr>
116<td>vector_size(L)</td>  <td>This visualizer shows the change of the
117domain sizes for a collection of variables from the root node to the
118current node in the search.</td>
119</tr>
120<tr>
121<td>binary_vector(Bool)</td>  <td>This visualizer is a special variant
122of the vector visualizer for a collection of 0/1 vairables.  Values
123are marked either as unassigned, or as assigned to zero or to one.</td>
124</tr>
125<tr>
126<td>domain_matrix(Matrix)</td>  <td>This visualizer shows a 2D matrix of
127domain variables.  Depending on the options, it only shows the
128assigned values, or displayed the values remaining in the domain.</td>
129</tr>
130<tr>
131<td>binary_matrix(BoolMatrix)</td>  <td>A specialized version of the
132matrix visualizer for 0/1 variables.</td>
133</tr>
134</table>
135
136</P><P>
137Constraint visualizers show the state and/or evolution of a global
138constraint.  At the moment, visualizers for the following global
139constraints are provided.
140
141<table border=1>
142<tr>
143<td>Constraint Visualizer</td><td></td>
144</tr>
145<tr>
146<td>alldifferent(Xs)</td><td></td>
147</tr>
148<tr>
149<td>alldifferent_matrix(Matrix)</td><td></td>
150</tr>
151<tr>
152<td>bin_packing(Items,Sizes,Bins)</td><td></td>
153</tr>
154<tr>
155<td>bool_channeling(X,Bool,Start)</td><td></td>
156</tr>
157<tr>
158<td>cumulative(Starts,Durations,Resources,Limit)</td><td></td>
159</tr>
160<tr>
161<td>cumulative(Starts,Durationss,Resources,Limit,End)</td><td></td>
162</tr>
163<tr>
164<td>disjoint2(Rectangles)</td><td></td>
165</tr>
166<tr>
167<td>element(X,Vs,Y)</td><td></td>
168</tr>
169<tr>
170<td>gcc(Limits,Vars)</td><td></td>
171</tr>
172<tr>
173<td>gcc_matrix(RowLimits,ColLimits,Matrix)</td><td></td>
174</tr>
175<tr>
176<td>inverse(Succ,Pred)</td><td></td>
177</tr>
178<tr>
179<td>lex_le(Xs,Ys)</td><td></td>
180</tr>
181<tr>
182<td>lex_lt(Xs,Ys)</td><td></td>
183</tr>
184<tr>
185<td>same(Xs,Ys)</td><td></td>
186</tr>
187<tr>
188<td>sequence_total(Min,Max,Low,Hi,K,ZeroOnes)</td><td></td>
189</tr>
190<tr>
191<td></td><td></td>
192</tr>
193</table>
194
195</P><P>
196Possible Options are:
197<DL>
198<DT>display</DT><DD>
199    influences how the visualizer will be drawn (expanded, text, gantt, ...),
200    default: minimal
201<DT>group</DT><DD>
202    group id number for the visualizer (integer, or 'other')
203<DT>x,y</DT><DD>
204    position at which the visualizer will be placed (default 0,0)
205</DD>
206</DL>
207</P>
208"),
209                  eg:ascii("top(N,L):-\n"
210                           "    length(L,N),\n"                
211                           "    L :: 1..N,\n"
212                           "    alldifferent(L),\n"
213                           "    create_visualization([],Handle),\n"
214                           "    add_visualizer(Handle,vector(L),[]),\n"
215                           "    number_variables(Handle,L,Terms),\n"
216                           "    root(Handle),\n"
217                           "    search(Terms,1,first_fail,tree_indomain(Handle,_),complete,[]),\n"
218                           "    solution(Handle),\n"
219                           "    close_visualization(Handle).\n"),
220                  see_also:[alldifferent/1,
221                            alldifferent_matrix/1,
222                            bin_packing/3,
223                            bool_channeling/3,
224                            cumulative/3,
225                            element/3,
226                            gcc/2,
227                            gcc_matrix/3,
228                            inverse/2,
229                            lex_le/2,
230                            lex_lt/2,
231                            same/2,
232                            sequence_total/6,
233                            create_visualization/2,
234                            close_visualization/1,
235                            solution/1,try/4,failure/4,tree_indomain/3,
236                            draw_visualization/1]]).
237
238:-export(add_visualizer/3).
239
240:-comment(draw_visualization/1,[summary:"Log the current state of the constraint system",
241                  args:["Handle":"an opaque data structure for the visualization"],
242                  amode:draw_visualization(+),
243                  desc:html("This predicate is used to explicitely log the state of the constraint systems for visualization. It is used by the application programmer to show the effect of some setup steps, before the search is started. It is also called automatically by the tree logging predicates, so that a user rarely needs to call it inside a search routine."),
244                  eg:ascii("top(N,L):-\n"
245                           "    length(L,N),\n"                
246                           "    L :: 1..N,\n"
247                           "    alldifferent(L),\n"
248                           "    create_visualization([],Handle),\n"
249                           "    add_visualizer(Handle,vector(L),[]),\n"
250                           "    draw_visualization(Handle),\n"
251                           "    close_visualization(Handle).\n"),
252                  see_also:[root/1,solution/1,try/4,failure/4,tree_indomain/3,draw_visualization/2]]).
253
254
255:-export(draw_visualization/1).
256
257:-comment(draw_visualization/2,[summary:"Log the current state of the constraint system",
258                  args:["Handle":"an opaque data structure for the visualization",
259                        "Options":"a list of option:value pairs"],
260                  amode:draw_visualization(+,+),
261                  desc:html("This predicate is used to explicitely log the state of the constraint systems for visualization, i.e. create a visualisation time point. It is used by the application programmer to show the effect of some setup steps, before the search is started. It is also called automatically by the tree logging predicates, so that a user rarely needs to call it inside a search routine."),
262                  eg:ascii("top(N,L):-\n"
263                           "    length(L,N),\n"                
264                           "    L :: 1..N,\n"
265                           "    alldifferent(L),\n"
266                           "    create_visualization([],Handle),\n"
267                           "    add_visualizer(Handle,vector(L),[]),\n"
268                           "    draw_visualization(Handle,[]),\n"
269                           "    close_visualization(Handle).\n"),
270                  see_also:[root/1,solution/1,try/4,failure/4,tree_indomain/3,draw_visualization/1]]).
271
272:-export(draw_visualization/2).
273
274:-comment(close_visualization/1,[summary:"Stop the visualization, close all log files and flush all file output",
275                  args:["Handle":"an opaque data structure for the visualization"],
276                  amode:close_visualization(+),
277                  desc:html("This predicate should be called at the end of a program to close the visualization logs, flush all file output and reset the internal data structures."),
278                  eg:ascii("top(N,L):-\n"
279                           "    length(L,N),\n"                
280                           "    L :: 1..N,\n"
281                           "    alldifferent(L),\n"
282                           "    create_visualization([],Handle),\n"
283                           "    add_visualizer(Handle,vector(L),[]),\n"
284                           "    number_variables(Handle,L,Terms),\n"
285                           "    root(Handle),\n"
286                           "    search(Terms,1,first_fail,tree_indomain(Handle,_),complete,[]),\n"
287                           "    solution(Handle),\n"
288                           "    close_visualization(Handle).\n"),
289                  see_also:[solution/1,try/4,failure/4,tree_indomain/3,visualization:draw_visualization/1]]).
290
291
292:-export(close_visualization/1).
293
294
295:-lib(ic).
296:-lib(lists).
297
298:-use_module(node_cnt).
299:-use_module(vis_structures).
300:-use_module(vis_options).
301
302% counting visualizers
303:-local variable(id).
304% counting calls to draw_visualizer
305:-local variable(number).
306
307create_visualization(Options,Handle):-
308        setval(id,0),
309        setval(number,0),
310        set_node_cnt(-1),
311        Handle = visualization{},
312        add_options(Options,visualization,Handle),
313        default_options(Handle,visualization),
314        open_overview(Handle).
315
316open_overview(visualization{root:Root,
317                            tree_root:TreeRoot,
318                            output:Dir,
319                            schema_path:SchemaPath,
320                            tree_stream:TreeStream,
321                            stream:Stream}):-
322	( exists(Dir) -> true ; mkdir(Dir) ),
323        concat_string([Dir,'/',Root,".viz"],File),
324        concat_string([Dir,'/',TreeRoot,".tre"],TreeFile),
325        open(File,write,Stream),
326        printf(Stream,"<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\n",[]),
327        printf(Stream,"<visualization version=\"1.0\"\n  xmlns:xsi="
328                      "\"http://www.w3.org/2001/XMLSchema-instance\"\n"
329                      "  xsi:noNamespaceSchemaLocation=\"%w/visualization.xsd\">\n",[SchemaPath]),
330        open(TreeFile,write,TreeStream),
331        printf(TreeStream,"<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\n",[]),
332        printf(TreeStream,"<tree version=\"1.0\"\n  xmlns:xsi=\"http://www.w3.org/2001/XMLSchema-instance\"\n  xsi:noNamespaceSchemaLocation=\"%w/tree.xsd\">\n",[SchemaPath]).
333
334close_visualization(Handle):-
335        close_overview(Handle).
336
337close_overview(visualization{stream:Stream,
338                             tree_stream:TreeStream}):-
339        printf(Stream,"</visualization>\n",[]),
340        close(Stream),
341        printf(TreeStream,"</tree>\n",[]),
342        close(TreeStream).
343
344
345add_visualizer(visualization{stream:Stream,
346                             visualizers:OpenList},Type,Options):-
347        incval(id),
348        getval(id,Id),
349        type_table(Type,TypeName),
350        domain_info(Type,Width,Height,Min,Max),
351        Visualizer = visualizer{id:Id,
352                                type:Type,
353                                type_name:TypeName},
354        add_options(Options,visualizer,Visualizer),
355        (memberchk(group:_,Options) ->
356            true
357        ;
358            add_options([group:Id],visualizer,Visualizer)
359        ),
360        add_options([width:Width,
361                     height:Height,
362                     min:Min,
363                     max:Max],visualizer,Visualizer),
364        default_options(Visualizer,visualizer),
365        store_visualizer(Stream,Visualizer),
366        memberchk(Visualizer,OpenList),
367        !.
368
369store_visualizer(Stream,visualizer{id:Id,
370                                   type_name:TypeName,
371                                   display:Display,
372                                   x:X,
373                                   y:Y,
374                                   width:Width,
375                                   height:Height,
376                                   group:Group,
377                                   min:Min,
378                                   max:Max}):-
379        printf(Stream,"<visualizer id=\"%w\" type=\"%w\" display=\"%w\" ",
380               [Id,TypeName,Display]),
381        optional(Stream,"x",X,0),
382        optional(Stream,"y",Y,0),
383        optional(Stream,"width",Width,0),
384        optional(Stream,"height",Height,0),
385        optional(Stream,"group",Group,'-'),
386        optional(Stream,"min",Min,0),
387        optional(Stream,"max",Max,0),
388        printf(Stream," />\n",[]).
389
390optional(_Stream,_Label,Default,Default):-
391        !.
392optional(Stream,Label,Var,_Default):-
393        printf(Stream," %w=\"%w\"",[Label,Var]).
394
395type_table(vector(_),vector).
396type_table(vector_waterfall(_),vector_waterfall).
397type_table(vector_size(_),vector_size).
398type_table(binary_vector(_),binary_vector).
399type_table(binary_matrix(_),binary_matrix).
400type_table(domain_matrix(_),domain_matrix).
401% constraints
402type_table(alldifferent(_),alldifferent).
403type_table(alldifferent_matrix(_),alldifferent_matrix).
404type_table(bin_packing(_,_,_),bin_packing).
405type_table(bool_channeling(_,_,_),bool_channeling).
406type_table(cumulative(_,_,_,_),cumulative).
407type_table(cumulative(_,_,_,_,_),cumulative).
408type_table(cumulative_cost(_,_,_,_,_),cumulative_cost).
409type_table(disjoint2(_,_,_),disjoint2).
410type_table(element(_,_,_),element).
411type_table(gcc(_,_),gcc).
412type_table(gcc_matrix(_,_,_),gcc_matrix).
413type_table(inverse(_,_),inverse).
414type_table(lex_le(_,_),lex_le).
415type_table(lex_lt(_,_),lex_lt).
416type_table(same(_,_),same).
417type_table(sequence_total(_,_,_,_,_,_),sequence_total).
418
419% visualizer specific; 
420domain_info(vector(Coll),Width,Height,Min,Max):-
421        !,
422        collection_to_list(Coll,L),
423        length(L,Width),
424        get_min_max(L,Min,Max),
425        Height is Max-Min+1.
426domain_info(vector_waterfall(Coll),Width,Height,Min,Max):-
427        !,
428        collection_to_list(Coll,L),
429        length(L,Width),
430        get_min_max(L,Min,Max),
431        Height is Width.
432domain_info(vector_size(Coll),Width,Height,Min,Max):-
433        !,
434        collection_to_list(Coll,L),
435        length(L,Width),
436        Height is Width,
437        Min = 0,
438        Max = 1.
439domain_info(binary_vector(Coll),Width,1,0,1):-
440        !,
441        collection_to_list(Coll,L),
442        length(L,Width).
443domain_info(binary_matrix(Matrix),M,N,0,1):-
444        !,
445        dim(Matrix,[N,M]).
446domain_info(domain_matrix(Matrix),M,N,Min,Max):-
447        !,
448        dim(Matrix,[N,M]),
449        flatten_array(Matrix,List),
450        get_min_max(List,Min,Max).
451domain_info(alldifferent(L),Width,Height,Min,Max):-
452        !,
453        domain_info(vector(L),Width,Height,Min,Max).
454domain_info(alldifferent_matrix(M),Width,Height,Min,Max):-
455        !,
456        domain_info(domain_matrix(M),Width,Height,Min,Max).
457domain_info(bin_packing(Items,Sizes,Bins),Width,Height,Min,Max):-
458        !,
459        collection_to_list(Items,_L1),
460        collection_to_list(Sizes,_L2),
461        collection_to_list(Bins,L3),
462        length(L3,Width),
463        get_min_max(L3,Min,Max),
464        Height is Max.
465domain_info(bool_channeling(X,_Bool,_Start),Width,Height,Min,Max):-
466        !,
467        get_integer_bounds(X,_,Width),
468        Height = 2,
469        Min = 0,
470        Max = 0.
471domain_info(cumulative(Start,Dur,Res,Limit),Width,Height,Min,Max):-
472        !,
473        collection_to_list(Start,L1),
474        collection_to_list(Dur,L2),
475        collection_to_list(Res,_L3),
476%        writeln(L3),
477        get_integer_bounds(Limit,_,Height),
478%        writeln(Height),
479        get_last_end(L1,L2,0,Width),
480%        writeln(Width-Height),
481        Min =0,
482        Max = 0.
483domain_info(cumulative(Start,Dur,Res,Limit,End),Width,Height,Min,Max):-
484        !,
485        collection_to_list(Start,L1),
486        collection_to_list(Dur,L2),
487        collection_to_list(Res,_L3),
488%        writeln(L3),
489        get_integer_bounds(Limit,_,Height),
490        get_integer_bounds(End,_,Width2),
491%        writeln(Height),
492        get_last_end(L1,L2,0,Width1),
493        Width is max(Width1,Width2),
494%        writeln(Width-Height),
495        Min =0,
496        Max = 0.
497domain_info(cumulative_cost(Areas,Tasks,Limit,Horizon,_Cost),Width,Height,Min,Max):-
498        !,
499        writeln(cc(Width)),
500        collection_to_list(Areas,_AreasList),
501        collection_to_list(Tasks,TasksList),
502        get_integer_bounds(Limit,_,Height),
503        get_integer_bounds(Horizon,_,Width2),
504        writeln(Height),
505        writeln(get_last_end(TasksList,0,Width1)),
506        get_last_end(TasksList,0,Width1),
507        Width is max(Width1,Width2),
508        writeln(Width-Height),
509        Min =0,
510        Max = 0.
511domain_info(disjoint2(_L,W,H),Width,Height,Min,Max):-
512        !,
513        get_integer_bounds(W,_,Width),
514        get_integer_bounds(H,_,Height),
515        Min = 0,
516        Max = 0.
517domain_info(element(_X,L,_C),Width,Height,Min,Max):-
518        !,
519        get_min_max(L,Min,Max),
520        length(L,N),
521        Width is N+2,
522        Height is Max-Min+3.
523domain_info(gcc(_,L),Width,Height,Min,Max):-
524        !,
525        domain_info(vector(L),Width,Height,Min,Max).
526domain_info(gcc_matrix(_,_,M),Width,Height,Min,Max):-
527        !,
528        domain_info(domain_matrix(M),Width,Height,Min,Max).
529domain_info(inverse(L,_K),Width,Height,Min,Max):-
530        !,
531        domain_info(vector(L),Width,Height,Min,Max).
532domain_info(same(L,_K),Width,Height,Min,Max):-
533        !,
534        domain_info(vector(L),Width,Height,Min,Max).
535domain_info(sequence_total(_,_,_,_,_,L),Width,Height,Min,Max):-
536        !,
537        domain_info(vector(L),Width,Height,Min,Max).
538domain_info(lex_le(L,_K),Width,Height,Min,Max):-
539        !,
540        domain_info(vector(L),Width,Height,Min,Max).
541domain_info(lex_lt(L,_K),Width,Height,Min,Max):-
542        !,
543        domain_info(vector(L),Width,Height,Min,Max).
544domain_info(Type,_,_,_,_):-
545        writeln(no_domain_info(Type)),
546        abort.
547
548get_last_end([],[],E,E).
549get_last_end([A|A1],[B|B1],E,End):-
550        get_integer_bounds(A,_,LastStart),
551        get_integer_bounds(B,_,MaxDur),
552        E1 is max(E,LastStart+MaxDur),
553        get_last_end(A1,B1,E1,End).
554
555get_last_end([],E,E).
556get_last_end([Task|A1],E,End):-
557        arg(1,Task,Start),
558        arg(2,Task,Dur),
559        get_integer_bounds(Start,_,LastStart),
560        get_integer_bounds(Dur,_,MaxDur),
561        E1 is max(E,LastStart+MaxDur),
562        get_last_end(A1,E1,End).
563
564binary_domain_rep(X,x):-
565        var(X),
566        !.
567binary_domain_rep(X,X).
568
569
570get_min_max([H|T],Min,Max):-
571        get_integer_bounds(H,Min0,Max0),
572        (foreach(X,T),
573         fromto(Min0,A,A1,Min),
574         fromto(Max0,B,B1,Max) do
575            get_integer_bounds(X,Min1,Max1),
576            A1 is min(A,Min1),
577            B1 is max(B,Max1)
578        ).
579
580
581draw_visualization(Handle):-
582        draw_visualization(Handle,[]).
583
584draw_visualization(Handle,_Options):-
585        var(Handle),
586        !.
587draw_visualization(Handle,Options):-
588        Handle = visualization{stream:Stream,
589                               visualizers:OpenList,
590                               range_from:From,
591                               range_to:To},
592        incval(number),
593        getval(number,Number),
594        current_node_cnt(TreeNode),
595        (Number >= From,Number =< To ->
596            printf(Stream,"<state id=\"%d\" tree_node=\"%d\" >\n",
597                   [Number,TreeNode]),
598            draw_lp(OpenList,Options,Handle,Stream),
599            printf(Stream,"</state>\n",[])
600        ;
601            true
602        ).
603
604
605
606draw_lp(X,_,_,_):-
607        var(X),
608        !.
609draw_lp([H|T],Options,Handle,Stream):-
610        draw_visualizer(H,Options,Handle,Stream),
611        draw_lp(T,Options,Handle,Stream).
612
613draw_visualizer(H,Options,_Handle,Stream):-
614        H = visualizer{id:Id,type:Type},
615        visualizer_state(Stream,Id,Type,Options).
616
617visualizer_state(Stream,Id,Type,Options):-
618        printf(Stream,"<visualizer_state id=\"%d\" >\n",[Id]),
619%        writeln(draw_type(Type)),
620        draw_type(Stream,Type),
621        draw_option(Stream,Options),
622        printf(Stream,"</visualizer_state>\n",[]).
623
624draw_option(Stream,Options):-
625        (delete(focus(Term),Options,O1a) ->
626            treat_focus(Stream,'-',Term)
627        ;
628            O1a = Options
629        ),
630        (delete(focus(Group,Term),O1a,O1) ->
631            treat_focus(Stream,Group,Term)
632        ;
633            O1 = O1a
634        ),
635        (delete(failed(Index,Value),O1,O2a) ->
636            treat_failed(Stream,'-',Index,Value)
637        ;
638            O2a = O1
639        ),
640        (delete(failed(Group,Index,Value),O2a,O2) ->
641            treat_failed(Stream,Group,Index,Value)
642        ;
643            O2 = O2a
644        ),
645        (delete(focus:Term,O2,O3) ->
646            treat_focus(Stream,'-',Term)
647        ;
648            O3 = O2
649        ),
650        (O3 = [] ->
651            true
652        ;
653            writeln(unknown_option(O2))
654        ).
655
656treat_failed(Stream,Group,Index,Value):-
657        integer(Index),
658        integer(Value),
659        !,
660        printf(Stream,"<failed",[]),
661        optional(Stream,"group",Group,'-'),
662        printf(Stream," index=\"%w\" value=\"%w\" />\n",
663               [Index,Value]).
664treat_failed(Stream,Group,I-J,Value):-
665        integer(I),
666        integer(J),
667        integer(Value),
668        !,
669        printf(Stream,"<failed",[]),
670        optional(Stream,"group",Group,'-'),
671        printf(Stream," index=\"%w %w\" value=\"%w\" />\n",
672               [I,J,Value]).
673treat_failed(_Stream,Group,Index,Value):-
674        writeln(unknown_failed(Group,Index,Value)),
675        abort.
676
677
678
679treat_focus(Stream,Group,I):-
680        integer(I),
681        !,
682        printf(Stream,"<focus",[]),
683        optional(Stream,"group",Group,'-'),
684        printf(Stream," index=\"%w\" />\n",
685               [I]).
686treat_focus(Stream,Group,I-J):-
687        integer(I),
688        integer(J),
689        !,
690        printf(Stream,"<focus",[]),
691        optional(Stream,"group",Group,'-'),
692        printf(Stream," index=\"%w %w\" />\n",
693               [I,J]).
694treat_focus(Stream,Group,row(I)):-
695        !,
696        printf(Stream,"<focus",[]),
697        optional(Stream,"group",Group,'-'),
698        printf(Stream," type=\"%w\" index=\"%w\" />\n",
699               [row,I]).
700treat_focus(Stream,Group,col(I)):-
701        !,
702        printf(Stream,"<focus",[]),
703        optional(Stream,"group",Group,'-'),
704        printf(Stream," type=\"%w\" index=\"%w\" />\n",
705               [col,I]).
706treat_focus(Stream,Group,block(X,Y,W,H)):-
707        !,
708        printf(Stream,"<focus",[]),
709        optional(Stream,"group",Group,'-'),
710        printf(Stream," type=\"%w\" index=\"%w %w %w %w\" />\n",
711               [block,X,Y,W,H]).
712treat_focus(_Stream,Group,Index):-
713        writeln(unknown_focus(Group,Index)),
714        abort.
715
716draw_type(Stream,bin_packing(L1,L2,L3)):-
717        !,
718        printf(Stream,"<argument index=\"items\" >\n",[]),
719        draw_type(Stream,vector(L1)),
720        printf(Stream,"</argument>\n",[]),
721        printf(Stream,"<argument index=\"sizes\" >\n",[]),
722        draw_type(Stream,vector(L2)),
723        printf(Stream,"</argument>\n",[]),
724        printf(Stream,"<argument index=\"bins\" >\n",[]),
725        draw_type(Stream,vector(L3)),
726        printf(Stream,"</argument>\n",[]).
727draw_type(Stream,bool_channeling(X,Bool,Start)):-
728        !,
729        printf(Stream,"<argument index=\"1\" >\n",[]),
730        vector_entry(Stream,X,1),
731        printf(Stream,"</argument>\n",[]),
732        printf(Stream,"<argument index=\"2\" >\n",[]),
733        draw_type(Stream,vector(Bool)),
734        printf(Stream,"</argument>\n",[]),
735        printf(Stream,"<argument index=\"3\" >\n",[]),
736        vector_entry(Stream,Start,1),
737        printf(Stream,"</argument>\n",[]).
738draw_type(Stream,cumulative(L1,L2,L3,Limit)):-
739        !,
740        printf(Stream,"<argument index=\"tasks\" >\n",[]),
741        draw_tuples(Stream,L1,L2,L3,["start","dur","res"]),
742        printf(Stream,"</argument>\n",[]),
743        printf(Stream,"<argument index=\"limit\" >\n",[]),
744        vector_entry(Stream,Limit,1),
745        printf(Stream,"</argument>\n",[]).
746draw_type(Stream,cumulative(L1,L2,L3,Limit,End)):-
747        !,
748        printf(Stream,"<argument index=\"tasks\" >\n",[]),
749        draw_tuples(Stream,L1,L2,L3,["start","dur","res"]),
750        printf(Stream,"</argument>\n",[]),
751        printf(Stream,"<argument index=\"limit\" >\n",[]),
752        vector_entry(Stream,Limit,1),
753        printf(Stream,"</argument>\n",[]),
754        printf(Stream,"<argument index=\"end\" >\n",[]),
755        vector_entry(Stream,End,1),
756        printf(Stream,"</argument>\n",[]).
757draw_type(Stream,cumulative_cost(Areas,Tasks,Limit,End,Cost)):-
758        !,
759        writeln(draw_type),
760        printf(Stream,"<argument index=\"areas\" >\n",[]),
761        draw_tuples(Stream,Areas,["x","y","width","height","cost"]),
762        printf(Stream,"</argument>\n",[]),
763        printf(Stream,"<argument index=\"tasks\" >\n",[]),
764        draw_tuples(Stream,Tasks,["start","dur","res","lp"]),
765        printf(Stream,"</argument>\n",[]),
766        printf(Stream,"<argument index=\"limit\" >\n",[]),
767        vector_entry(Stream,Limit,1),
768        printf(Stream,"</argument>\n",[]),
769        printf(Stream,"<argument index=\"end\" >\n",[]),
770        vector_entry(Stream,End,1),
771        printf(Stream,"</argument>\n",[]),
772        printf(Stream,"<argument index=\"cost\" >\n",[]),
773        vector_entry(Stream,Cost,1),
774        printf(Stream,"</argument>\n",[]).
775draw_type(Stream,disjoint2(Rect,W,H)):-
776        !,
777        printf(Stream,"<argument index=\"1\" >\n",[]),
778        draw_tuples(Stream,Rect,["x","y","w","h"]),
779        printf(Stream,"</argument>\n",[]),
780        printf(Stream,"<argument index=\"2\" >\n",[]),
781        vector_entry(Stream,W,1),
782        printf(Stream,"</argument>\n",[]),
783        printf(Stream,"<argument index=\"3\" >\n",[]),
784        vector_entry(Stream,H,1),
785        printf(Stream,"</argument>\n",[]).
786draw_type(Stream,element(X,L,C)):-
787        !,
788        printf(Stream,"<argument index=\"1\" >\n",[]),
789        vector_entry(Stream,X,1),
790        printf(Stream,"</argument>\n",[]),
791        printf(Stream,"<argument index=\"2\" >\n",[]),
792        draw_type(Stream,vector(L)),
793        printf(Stream,"</argument>\n",[]),
794        printf(Stream,"<argument index=\"3\" >\n",[]),
795        vector_entry(Stream,C,1),
796        printf(Stream,"</argument>\n",[]).
797draw_type(Stream,gcc(Param,L)):-
798        !,
799        printf(Stream,"<argument index=\"1\" >\n",[]),
800        draw_tuples(Stream,Param,["low","high","value"]),
801        printf(Stream,"</argument>\n",[]),
802        printf(Stream,"<argument index=\"2\" >\n",[]),
803        draw_type(Stream,vector(L)),
804        printf(Stream,"</argument>\n",[]).
805draw_type(Stream,gcc_matrix(ParamRow,ParamCol,M)):-
806        writeln(ParamRow),
807        !,
808        printf(Stream,"<argument index=\"1\" >\n",[]),
809        draw_collection_tuples(Stream,ParamRow,["low","high","value"]),
810        printf(Stream,"</argument>\n",[]),
811        printf(Stream,"<argument index=\"2\" >\n",[]),
812        draw_collection_tuples(Stream,ParamCol,["low","high","value"]),
813        printf(Stream,"</argument>\n",[]),
814        printf(Stream,"<argument index=\"3\" >\n",[]),
815        draw_type(Stream,domain_matrix(M)),
816        printf(Stream,"</argument>\n",[]).
817draw_type(Stream,inverse(L,K)):-
818        !,
819        printf(Stream,"<argument index=\"1\" >\n",[]),
820        draw_type(Stream,vector(L)),
821        printf(Stream,"</argument>\n",[]),
822        printf(Stream,"<argument index=\"2\" >\n",[]),
823        draw_type(Stream,vector(K)),
824        printf(Stream,"</argument>\n",[]).
825draw_type(Stream,lex_le(L,K)):-
826        !,
827        printf(Stream,"<argument index=\"1\" >\n",[]),
828        draw_type(Stream,vector(L)),
829        printf(Stream,"</argument>\n",[]),
830        printf(Stream,"<argument index=\"2\" >\n",[]),
831        draw_type(Stream,vector(K)),
832        printf(Stream,"</argument>\n",[]).
833draw_type(Stream,lex_lt(L,K)):-
834        !,
835        printf(Stream,"<argument index=\"1\" >\n",[]),
836        draw_type(Stream,vector(L)),
837        printf(Stream,"</argument>\n",[]),
838        printf(Stream,"<argument index=\"2\" >\n",[]),
839        draw_type(Stream,vector(K)),
840        printf(Stream,"</argument>\n",[]).
841draw_type(Stream,same(L,K)):-
842        !,
843        printf(Stream,"<argument index=\"1\" >\n",[]),
844        draw_type(Stream,vector(L)),
845        printf(Stream,"</argument>\n",[]),
846        printf(Stream,"<argument index=\"2\" >\n",[]),
847        draw_type(Stream,vector(K)),
848        printf(Stream,"</argument>\n",[]).
849draw_type(Stream,sequence_total(TotalLow,TotalHigh,Low,High,N,Binary)):-
850        !,
851        printf(Stream,"<argument index=\"TotalLow\" >\n",[]),
852        vector_entry(Stream,TotalLow,1),
853        printf(Stream,"</argument>\n",[]),
854        printf(Stream,"<argument index=\"TotalHigh\" >\n",[]),
855        vector_entry(Stream,TotalHigh,1),
856        printf(Stream,"</argument>\n",[]),
857        printf(Stream,"<argument index=\"Low\" >\n",[]),
858        vector_entry(Stream,Low,1),
859        printf(Stream,"</argument>\n",[]),
860        printf(Stream,"<argument index=\"High\" >\n",[]),
861        vector_entry(Stream,High,1),
862        printf(Stream,"</argument>\n",[]),
863        printf(Stream,"<argument index=\"N\" >\n",[]),
864        vector_entry(Stream,N,1),
865        printf(Stream,"</argument>\n",[]),
866        printf(Stream,"<argument index=\"Binary\" >\n",[]),
867        draw_type(Stream,vector(Binary)),
868        printf(Stream,"</argument>\n",[]).
869draw_type(Stream,Term):-
870        functor(Term,F,1),
871        memberchk(F,[vector,vector_waterfall,
872                     vector_size,binary_vector,alldifferent]),
873        arg(1,Term,L),
874        !,
875        collection_to_list(L,List),
876        (foreach(X,List),
877         count(J,1,_),
878         param(Stream) do
879            vector_entry(Stream,X,J)
880        ).
881draw_type(Stream,Term):-
882        functor(Term,F,1),
883        memberchk(F,[domain_matrix,binary_matrix,
884                     alldifferent_matrix]),
885        arg(1,Term,Matrix),
886        !,
887        (foreachelem(X,Matrix,[I,J]),
888         param(Stream) do
889            matrix_entry(Stream,X,I,J)
890        ).
891draw_type(_Stream,Type):-
892        writeln(unknown_type(Type)),
893        abort.
894
895
896draw_collection_tuples(Stream,Lists,Keys):-
897        (foreach(X,Lists),
898         count(J,1,_),
899         param(Stream,Keys) do
900            printf(Stream,"<collection index=\"%d\" >\n",[J]),
901            draw_tuples(Stream,X,Keys),
902            printf(Stream,"</collection>\n",[])
903        ).
904
905
906
907draw_tuples(Stream,L,Keys):-
908        (foreach(X,L),
909         count(J,1,_),
910         param(Stream,Keys) do
911            tuple_entry(Stream,J,X,Keys)
912        ).
913
914tuple_entry(Stream,J,X,Keys):-
915        printf(Stream,"<tuple index=\"%d\" >\n",[J]),
916        (foreach(Key,Keys),
917         count(J,1,_),
918         param(Stream,X) do
919            arg(J,X,V),
920            vector_entry(Stream,V,Key)
921        ),
922        printf(Stream,"</tuple>\n",[]).
923
924draw_tuples(Stream,L1,L2,L3,Keys):-
925        (foreach(X,L1),
926         foreach(Y,L2),
927         foreach(Z,L3),
928         count(J,1,_),
929         param(Stream,Keys) do
930            tuple_entry(Stream,J,X,Y,Z,Keys)
931        ).
932
933tuple_entry(Stream,J,X,Y,Z,[Key1,Key2,Key3]):-
934        printf(Stream,"<tuple index=\"%d\" >\n",[J]),
935        vector_entry(Stream,X,Key1),
936        vector_entry(Stream,Y,Key2),
937        vector_entry(Stream,Z,Key3),
938        printf(Stream,"</tuple>\n",[]).
939
940        
941        
942vector_entry(Stream,X,J):-
943        integer(X),
944        !,
945        printf(Stream,"<integer index=\"%w\" value=\"%d\" />\n",
946               [J,X]).
947vector_entry(Stream,X,J):-
948        is_solver_var(X),
949        !,
950        get_domain_as_white_spaced_list(X,Domain),
951        printf(Stream,"<dvar index=\"%w\" domain=\"%w\" />\n",
952               [J,Domain]).
953vector_entry(_Stream,Var,_J):-
954        var(Var),
955        !.
956vector_entry(Stream,List,J):-
957%        writeln(other(List,J)),
958        printf(Stream,"<collection index=\"%w\">\n",[J]),
959        (foreach(lp(Time,Value),List),
960         count(K,1,_),
961         param(Stream) do
962            printf(Stream,"<tuple index=\"%w\">\n",[K]),
963            printf(Stream,"<integer index=\"%w\" value=\"%d\" />\n",
964                   [time,Time]),
965            IntValue is integer(round(Value*10000)),
966            printf(Stream,"<integer index=\"%w\" value=\"%d\" />\n",
967                   [value,IntValue]),
968%            printf(Stream,"<number index=\"%w\" value=\"%7.5f\" />\n",
969%                   [value,Value]),
970            printf(Stream,"</tuple>\n",[])
971        ),
972        printf(Stream,"</collection>\n",[]).
973matrix_entry(Stream,X,I,J):-
974        integer(X),
975        !,
976        printf(Stream,"<integer index=\"%d %d\" value=\"%d\" />\n",
977               [I,J,X]).
978matrix_entry(Stream,X,I,J):-
979        get_domain_as_white_spaced_list(X,Domain),
980        printf(Stream,"<dvar index=\"%d %d\" domain=\"%w\" />\n",
981               [I,J,Domain]).
982
983get_domain_as_white_spaced_list(X,Domain):-
984        get_domain(X,EclipseDomain),
985        convert_to_white_spaced_list(EclipseDomain,Domain).
986
987convert_to_white_spaced_list(A..B,Domain):-
988        !,
989        join_string([A,"..",B]," ",Domain).
990convert_to_white_spaced_list(EclipseDomain,Domain):-
991%        writeln(EclipseDomain),
992        (foreach(A,EclipseDomain),
993         foreach(B,Entries) do
994            convert_entry(A,B)
995        ),
996        join_string(Entries," ",Domain).
997
998convert_entry(X,X):-
999        integer(X),
1000        !.
1001convert_entry(A..B,Entry):-
1002        join_string([A,"..",B]," ",Entry).
1003