Previous Up Next

Chapter 5  Programming Concepts

5.1  Overview

In this chapter we will present typical programming concepts in ECLiPSe with example uses in the RiskWise application. These programming concepts each perform one particular operation in an efficient way, and show how these tasks should be programmed in ECLiPSe. They can be adapted to specific tasks by adding additional parameters, changing calls inside the concepts or passing different data structures.

The presentation of the concepts follows the same pattern: We first describe the concept in general terms and then present the parameters required. This is followed by one or several implementations of the concept in ECLiPSe, and some larger examples from the RiskWise code.

5.2  Alternatives

Description

This concept is used to choose between alternative actions based on some data structure. For each alternative, a guard qi is specified. The guard is a test which succeeds if the condition for selecting one alternative is met. The actions ri are executed when the guard succeeds. In order to choose only the right alternative, and not to leave any unwanted choicepoints in the execution, we must eliminate the remaining alternatives after the guard succeeds. For this we use a cut (!) after each guard but the last. We can leave out the cut after the last guard, as there are no choices left at this point.

Parameters
X
a data structure
Schema
:-mode alternatives(+).
alternatives(X):-
        q1(X),
        !,
        r1(X).
alternatives(X):-
        q2(X),
        !,
        r2(X).
alternatives(X):-
        qn(X),
        rn(X).
Comments

Very often, other parameters must be passed either to the guards, or to the actions.

The errors which are introduced if a cut to commit to a choice is left out are very hard to debug, and may only show after long execution. Much better to always cut after each guard.

When adding new parameters it is important to ensure that they are added to all clauses of the predicate. If a parameter is not used in some clause, then it should be added as a singleton variable. If we miss an argument on one of the clauses in the middle, the compiler will create an error message about non consecutive clauses. But if we miss an argument for either the first or the last clause, the compiler will just treat this as another predicate definition with the same name, but a different arity. Errors of this form are very hard to spot.

Example

:-mode interface_type(+,+,-).
interface_type(_Node,local,local):-
        !.
interface_type(Node,_Interface,backbone_net):-
        node(Node,net),
        !.
interface_type(Node,Interface,backbone):-
        backbone_line(Node,Interface,_,_),
        !.
interface_type(Node,Interface,backbone):-
        backbone_line(_,_,Node,Interface),
        !.
interface_type(Node,Interface,interconnection):-
        group(interconnection,_,Node,Interface),
        !.
interface_type(_Node,_Interface,customer).

Here we branch on information passed in the first two arguments, and return a result in the last argument. The last clause is a default rule, saying that the interface type is customer, if none of the other rules applied.

Some programmers perfer to make the output unification explicit, like so:

:-mode interface_type(+,+,-).
interface_type(_Node,local,Result):-
        !,
        Result = local.
interface_type(Node,_Interface,Result):-
        node(Node,net),
        !,
        Result = backbone_net.
interface_type(Node,Interface,Result):-
        backbone_line(Node,Interface,_,_),
        !,
        Result = backbone.
interface_type(Node,Interface,Result):-
        backbone_line(_,_,Node,Interface),
        !,
        Result = backbone.
interface_type(Node,Interface,Result):-
        group(interconnection,_,Node,Interface),
        !,
        Result = interconnection.
interface_type(_Node,_Interface,Result):-
        Result = customer.

This has advantages if the predicate may be called with the last argument instantiated.

5.3  Iteration on lists

Description

This concept is used to perform some action on each element of a list. There are two implementations given here. The first uses the do loop of ECLiPSe, the second uses recursion to achieve the same purpose. In the do loop, the foreach keyword describes an action for each element of a list. The first argument (here X) is a formal parameter of the loop. At each iteration, it will be bound to one element of the list. The second argument is the list over which we iterate.

It is a matter of style whether to use the first or second variant. For simple iterations, the do loop is usually more elegant. We can also often use it inline, and avoid introducing a new predicate name just to perform some iteration.

Parameters
L
a list
Schema
/* version 1 */

:-mode iteration(+).
iteration(L):-
        (foreach(X,L) do
            q(X)
        ).

/* version 2 */

