Previous Up Next

Chapter 2  Program annotation

When visualising CLP program behaviour, not all the variables of the program are of interest. ECLiPSe supports the concept of a set of viewable variables whose state over the course of a program run are of interest to the user. The library lib(viewable) contains the annotation predicates that allow a programmer to define (and expand) these viewable sets.

2.1  Viewables

By collecting together related program variables into a logical, multidimensional array-like structure called a viewable, the user can view the changing state of these variables in a number of ways using the provided visualisation clients (these will be covered in depth later (section 3)).

As an example of how to annotate an ECLiPSe program, consider the following classic cryptographic example, SEND+MORE=MONEY

sendmore(Digits) :-
    Digits = [S,E,N,D,M,O,R,Y],
    Digits :: [0..9],
    Carries = [C1,C2,C3,C4],
    Carries :: [0..1],
    alldifferent(Digits),
    S #\= 0,
    M #\= 0,
    C1         #= M,
    C2 + S + M #= O + 10*C1,
    C3 + E + O #= N + 10*C2,
    C4 + N + R #= E + 10*C3,
         D + E #= Y + 10*C4,
    labeling(Carries),
    labeling(Digits).

It is hopefully clear from the code that this formulation of the classic puzzle uses four variables [C1,C2,C3,C4] to indicate the carry digits. If we suppose that the user is only interested in the behaviour of the program with respect to the primary problem variables, which in this case corresponds to the variables [S,E,N,D,M,O,R,Y], then we can annotate the program code by declaring a viewable which contains these variables.

sendmore(Digits) :-
    Digits = [S,E,N,D,M,O,R,Y],
    Digits :: [0..9],
    viewable_create(digits, Digits),
    ...
    ...
    labeling(Carries),
    labeling(Digits).

As can be seen, viewables are declared using the viewable_create/2 predicate, the first parameter of which is an atom which will be used to uniquely identify the viewable later, and the second argument is a (possibly nested) list of variables.

Declaring viewables has little performance overhead when running code normally (that is to say, without any visualisation clients), and so it is safe to leave the visualisation annotations in the code even when not visualising.

2.1.1  2D and beyond

In the previous example, the created viewable was a simple one dimensional structure, it is possible however to create multi-dimensional structures if the problem variables are so related. For example one could choose to group the variables in a way that mirrors the problem structure, for example a 2D array representing the equation

 SEND
+MORE
MONEY

would be the array




0SEND 
0MORE 
MONEY



and would be declared in the program as nested lists

