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  The ECLiPSe Constraint Logic Programming System. 
15% The Initial Developer of the Original Code is  Cisco Systems, Inc. 
16% Portions created by the Initial Developer are
17% Copyright (C) 2006 Cisco Systems, Inc.  All Rights Reserved.
18% 
19% Contributor(s): 
20% 
21% END LICENSE BLOCK
22
23\chapter{Program annotation}
24When visualising CLP program behaviour, not all the variables of the
25program are of interest.  {\eclipse} supports the concept of a set of
26\viewable{} variables whose state over the course of a program run are
27of interest to the user.  The library
28\bipref{lib(viewable)}{../bips/lib/viewable/index.html} contains the
29annotation predicates that allow a programmer to define (and expand)
30these \viewable{} sets.
31
32
33\section{Viewables}
34\label{sec:viewables}
35By collecting together related program
36variables into a logical, multidimensional array-like structure called
37a \viewable{}, the user can view the changing state of these variables
38in a number of ways using the provided visualisation clients (these
39will be covered in depth later (section \ref{sec:visu-clients})).
40
41As an example of how to annotate an {\eclipse} program, consider the
42following classic cryptographic example, \texttt{SEND+MORE=MONEY}
43
44\begin{code}
45sendmore(Digits) :-
46    Digits = [S,E,N,D,M,O,R,Y],
47    Digits :: [0..9],
48    Carries = [C1,C2,C3,C4],
49    Carries :: [0..1],
50    alldifferent(Digits),
51    S #\verb+\+= 0,
52    M #\verb+\+= 0,
53    C1         #= M,
54    C2 + S + M #= O + 10*C1,
55    C3 + E + O #= N + 10*C2,
56    C4 + N + R #= E + 10*C3,
57         D + E #= Y + 10*C4,
58    labeling(Carries),
59    labeling(Digits).
60\end{code}
61
62
63It is hopefully clear from the code that this formulation of the
64classic puzzle uses four variables \texttt{[C1,C2,C3,C4]} to indicate
65the \emph{carry} digits.  If we suppose that the user is only
66interested in the behaviour of the program with respect to the primary
67problem variables, which in this case corresponds to the variables
68\texttt{[S,E,N,D,M,O,R,Y]}, then we can annotate the program code by
69declaring a \viewable{} which contains these variables.
70
71\begin{code}
72sendmore(Digits) :-
73    Digits = [S,E,N,D,M,O,R,Y],
74    Digits :: [0..9],
75    viewable_create(digits, Digits),
76    ...
77    ...
78    labeling(Carries),
79    labeling(Digits).
80\end{code}
81
82As can be seen, \viewable{}s are declared using the
83\viewablecreatetwo{} predicate, the first parameter of which is an
84atom which will be used to uniquely identify the \viewable{} later,
85and the second argument is a (possibly nested) list of variables.
86
87Declaring \viewable{}s has little performance overhead when running
88code normally (that is to say, without any visualisation clients), and
89so it is safe to leave the visualisation annotations in the code even
90when not visualising.
91
92\subsection{2D and beyond}
93In the previous example, the created \viewable{} was a simple one
94dimensional structure, it is possible however to create
95multi-dimensional structures if the problem variables are so related.
96For example one could choose to group the variables in a way that
97mirrors the problem structure, for example a 2D array representing the
98equation
99
100\begin{center}
101\begin{tabular}{c c c c c}
102  & S & E & N & D \\
103+ & M & O & R & E \\
104\hline
105M & O & N & E & Y
106\end{tabular}
107\end{center}
108
109would be the array
110\begin{displaymath}
111\left(\begin{array}{c c c c c}
1120 & S & E & N & D \\
1130 & M & O & R & E \\
114M & O & N & E & Y
115\end{array}\right)
116\end{displaymath}
117
118and would be declared in the program as nested lists
119
120\begin{quote}\begin{verbatim}
121viewable_create(equation,[[0, S, E, N, D],[0, M, O, R, E],[M, O, N, E, Y]]
122\end{verbatim}\end{quote}
123
124or it could be declared in the program using {\eclipse} array syntax
125\begin{quote}\begin{verbatim}
126viewable_create(equation,[]([](0, S, E, N, D),
127                            [](0, M, O, R, E),
128                            [](M, O, N, E, Y)))
129\end{verbatim}\end{quote}
130
131Three points should be noted here,
132\begin{enumerate}
133\item \viewablecreatetwo{} accepts both nested lists and arrays.
134\item Variables may occur more than once in \viewable{}.
135\item Constants may occur in \viewable{}s.
136\end{enumerate}
137
138
139\subsection{Growth}
140
141So far we have introduced only static (or \emph{fixed} dimension)
142\viewable{}s, but it is conceivable that during the course of program
143runs new variables may be introduced which the user has an interest in
144looking at.  In order to accommodate this, \viewable{}s may be
145declared as having \emph{flexible} dimensions.
146
147To declare a \viewable{} with flexible dimensions, the three argument
148form of the \viewablecreatethree{} predicate is used.  The third
149argument specifies the type of the \viewable{} and at present the type
150must be of the form \texttt{array(FixityList, ElementType)} where
151
152\begin{description}
153\item[\texttt{FixityList}] is a list with an atom \texttt{fixed} or
154\texttt{flexible} specifying the fixity for each dimension. The fixity
155denotes whether the dimension's size is fixed or may vary during the
156time when the viewable is existent.
157\item[\texttt{ElementType}] is a term which specifies the type of the
158constituent viewable elements. Currently there are two supported
159element types:
160
161  \begin{description}
162  \item[\texttt{any}] which includes any ECLiPSe term.
163  \item[\texttt{numeric_bounds}] which includes any ground number,
164  integer \bipref{fd}{../bips/lib/fd/index.html} variables,
165  \bipref{ic}{../bips/lib/ic/index.html} variables and
166  \bipref{range}{../bips/lib/range/index.html} variables (including
167  \bipref{eplex}{../bips/lib/eplex/index.html} and
168  \bipref{ria}{../bips/lib/ria/index.html} variables).
169  \end{description}
170
171\end{description}
172
173Let us expand our example by assuming that, during the program run our
174user is only interested in the \emph{digit} variables but once
175labelling has finished they wish to also see the \emph{carry}
176variables.  Clearly the user is free to simply print out the
177\emph{carry} variables after completing the labelling, but within the
178visualisation framework they may also expand the viewable by adding
179the \emph{carry} digits to it.  The code to do this is
180
181\begin{code}
182sendmore(Digits) :-
183    Digits = [S,E,N,D,M,O,R,Y],
184    Digits :: [0..9],
185    viewable_create(equation,
186                    []([](0, S, E, N, D),
187                       [](0, M, O, R, E),
188                       [](M, O, N, E, Y)),
189                    array([flexible,fixed], any)),
190    ...
191    ...
192    labeling(Carries),
193    labeling(Digits),
194    viewable_expand(equation, 1, [C1, C2, C3, C4, 0]).
195\end{code}
196
197Once declared as flexible, dimensions may be expanded by the
198\viewableexpandthree{} predicate.  The predicate specifies which
199dimension to expand and which values should be added.  Had the
200\viewable{} been 3 dimensional, then the values to be added would need
201to be 2 dimensional.  In general for an N dimensional \viewable{},
202when expanding a flexible dimension, the values to be added must be
203N-1 dimensional arrays or nested lists.
204
205As with \viewablecreatetwo{} and \viewablecreatethree{},
206\viewableexpandthree{} silently succeeds with little overhead at
207runtime, so it too may be left in code even when not visualising.
208
209
210\subsection{Types}
211
212As mentioned briefly in the previous section, \viewable{}s have a type
213definition which determines what sort of values may be stored in them.
214This type information allows visualisation clients to render the
215values in a fitting manner.
216
217Explicitly stating that the variables in a viewable are
218\texttt{numeric_bounds} where known will increase the number
219of ways in which the
220\viewable{} elements may be viewed.
221
222
223\subsection{Named dimensions}
224
225Each position in a \viewable{}'s dimension has an associated name.  By
226default, these names are simply the increasing natural numbers
227starting from ``1''.  So, for example, in the previous code samples
228the variable \texttt{R} would be at location \texttt{["2","4"]}.
229
230By using the most expressive form, the \viewablecreatefour{} predicate
231allows the user to assign their own symbolic names to dimension
232locations.
233
234In our ongoing example, we could name the first dimension positions
235\texttt{["send", "more", "money"]} and the second dimension positions
236\texttt{["ten thousands", "thousands", "hundreds", "tens", "units"]}.
237
238A version of \viewableexpandfour{} exists also which allows the user to
239assign a name to the new position of an expanded dimension.
240
241Our completed example now looks like this
242
243\begin{code}
244:-lib(viewable).
245
246sendmore(Digits) :-
247    Digits = [S,E,N,D,M,O,R,Y],
248    Digits :: [0..9],
249    viewable_create(equation,
250                    []([](0, S, E, N, D),
251                       [](0, M, O, R, E),
252                       [](M, O, N, E, Y)),
253                    array([flexible,fixed], numeric_bounds),
254                    [["send", "more", "money"],
255                     ["ten thousands", "thousands",
256                      "hundreds", "tens", "units"]]),
257    Carries = [C1,C2,C3,C4],
258    Carries :: [0..1],
259    alldifferent(Digits),
260    S #\verb+\+= 0,
261    M #\verb+\+= 0,
262    C1         #= M,
263    C2 + S + M #= O + 10*C1,
264    C3 + E + O #= N + 10*C2,
265    C4 + N + R #= E + 10*C3,
266         D + E #= Y + 10*C4,
267    labeling(Carries),
268    labeling(Digits),
269    viewable_expand(equation, 1, [C1, C2, C3, C4, 0], "carries").
270\end{code}
271
272\subsection{Structured data}
273
274In an effort to increase the ease with which program behaviour can be
275viewed and to provide tighter integration between {\eclipse} modules,
276data held in graph structures can also be annotated.
277
278The following code demonstrates how a simple graph structure from the
279\bipref{lib(graph_algorithms)}{../bips/lib/graph_algorithms/index.html}
280library can be used to define a \viewable{}.
281
282\begin{code}
283:-lib(graph_algorithms).
284:-lib(viewable).
285:-lib(ic).
286
287test:-
288    make_graph(7,
289               [e(1,2,F12), e(2,3,F23), e(2,4,F24), e(3,5,F35),
290                e(4,5,F45), e(4,6,F46), e(5,6,F56), e(6,3,F63),
291                e(6,7,F67)],
292               Graph),
293    Flows = [F23,F24,F35,F45,F46,F56,F63],
294    Flows :: 0..5,
295    (for(Node, 2, 6), param(Graph) do
296        graph_get_incoming_edges(Graph, Node, InEdges),
297        graph_get_adjacent_edges(Graph, Node, OutEdges),
298        (foreach(e(_From, _To, Flow), InEdges),
299         foreach(Flow, InFlow) do true),
300        (foreach(e(_From, _To, Flow), OutEdges),
301         foreach(Flow, OutFlow) do true),
302        sum(InFlow) #= sum(OutFlow)
303    ),
304    F12 #= 9,
305    viewable_create(flow_viewable, Graph, graph(fixed),
306                    [node_property([0->[name(nodes), label]]),
307                     edge_property([0->[name(edges), label]])
308                    ]),
309    labeling(Flows).
310\end{code}
311
312This simple network flow problem uses the graph structure to hold the
313problem variables and also to define the network topology.  Note the
314single \viewablecreatefour{} statement immediately before the
315labeling step.
316
317As with the regular list/array based viewable create calls, the first
318argument specifies the viewable name and the structure containing the
319variables of interest (in this case the graph) comes second.  The
320third argument defines the type as being a graph whose structure is
321fixed (as all graph_algorithms graphs are).  Currently only fixed
322graphs are supported.  The final (optional) argument defines a mapping
323between the node/edge structures within the graph and properties
324useful for visualisation.  The table below outlines the currently
325supported properties.
326
327\begin{tabular}{|l|p{0.5\textwidth}|c|c|}
328\hline
329markup & meaning & applicability & required \\
330\hline
331\hline
332name(String) & A unique name to refer to this property & both & yes \\
333\hline
334label & This property should be used as the node/edge text label & both & yes \\
335\hline
336\end{tabular}
337For more control over the display of graphs structures, consider using
338the \bipref{lib(graphviz)}{../bips/lib/graphviz/index.html} library.
339
340\subsection{Solver variables}
341The program annotations shown so far will work with most solvers in
342{\eclipse} but not all.  Generally speaking if the solver operates by
343monotonically reducing the domain of its variables then no further
344annotations are required.  There are solvers however which do not
345manipulate variables in this way.  For instance the
346\bipref{lib(eplex)}{../bips/lib/eplex/index.html} library uses
347{\eclipse} program variables as handles to the values calculated by an
348external solver.  When solutions are found by the external solver, the
349{\eclipse} variables are not (always) instantiated but rather must be
350queried to obtain their values.
351
352In order to facilitate the visualisation of such variables, the same
353\viewable creation annotations can be used, but the name of the solver
354must be given explicitly.  As an example consider the following
355\bipref{lib(eplex)}{../bips/lib/eplex/index.html} model of a simple
356transportation problem involving 3 factories \texttt{1,2,3} and 4
357clients \texttt{A,B,C,D} taken from the {\eclipse} examples web page.
358
359\begin{code}
360%----------------------------------------------------------------------
361% Example for basic use of ECLiPSe/CPLEX interface
362%
363% Distribution problem taken from EuroDecision chapter in D4.1
364%----------------------------------------------------------------------
365
366:- lib(eplex_xpress).
367:- eplex_instance(foo).
368
369%----------------------------------------------------------------------
370% Explicit version (clients A-D, plants 1-3)
371%----------------------------------------------------------------------
372
373main(Cost, Vars) :-
374        Vars = [A1, B1, C1, D1, A2, B2, C2, D2, A3, B3, C3, D3],
375        foo:(Vars :: 0.0..10000.0),              % variables
376
377        foo:(A1 + A2 + A3 $= 200),               % demand constraints
378        foo:(B1 + B2 + B3 $= 400),
379        foo:(C1 + C2 + C3 $= 300),
380        foo:(D1 + D2 + D3 $= 100),
381
382        foo:(A1 + B1 + C1 + D1 $=< 500),         % capacity constraints
383        foo:(A2 + B2 + C2 + D2 $=< 300),
384        foo:(A3 + B3 + C3 + D3 $=< 400),
385
386        foo:eplex_solver_setup(
387                       min(                      % solve
388                           10*A1 + 7*A2 + 11*A3 +
389                           8*B1 + 5*B2 + 10*B3 +
390                           5*C1 + 5*C2 +  8*C3 +
391                           9*D1 + 3*D2 +  7*D3)),
392
393        foo:eplex_solve(Cost).
394\end{code}
395
396Adding the following line immediately before the call to
397\texttt{eplex_solve/1} indicates that the solution values computed by
398the eplex instance \texttt{foo} are of interest.  Note the
399\emph{element type} field of the third argument says that the values
400of interest may be changed by the solver \texttt{foo}.  Further note
401that you will need to load the \viewable library inorder to access
402these annotations.
403
404\begin{code}
405viewable_create(vars, Vars
406                array([fixed], changeable(foo, any))),
407\end{code}        
408
409This \emph{changeable} element type can appear in any form of the
410annotations, so as another example, the following annotation gives
411more structure to the variables.
412
413\begin{code}
414viewable_create(vars, []([](A1, A2, A3),
415                         [](B1, B2, B3),
416                         [](C1, C2, C3),
417                         [](D1, D2, D3)),
418                array([fixed,fixed], changeable(foo, any))),
419\end{code}        
420
421As a final example, adding these two lines will make the structure of
422the problem even more explicit.
423
424\begin{code}
425make_graph_symbolic([]('A','B','C','D',1,2,3),
426                    [edge(1,'A',A1),edge(2,'A',A2),edge(3,'A',A3),
427                     edge(1,'B',B1),edge(2,'B',B2),edge(3,'B',B3),
428                     edge(1,'C',C1),edge(2,'C',C2),edge(3,'C',C3),
429                     edge(1,'D',D1),edge(2,'D',D2),edge(3,'D',D3)],G),
430viewable_create(network, G, graph(fixed,changeable(foo,graph_data))),
431\end{code}
432
433
434\quickref{Overview of program annotation}{
435\begin{description}
436\item[viewable_create\biprefnoidx{/2}{../bips/lib/viewable/viewable_create-2.html}\biprefnoidx{/3}{../bips/lib/viewable/viewable_create-3.html}\biprefnoidx{/4}{../bips/lib/viewable/viewable_create-4.html}]
437  used to group problem variables for visualisation purposes.  Groupings
438  referred to as \viewable{}s.
439\item[viewable_expand\biprefnoidx{/3}{../bips/lib/viewable/viewable_expand-3.html}\biprefnoidx{/4}{../bips/lib/viewable/viewable_expand-4.html}] \viewable{}s can be of a fixed size, or can expand and shrink.
440\item[types] elements of a \viewable{} may be defined as being numeric values or may be any \eclipse term.  The type of a \viewable{} will determine how it can be visualised.
441\item[structure] interesting variables contained within graph structures can be directly annotated using the \texttt{graph(static)} viewable type.
442\end{description}
443}
444