:-mode iteration(+).
iteration([]).
iteration([H|T]):-
        q(H),
        iteration(T).

Comments

If we want to scan several lists in parallel, we can use multiple foreach statements in the same do loop. The following code fragment calls predicate q for the first elements of list L and K, then for the second elements, etc.

:-mode iteration(+,+).
iteration(L,K):-
        (foreach(X,L),
         foreach(Y,K) do
            q(X,Y)
        ).

This requires that the lists are of the same length, otherwise this do loop will fail.

Note that we can put as many parallel operations into a do loop as we want, they are all executed inside one big loop. We can of course also nest do loops so that one loop is executed inside another loop.

The foreach operator can also be used to create a list in a do loop. This is shown in the transformation concept.

Very often, we have to pass additional parameters into the do loop. We do this with the param parameter, which lists all variables from outside the loop that we want to use inside the loop. A variable which is not mentioned as a param argument, is unbound inside the loop. Normally, this will create a warning about a singleton variable inside a do loop. The following code fragment shows the use of param to pass variables A, B and C to the call of predicate q.

:-mode iteration(+,+,+,+).
iteration(L,A,B,C):-
        (foreach(X,L),
         param(A,B,C) do
            q(X,A,B,C)
        ).
Example

% set the group fields inside the interfaces for each interface
:-mode set_group_of_interfaces(+,+).
set_group_of_interfaces(L,Interfaces):-
        (foreach(group with [type:Type,
                             name:Name,
                             interface:I],L),
         param(Interfaces) do
            find_interface(I,Interfaces,Interface),
            set_group_of_interface(Type,Name,Interface)
        ).

Here we use the information that each member of the list L is a term group/4 to replace the formal parameter with a term structure where we access individual fields directly. Also note that the body of the loop may contain more than one predicate call.

5.4  Iteration on terms

Description

We can iterate not only over all elements of a list, as in the previous concept, but also over all arguments of a term. Obviously, this only makes sense if all arguments of the term are of a similar type i.e. the term is used as a vector. The foreacharg keyword of the do loop iterates over each argument of a term.

Parameters
T
a term
Schema
:-mode iteration(+).
iteration(T):-
        (foreacharg(X,T) do
            q(X)
        ).
Comments

We can use multiple foreacharg keywords to scan multiple vectors at the same time, but we cannot use foreacharg to create terms (we do not know the functor of the term). If we want to create a new term, we have to generate it with the right functor and arity before the do loop. The following code segment performs vector addition C = A+ B.

:-mode vector_add(+,+,-).
vector_add(A,B,C):-
        functor(A,F,N),
        functor(C,F,N),
        (foreacharg(X,A),
         foreacharg(Y,B),
         foreacharg(Z,C) do
           Z is X + Y
        ).

If the terms A and B do not have the same number of arguments, the predicate will fail.

Example

:-mode interface_mib_add(+,+,-).
interface_mib_add(A,B,C):-
        C = interface_mib with [],
        (foreacharg(A1,A),
         foreacharg(B1,B),
         foreacharg(C1,C) do
            C1 is A1 + B1
        ).

This predicate adds vectors with the functor interface_mib and returns such a vector.

5.5  Iteration on array

Description

The next concept is iteration on an array structure. We often want to perform some action on each element of a two-dimensional array.

Again, we present two implementations. The first uses nested foreacharg do loops to perform some operation q on each element of an array. The second uses nested for loops to iterate over all index combinations I and J. This second variant is more complex, and should be used only if we require the index values I and J as well as the matrix element X.

Parameters
Matrix
a matrix
Schema
/* version 1 */

:-mode iteration(+).
iteration(Matrix):-
        (foreacharg(Line,Matrix) do
            (foreacharg(X,Line) do
                q(X)
            )
        ).

/* version 2 */

:-mode iteration(+).
iteration(Matrix):-
        dim(Matrix,[N,M]),
        (for(I,1,N),
         param(M,Matrix) do
            (for(J,1,M),
             param(I,Matrix) do
                subscript(Matrix,[I,J],X),
                q(X,I,J)
            )
        ).
Comments