viewable_create(equation,[[0, S, E, N, D],[0, M, O, R, E],[M, O, N, E, Y]]

or it could be declared in the program using ECLiPSe array syntax

viewable_create(equation,[]([](0, S, E, N, D),
                            [](0, M, O, R, E),
                            [](M, O, N, E, Y)))

Three points should be noted here,

  1. viewable_create/2 accepts both nested lists and arrays.
  2. Variables may occur more than once in viewable.
  3. Constants may occur in viewables.

2.1.2  Growth

So far we have introduced only static (or fixed dimension) viewables, but it is conceivable that during the course of program runs new variables may be introduced which the user has an interest in looking at. In order to accommodate this, viewables may be declared as having flexible dimensions.

To declare a viewable with flexible dimensions, the three argument form of the viewable_create/3 predicate is used. The third argument specifies the type of the viewable and at present the type must be of the form array(FixityList, ElementType) where

FixityList
is a list with an atom fixed or flexible specifying the fixity for each dimension. The fixity denotes whether the dimension’s size is fixed or may vary during the time when the viewable is existent.
ElementType
is a term which specifies the type of the constituent viewable elements. Currently there are two supported element types:
any
which includes any ECLiPSe term.
numeric_bounds
which includes any ground number, integer fd variables, ic variables and range variables (including eplex and ria variables).

Let us expand our example by assuming that, during the program run our user is only interested in the digit variables but once labelling has finished they wish to also see the carry variables. Clearly the user is free to simply print out the carry variables after completing the labelling, but within the visualisation framework they may also expand the viewable by adding the carry digits to it. The code to do this is

sendmore(Digits) :-
    Digits = [S,E,N,D,M,O,R,Y],
    Digits :: [0..9],
    viewable_create(equation,
                    []([](0, S, E, N, D),
                       [](0, M, O, R, E),
                       [](M, O, N, E, Y)),
                    array([flexible,fixed], any)),
    ...
    ...
    labeling(Carries),
    labeling(Digits),
    viewable_expand(equation, 1, [C1, C2, C3, C4, 0]).

Once declared as flexible, dimensions may be expanded by the viewable_expand/3 predicate. The predicate specifies which dimension to expand and which values should be added. Had the viewable been 3 dimensional, then the values to be added would need to be 2 dimensional. In general for an N dimensional viewable, when expanding a flexible dimension, the values to be added must be N-1 dimensional arrays or nested lists.

As with viewable_create/2 and viewable_create/3, viewable_expand/3 silently succeeds with little overhead at runtime, so it too may be left in code even when not visualising.

2.1.3  Types

As mentioned briefly in the previous section, viewables have a type definition which determines what sort of values may be stored in them. This type information allows visualisation clients to render the values in a fitting manner.

Explicitly stating that the variables in a viewable are numeric_bounds where known will increase the number of ways in which the viewable elements may be viewed.

2.1.4  Named dimensions

Each position in a viewable’s dimension has an associated name. By default, these names are simply the increasing natural numbers starting from “1”. So, for example, in the previous code samples the variable R would be at location ["2","4"].

By using the most expressive form, the viewable_create/4 predicate allows the user to assign their own symbolic names to dimension locations.

In our ongoing example, we could name the first dimension positions ["send", "more", "money"] and the second dimension positions ["ten thousands", "thousands", "hundreds", "tens", "units"].

A version of viewable_expand/4 exists also which allows the user to assign a name to the new position of an expanded dimension.

Our completed example now looks like this

:-lib(viewable).

sendmore(Digits) :-
    Digits = [S,E,N,D,M,O,R,Y],
    Digits :: [0..9],
    viewable_create(equation,
                    []([](0, S, E, N, D),
                       [](0, M, O, R, E),
                       [](M, O, N, E, Y)),
                    array([flexible,fixed], numeric_bounds),
                    [["send", "more", "money"],
                     ["ten thousands", "thousands",
                      "hundreds", "tens", "units"]]),
    Carries = [C1,C2,C3,C4],
    Carries :: [0..1],
    alldifferent(Digits),
    S #\= 0,
    M #\= 0,
    C1         #= M,
    C2 + S + M #= O + 10*C1,
    C3 + E + O #= N + 10*C2,
    C4 + N + R #= E + 10*C3,
         D + E #= Y + 10*C4,
    labeling(Carries),
    labeling(Digits),
    viewable_expand(equation, 1, [C1, C2, C3, C4, 0], "carries").

2.1.5  Structured data

In an effort to increase the ease with which program behaviour can be viewed and to provide tighter integration between ECLiPSe modules, data held in graph structures can also be annotated.

The following code demonstrates how a simple graph structure from the lib(graph_algorithms) library can be used to define a viewable.

:-lib(graph_algorithms).
:-lib(viewable).
:-lib(ic).

test:-
    make_graph(7,
               [e(1,2,F12), e(2,3,F23), e(2,4,F24), e(3,5,F35),
                e(4,5,F45), e(4,6,F46), e(5,6,F56), e(6,3,F63),
                e(6,7,F67)],
               Graph),
    Flows = [F23,F24,F35,F45,F46,F56,F63],
    Flows :: 0..5,
    (for(Node, 2, 6), param(Graph) do
        graph_get_incoming_edges(Graph, Node, InEdges),
        graph_get_adjacent_edges(Graph, Node, OutEdges),
        (foreach(e(_From, _To, Flow), InEdges),
         foreach(Flow, InFlow) do true),
        (foreach(e(_From, _To, Flow), OutEdges),
         foreach(Flow, OutFlow) do true),
        sum(InFlow) #= sum(OutFlow)
    ),
    F12 #= 9,
    viewable_create(flow_viewable, Graph, graph(fixed),
                    [node_property([0->[name(nodes), label]]),
                     edge_property([0->[name(edges), label]])
                    ]),
    labeling(Flows).

This simple network flow problem uses the graph structure to hold the problem variables and also to define the network topology. Note the single viewable_create/4 statement immediately before the labeling step.

As with the regular list/array based viewable create calls, the first argument specifies the viewable name and the structure containing the variables of interest (in this case the graph) comes second. The third argument defines the type as being a graph whose structure is fixed (as all graph_algorithms graphs are). Currently only fixed graphs are supported. The final (optional) argument defines a mapping between the node/edge structures within the graph and properties useful for visualisation. The table below outlines the currently supported properties.

markupmeaningapplicabilityrequired
name(String)A unique name to refer to this propertybothyes
labelThis property should be used as the node/edge text labelbothyes

For more control over the display of graphs structures, consider using the lib(graphviz) library.

2.1.6  Solver variables

The program annotations shown so far will work with most solvers in ECLiPSe but not all. Generally speaking if the solver operates by monotonically reducing the domain of its variables then no further annotations are required. There are solvers however which do not manipulate variables in this way. For instance the lib(eplex) library uses ECLiPSe program variables as handles to the values calculated by an external solver. When solutions are found by the external solver, the ECLiPSe variables are not (always) instantiated but rather must be queried to obtain their values.

In order to facilitate the visualisation of such variables, the same viewablecreation annotations can be used, but the name of the solver must be given explicitly. As an example consider the following lib(eplex) model of a simple transportation problem involving 3 factories 1,2,3 and 4 clients A,B,C,D taken from the ECLiPSe examples web page.

%----------------------------------------------------------------------
% Example for basic use of ECLiPSe/CPLEX interface
%
% Distribution problem taken from EuroDecision chapter in D4.1
%----------------------------------------------------------------------

:- lib(eplex_xpress).
:- eplex_instance(foo).

%----------------------------------------------------------------------
% Explicit version (clients A-D, plants 1-3)
%----------------------------------------------------------------------

main(Cost, Vars) :-
        Vars = [A1, B1, C1, D1, A2, B2, C2, D2, A3, B3, C3, D3],
        foo:(Vars :: 0.0..10000.0),              % variables

        foo:(A1 + A2 + A3 $= 200),               % demand constraints
        foo:(B1 + B2 + B3 $= 400),
        foo:(C1 + C2 + C3 $= 300),
        foo:(D1 + D2 + D3 $= 100),

        foo:(A1 + B1 + C1 + D1 $=< 500),         % capacity constraints
        foo:(A2 + B2 + C2 + D2 $=< 300),
        foo:(A3 + B3 + C3 + D3 $=< 400),

        foo:eplex_solver_setup(
                       min(                      % solve
                           10*A1 + 7*A2 + 11*A3 +
                           8*B1 + 5*B2 + 10*B3 +
                           5*C1 + 5*C2 +  8*C3 +
                           9*D1 + 3*D2 +  7*D3)),

        foo:eplex_solve(Cost).

Adding the following line immediately before the call to eplex_solve/1 indicates that the solution values computed by the eplex instance foo are of interest. Note the element type field of the third argument says that the values of interest may be changed by the solver foo. Further note that you will need to load the viewablelibrary inorder to access these annotations.

viewable_create(vars, Vars
                array([fixed], changeable(foo, any))),

This changeable element type can appear in any form of the annotations, so as another example, the following annotation gives more structure to the variables.

viewable_create(vars, []([](A1, A2, A3),
                         [](B1, B2, B3),
                         [](C1, C2, C3),
                         [](D1, D2, D3)),
                array([fixed,fixed], changeable(foo, any))),

As a final example, adding these two lines will make the structure of the problem even more explicit.

make_graph_symbolic([](’A’,’B’,’C’,’D’,1,2,3),
                    [edge(1,’A’,A1),edge(2,’A’,A2),edge(3,’A’,A3),
                     edge(1,’B’,B1),edge(2,’B’,B2),edge(3,’B’,B3),
                     edge(1,’C’,C1),edge(2,’C’,C2),edge(3,’C’,C3),
                     edge(1,’D’,D1),edge(2,’D’,D2),edge(3,’D’,D3)],G),
viewable_create(network, G, graph(fixed,changeable(foo,graph_data))),


viewable_create/2/3/4
used to group problem variables for visualisation purposes. Groupings referred to as viewables.
viewable_expand/3/4
viewables can be of a fixed size, or can expand and shrink.
types
elements of a viewable may be defined as being numeric values or may be any ECLiPSeterm. The type of a viewable will determine how it can be visualised.
structure
interesting variables contained within graph structures can be directly annotated using the graph(static) viewable type.
Figure 2.1: Overview of program annotation


Previous Up Next