The dim predicate can not only be used to create arrays, but also to find the size of an existing array.

Note the strange way in which parameters M, I and Matrix are passed through the nested for loops with param arguments. But if we do not do this, then the variable Matrix outside and inside the do loop are unrelated.

Example

The example calls the predicate fill_empty/3 for each index combination of entries in a matrix PMatrix.

:-mode fill_rest_with_empty(+,+).
fill_rest_with_empty(N,PMatrix):-
        (for(I,1,N),
         param(PMatrix,N) do
            (for(J,1,N),
             param(PMatrix,I) do
                fill_empty(PMatrix,I,J)
            )
        ).

5.6  Transformation

Description

This next concept is used to perform some transformation on each element of a list and to create a list of the transformed elements. At the end, both lists will have the same length, and the elements match, i.e. the first element of the second list is the transformed first element of the first list.

This concept uses the foreach keyword in two different ways. The first is used to scan an existing list L, the second is used to construct a list K as the result of the operation.

Parameters
L
a list
K
a free variable, will be bound to a list
Schema
:-mode transformation(+,-).
transformation(L,K):-
        (foreach(X,L),
         foreach(Y,K) do
            q(X,Y)
        ).
Comments

In the code above we cannot see that list L is an input and list K is an output. This can only be deduced from the calling pattern or from the mode declaration.

Example

The example takes a list of router_mib_data terms and builds a list of temporary t/2 terms where the second argument consists of router_mib terms.

:-mode convert_to_router_mib(+,-,-).
convert_to_router_mib(L,K,Router):-
        (foreach(router_mib_data with 
                 [router:Router,
                  time:Time,
                  tcp_segm_in:A,
                  tcp_segm_out:B,
                  udp_datagram_in:C,
                  udp_datagram_out:D],L),
         foreach(t(Time,router_mib with 
                   [tcp_segm_in:A,
                   tcp_segm_out:B,
                   udp_datagram_in:C,
                   udp_datagram_out:D]),K),
         param(Router) do
            true
         ).

In this example the transformation is completely handled by matching arguments in the foreach statements. We use the predicate true for an empty loop body.

Figuring out what is happening with the variable Router is left as an exercise for the advanced reader.

5.7  Filter

Description

The filter concept extracts from a list of elements those that satisfy some condition q and returns a list of these elements.

We present three implementations, one using recursion, the others using a do loop with the fromto keyword.

Parameters
L
a list
K
a free variable, will be bound to a list
Schema
/* version 1 */

:-mode filter(+,-).
filter([],[]).
filter([A|A1],[A|B1]):-
        q(A),
        !,
        filter(A1,B1).
filter([_A|A1],B1):-
        filter(A1,B1).

/* version 2 */

:-mode filter(+,-).
filter(L,K):-
        (foreach(X,L),
         fromto([],In,Out,K) do
            q(X,In,Out)
        ).

q(X,L,[X|L]):-
        q(X),
        !.
q(_,L,L).
/* version 3 */

:-mode filter(+,-).
filter(L,K):-
        (foreach(X,L),
         fromto(K,In,Out,[]) do
            q(X,In,Out)
        ).

q(X,[X|L],L):-
        q(X),
        !.
q(_,L,L).
Comments

The difference between versions 2 and 3 lies in the order of the elements in the result list. Version 2 produces the elements in the inverse order of version 1, whereas version 3 produces them in the same order as version 1. This shows that the fromto statement can be used to build lists forwards or backwards. Please note that the predicate q/3 is also different in variants 2 and 3.

The cuts (!) in the program clauses are very important, as they remove the possibility that a selected element is not included in the filtered list. If we remove the cuts, then the filter predicate has an exponential number of “solutions”. Only the first solution will be correct, on backtracking we will decide to reject elements which satisfy the test criterion and we will explore all combinations until we reach the empty list as the last “solution”.

Example

The following program is used to extract interfaces related to customers (types customer, selected and remaining) as a list of customer/3 terms, group them by node and perform some action on each group.

:-mode selected_min_max(+,+).
selected_min_max(Type,Interfaces):-
        Interfaces = interfaces with list:List,
        (foreach(Interface,List),
         fromto([],In,Out,Customers) do
            selected_customer(Interface,In,Out)
        ),
        sort(0,=<,Customers,Sorted),
        customers_by_node(Sorted,Grouped),
        selected_together(Type,Grouped,Interfaces).

selected_customer(interface with [type:Type,
                                  index:I,
                                  node_index:Node],
                  In,
                  [customer with [node:Node,
                                  index:I,
                                  type:Type]|In]):-
        memberchk(Type,[customer,selected,remaining]),
        !.
% all other types: backbone,backbone_net,interconnection,local
selected_customer(_,In,In).

5.8  Combine

Description

This concept takes a list, combines consecutive elements according to some criterion and returns a list of the combined elements.

The typical use of this concept will first sort the input list so that elements that can be combined are consecutive in the list.

Parameters
L
a list
Res
a free variable, will be bound to a list
Schema
:-mode combine(+,-).
combine([],[]).
combine([A,B|R],Res):-
        can_combine(A,B,C),
        !,
        combine([C|R],Res).
combine([A|A1],[A|Res]):-
        combine(A1,Res).
Comments

It is important to note that the recursive call in the second clause continues with the combined element C, since it may be combined with more elements of the rest of the list R.

The cut in the second clause ensures that elements that can be combined are always combined, and that we do not leave a choice point in the execution.

The most simple use of the concept is the removal of duplicate entries in a sorted list.

Example

:-mode combine_traffic(+,-).
combine_traffic([],[]).
combine_traffic([A,B|R],L):-
        try_to_combine(A,B,C),
        !,
        combine_traffic([C|R],L).
combine_traffic([A|R],[A|S]):-
        combine_traffic(R,S).

try_to_combine(interface_traffic_sample(Time,Router,Interface,
                                        X1,X2,X3,X4,X5,
                                        X6,X7,X8,X9,X10),
        interface_traffic_sample(Time,Router,Interface,
                                 Y1,Y2,Y3,Y4,Y5,
                                 Y6,Y7,Y8,Y9,Y10),
        interface_traffic_sample(Time,Router,Interface,
                                 Z1,Z2,Z3,Z4,Z5,
                                 Z6,Z7,Z8,Z9,Z10)):-
        Z1 is X1+Y1,
        Z2 is X2+Y2,
        Z3 is X3+Y3,
        Z4 is X4+Y4,
        Z5 is X5+Y5,
        Z6 is X6+Y6,
        Z7 is X7+Y7,
        Z8 is X8+Y8,
        Z9 is X9+Y9,
        Z10 is X10+Y10.

Here we combine traffic samples for the same interface and time point by adding the sample values X1 ... X10 and Y1 ... Y10. The predicate try_to_combine will only succeed if the two input arguments have the same time stamp, router and interface, but it will fail if the arguments differ on these fields.

Also note that we do not use named structures in this example. This is justified as any extension of the structure would probably entail a change of the program anyway.

5.9  Minimum

Description

This concept selects the smallest element of a list according to some comparison operator better.

Parameters
L
a list
V
a free variable, will be bound to an entry of L
Schema
:-mode minimum(+,-).
minimum([H|T],V):-
        (foreach(X,T),
         fromto(H,In,Out,V) do
            minimum_step(X,In,Out)
        ).

minimum_step(X,Old,X):-
        better(X,Old),
        !.
minimum_step(X,Old,Old).
Comments

This implementation of minimum fails if the input list has no elements. This means that somewhere else in the program we have to handle the case where the input list is empty. This seems to be the most clear definition of minimum, an empty list does not have a smallest element.

If several elements of the list have the same minimal value, only the first one is returned.

5.10  Best and rest

Description

This concept is an extension of the minimum concept. It not only returns the best element in the input list, but also the rest of the original list without the best element. This rest can then be used for example to select another element, and so on.

Parameters
L
a list
Best
a free variable, will be bound to an entry of L
Rest
a free variable, will be bound to a list of the entries of L without Best
Schema
:-mode best_and_rest(+,-,-).
best_and_rest([H|T],Best,Rest):-
        (foreach(X,T),
         fromto(H,In1,Out1,Best),
         fromto([],In2,Out2,Rest) do
            best(X,In1,Out1,In2,Out2)
        ).

best(X,Y,X,L,[Y|L]):-
        better(X,Y),
        !.
best(X,Y,Y,L,[X|L]).
Comments

The predicate fails if the input list is empty. We must handle that case somewhere else in the program.

If several elements of the list have the same best value, only the first one is selected.

The order of elements in Rest may be quite different from the order in the input list. If that is not acceptable, we must use a different implementation. A rather clever one is given below:

best_and_rest([First|Xs],Best,Rest):-
        (foreach(X,Xs),
         fromto(First,BestSoFar,NextBest,Best),
         fromto(Start,Rest1,Rest2,[]),
         fromto(Start,Head1,Head2,Gap),
         fromto(Rest,Tail1,Tail2,Gap) do
            (better(X,BestSoFar) ->
                NextBest = X,
                Tail1 = [BestSoFar|Head1],
                Tail2 = Rest1,
                Head2 = Rest2
            ;
                NextBest = BestSoFar,
                Tail2 = Tail1,
                Head2 = Head1,
                Rest1 = [X|Rest2]
            )
        ).

5.11  Sum

Description

The sum concept returns the sum of values which have been extracted from a list of data structures. It uses a foreach to scan each elements of the list and a fromto to accumulate the total sum.

Parameters
L
a list
Sum
a free variable, will be bound to a value
Schema
:-mode sum(+,-).
sum(L,Sum):-
        (foreach(X,L),
         fromto(0,In,Out,Sum) do
            q(X,V),
            Out is In+V
        ).
Comments

The initial value for the sum accumulator here is 0. We could use another initial value, this can be useful if we want to obtain the total over several summations.

Example

The program counts how many entries in the interface_mib_data list refer to active interfaces (octet count non-zero).

:-mode non_zero_measurements(+,-).
non_zero_measurements(L,N):-
        (foreach(X,L),
         fromto(0,In,Out,N) do
            non_zero_measurement(X,In,Out)
        ).

non_zero_measurement(interface_mib_data with [octet_in:A,
                                              octet_out:B],
                     In,Out):-
        A+B > 0,
        !,
        Out is In+1.
non_zero_measurement(_X,In,In).

5.12  Merge

Description

The merge concept is used when we want to match corresponding entries in two lists. We sort both lists on the same key, and then scan them in parallel, always discarding the entry with the smallest key first.

We can use this concept to combine information from the two lists, to find differences between lists quickly, or to lookup information from the second list for all elements of the first list.

Parameters
L
a list
K
a list
Schema
:-mode merge(+,+).
merge(L,K):-
        sort_on_key(L,L1),
        sort_on_key(K,K1),
        merge_lp(L1,K1).

merge_lp([],_):-
        !.
merge_lp([_|_],[]):-
        !.
merge_lp([A|A1],[B|B1]):-
        merge_compare(A,B,Op),
        merge_cont(Op,A,A1,B,B1).

merge_cont(<,A,A1,B,B1):-
        merge_lp(A1,[B|B1]).
merge_cont(=,A,A1,B,B1):-
        merge_op(A,B),
        merge_lp(A1,[B|B1]).
merge_cont(>,A,A1,B,B1):-
        merge_lp([A|A1],B1).
Comments

The cuts in merge_lp are used to remove choicepoints left by the compiler1.

The schema looks quite complex, but its performance is nearly always significantly better than a simple lookup in the second list.

Example

The example takes data from two different sources and merges it. The first argument is a list of interface_topology terms, the second a list of ndi_interface structures. For matching NodeInterface pairs, we copy information from the first structure into the second. If the NodeInterface pairs do not match, then we don’t do anything.

Also note the use of compare/3 to obtain a lexicographical ordering of NodeInterface pairs.

:-mode insert_topology(+,+).
insert_topology([],_):-
        !.
insert_topology([_|_],[]):-
        !.
insert_topology([A|A1],[B|B1]):-
        compare_index_interface(A,B,Op),
        insert_topology_op(Op,A,B,A1,B1).

compare_index_interface(interface_topology(_,Router1,
                                           Index1,_,_),
                  ndi_interface with [router:Router2,
                                      index:Index2],Op):-
        compare(Op,Router1-Index1,Router2-Index2).

insert_topology_op(<,A,B,A1,B1):-
        insert_topology(A1,[B|B1]).
insert_topology_op(=,A,B,A1,B1):-
        insert_one_topology(A,B),
        insert_topology(A1,B1).
insert_topology_op(>,A,_B,A1,B1):-
        insert_topology([A|A1],B1).

insert_one_topology(interface_topology(_,_,_,Ip,Mask),
                    ndi_interface with [ip_address:Ip,
                                    subnet_mask:Mask,
                                    subnet:Subnet]):-
        subnet(Ip,Mask,Subnet).        

5.13  Group

Description

This concept takes a sorted list of items and creates a list of lists, where items with the same key are put in the same sub-list. This works even for the empty input list.

The second argument of group_lp serves as an accumulator to collect items with the same key. As long as the next item uses the same key, it is put into this accumulator (2nd clause). If the remaining list is empty (1st clause) or it starts with an element of a different key (3rd clause), the accumulated list is put into the output list.

Parameters
L
a list
K
a free variable, will be bound to a list
Schema
:-mode group(+,-).
group([],[]).
group([H|T],K):-
        group_lp(T,[H],K).

group_lp([],L,[L]).
group_lp([H|T],[A|A1],K):-
        same_group(H,A),
        !,
        group_lp(T,[H,A|A1],K).
group_lp([H|T],L,[L|K]):-
        group_lp(T,[H],K).
Comments

The order of items in the resulting sub lists is the reverse of their order in the initial list.

The order of the sub lists in the result is the same as the order of the keys in the original list.

If the initial list is not sorted by the same key that is used in same_group, then this program does not work at all.

Example

The following program takes a list of terms and groups them according to some argument number N. It returns a list of group/2 terms, where the first argument is the common key in the group, and the second argument is a list of all terms which share that key.

:-mode group(+,+,-).
group([],_,[]):-
        !.
group(Terms,N,Grouped):-
        sort(N,=<,Terms,[H|T]),
        arg(N,H,Group),
        group1(T,Group,[H],N,Grouped).

group1([],Group,L,_,[group(Group,L)]).
group1([H|T],Group,L,N,Grouped):-
        arg(N,H,Group),
        !,
        group1(T,Group,[H|L],N,Grouped).
group1([H|T],Old,L,N,[group(Old,L)|Grouped]):-
        arg(N,H,Group),
        group1(T,Group,[H],N,Grouped).

5.14  Lookup

Description

The lookup concept is used to convert data stored in the local database into a list of terms that can be manipulated in the program. The most natural template (first argument of findall) is to use the same term as for the facts in the database.

Parameters
Res
a free variable, will be bound to a list
Schema
:-mode lookup(-).
lookup(Res):-
        findall(q(X),q(X),Res).
Comments

findall examplifies a typical meta-predicate, the second argument is actually a goal that will be executed. There are a number of other predicates of this type, and this feature can be extremely useful in writing interpreters, emulators etc, which treat data as program parts.

The findall predicate is significantly faster than bagof or setof. Their use is not recommended.

Example

% find all hops routing information
:-mode gather_hops(-).
gather_hops(Hops):-
        findall(hop(A,B,C),hop(A,B,C),Hops).

5.15  Fill matrix

Description

This concept takes a list of entries with indices I and J and a value V, and put the value in a matrix M at position Mi,j.

Parameters
L
a list of entries
Matrix
a matrix
Schema
:-mode fill_matrix(+,+).
fill_matrix(L,Matrix):-
        (foreach(entry with [i:I,j:J,value:V],L),
         param(Matrix) do
            subscript(Matrix,[I,J],V)
        ).
Comments

The program may fail if two entries in the list refer to the same index pair I and J, as the program would then try to insert two values at the same position.

It is not required that the input list contains all index combinations, we can use the iteration on array concept to fill any un-set elements with a default value.

Example

The example fills an array PMatrix with values from a list of hop/3 terms. We also convert the node names in the hop term into node indices for lookup in the PMatrix matrix.

:-mode fill_with_hops(+,+,+).
fill_with_hops([],_,_).
fill_with_hops([hop(Source,Dest,List)|R],Nodes,PMatrix):-
        find_node_index(Source,Nodes,S),
        find_node_index(Dest,Nodes,D),
        find_node_indices(List,Nodes,L),
        length(L,N), 
        subscript(PMatrix,[S,D],pi_entry with [list:L,
                                               length:N]),
        fill_with_hops(R,Nodes,PMatrix).

5.16  Cartesian

Description

This concept takes two input lists L and K and creates a list of pairs Res, in which each combination of elements of the first and the second list occurs exactly once.

The result is a list of terms pair(X, Y), where X is an element of list L and Y is an element of list K.

The implementation uses nested foreach do loops to create each combination of elements once. The fromto accumulators are used to collect the result list.

Parameters
L
a list
K
a list
Res
a free variable, will be bound to a list
Schema
:-mode cartesian(+,+,-).
cartesian(L,K,Res):-
        (foreach(X,L),
         fromto([],In,Out,Res),
         param(K) do
            (foreach(Y,K),
             fromto(In,In1,[pair(X,Y)|In1],Out),
             param(X) do
                true
            )
        ).
Comments

Note the use of an empty body (true) in the innermost loop. All calculations are done by parameter passing alone.

If we want to create the elements in the same order as the elements in the input list, we have to exchange input and output arguments of the fromto statements, like so:

:-mode cartesian(+,+,-).
cartesian(L,K,Res):-
        (foreach(X,L),
         fromto(Res,In,Out,[]),
         param(K) do
            (foreach(Y,K),
             fromto(In,[pair(X,Y)|In1],In1,Out),
             param(X) do
                true
            )
        ).
Example

The example builds all pairs of sources and sink nodes for flows and creates contribution structures from them. An additional accumulator NoPath is used to collect cases where there is no route between the nodes.

:-mode create_contribution(+,+,+,-,-).
create_contribution(FromList,ToList,
                    PMatrix,Contribution,NoPath):-
        (foreach(From,FromList),
         fromto([],In1,Out1,Contribution),
         fromto([],NP1,NP2,NoPath),
         param(ToList,PMatrix) do
            (foreach(To,ToList),
             fromto(In1,In,Out,Out1),
             fromto(NP1,NoPath1,NoPath2,NP2),
             param(From,PMatrix) do
                contribution(From,To,From,To,1,PMatrix,
                             In,Out,NoPath1,NoPath2)
            )
        ).

5.17  Ordered pairs

Description

This concept creates ordered pairs of entries from a list. Each combination where the first element occurs in the input list before the second element is created exactly once.

The result is a list of terms pair(X, Y) where X and Y are elements of the input list L.

Parameters
L
a list
K
a free variable, will be bound to a list
Schema
:-mode ordered_pairs(+,-).
ordered_pairs(L,K):-
        ordered_pairs_lp(L,[],K).

ordered_pairs_lp([],L,L).
ordered_pairs_lp([H|T],In,Out):-
        ordered_pairs_lp2(H,T,In,In1),
        ordered_pairs_lp(T,In1,Out).

ordered_pairs_lp2(H,[],L,L).
ordered_pairs_lp2(H,[A|A1],In,Out):-
        ordered_pairs_lp2(H,A1,[pair(H,A)|In],Out).
Comments

The second and third argument of ordered_pairs_lp and the third and fourth argument of ordered_pairs_lp2 serve as an accumulator to collect the results.

This concept can also be implemented with nested do loops. The recursive version seems more natural.

ordered_pairs(L,K):-
        (fromto(L,[El|Rest],Rest,[_]),
         fromto(K,TPairs,RPairs,[]) do
            (foreach(R,Rest),
             param(El),
             fromto(TPairs,[pair(El,R)|Pairs],Pairs,RPairs) do
                true
            )
        ).

1
As ECLiPSe only uses indexing on a single argument, the compiler cannot recognize that the clause patterns are exclusive.

Previous Up Next