[comp.lang.prolog] Triangle Puzzle

ok@quintus.UUCP (Richard A. O'Keefe) (02/15/88)

To follow up my "review" of "Prolog Programming in Depth",
I thought I'd take one of their examples and show how to
revise it, making it cleaner & faster & so on.  The one
I picked was "TRIANGLE.PRO", pp 234-237.  I got 1/3rd of
the way through typing it in, and found it too painful to
continue.  Has anyone got a machine-readable version of
this program they could send me?  They report that the
Arity Prolog *interpreter* takes "a little over a minute",
but this doesn't mean a great deal, especially as there
appear to be two typos in the jump/3 table.  For what
it's worth:
	jump(5,8,13).	should be jump(5,8,12).
and
	jump(13,21,11).	should be jump(13,12,11).
My version in compiled Quintus Prolog on a SUN-3/50 takes
0.75 seconds, but this doesn't mean much.

ok@quintus.UUCP (Richard A. O'Keefe) (02/15/88)

I might as well tell you what the interesting thing is about the
Triangle Puzzle program.  The puzzle is that you have a triangle
with holes for pegs in it, and 15 pegs.  The board looks like
			A
		      B   C
		    D   E   F
		  G   H   I   J
	        K   L   M   N   O
You start by removing any one of the pegs.  From then on a move
is to hop a peg over another peg into a hole, removing the peg
you hopped over:  (Peg)--(Peg)--(Hole) -> (Hole)--(Hole)--(Peg).
The goal is to remove all but one peg.

"Prolog Programming in Depth" contains the following predicate:

	legal_jump(OldBoard, NewBoard) :-
		peg(X, OldBoard),
		jump(X, Y, Z),
		not peg(Z, OldBoard),
		peg(Y, OldBoard),
		set_peg(0, X, OldBoard, W1),
		set_peg(0, Y, W1, W2),
		set_peg(1, Z, W2, NewBoard).

where jump/3 is a table containing entries like

	jump(1 /* =A */, 2 /* =B */, 4 /* =D */).

peg/2 is a table containing entries like

	peg(4, [_,_,_,1,_,_,_,_,_,_,_,_,_,_,_]).

and set_peg/4 is a table containing entries like

	set_peg(X, 4, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O],
		      [A,B,C,X,E,F,G,H,I,J,K,L,M,N,O]

It is easy to work out that there are 36 clauses in jump/3,
15 clauses in peg/2, and 15 clauses in set_peg/4.

There are lots of things wrong with this, starting with the use of a
list to represent the board.  Covington et al describe set_peg/4 as
"a very efficient way" of updating the board.  It is hardly that; I
haven't even mentioned the second thing wrong with it.  But one thing
really draws smashes its fist into the eye:  that 'not'.

Now, the program is such that when 'not peg(Z, OldBoard)' is called,
both Z and OldBoard are ground, and peg/2 is a base relation, so the
negation is sound.  That's not the problem.  The problem is that it
doesn't mean quite what you think it does.  Remember that we are
looking for the pattern (X:peg)--(Y:peg)--(Z:hole), where Covington
et al have chosen to represent "peg" by 1 and "hole" by 0 (that's
not such a wonderful idea itself, by the way).  What we want to
know is that there is a hole at Z.  'not peg(Z, OldBoard)' doesn't
mean that.  It means "it is not the case that there is a peg at Z
in OldBoard."  There are several ways it might succeed:
 o OldBoard might not be a list of 15 elements
 o Z might not be a position in the board
 o there might be something there other than a peg or a hole.
Isn't this nit-picking?  Well, when you consider that there is a typo
("21" for "12") in the jump/3 table, the possibility that Z might be
out of range is not so remote...

What's a clean way to do this?  Well, if we want to know whether there
is a hole at position Z, THAT's the thing to ask!  What should be done
is something like

	legal_jump(OldBoard, NewBoard) :-
		in_board(X, OldBoard, 1 /* peg */),
		jump(X, Y, Z),
		in_board(Z, OldBoard, 0 /* hole */),
		in_board(Y, OldBoard, 1 /* peg */),
		...

where in_board/3 is a table of clauses like

	in_board(4, [_,_,_,X,_,_,_,_,_,_,_,_,_,_,_], X).

But it's a bit of a pain to test the positions of the board one at
a time.  Why not just write patterns to match the possible jumps?
And again, the intermediate lists with the extremely odd names W1
and W2 are of no interest whatsoever.  What we want to know is the
effect of a particular jump on the board.  Pushing this to the
limit of cleanliness, I came up with

	legal_jump(OldBoard, NewBoard) :-
		jump(_, OldBoard, NewBoard).

where jump/3 was now a table of facts like

jump( 5, 	f(		A,
			      B,  +,
			    D,  +,  F,
			  G,  -,  I,  J,
		        K,  L,  M,  N,  Q	),
		f(		A,
			      B,  -,
			    D,  -,  F,
			  G,  +,  I,  J,
		        K,  L,  M,  N,  Q	)).

This looks like a lot more work to write than the Covington et al
version.  In fact it is less work.  To start with, we have replaced
36+30+30 = 66 clauses by 36.  Each clause of the new jump/3 is about
as complex as a clause of set_peg/3, which may be clearer if it is
written as

jump(5, f(A,B,+,D,+,F,G,-,I,J,K,L,M,N,Q),
        f(A,B,-,D,-,F,G,+,I,J,K,L,M,N,Q)).

I want to stress this, because at first blush just writing down the
legal jumps like this looks like cheating.  But the original jump/3
table was no less a table of jumps; I have merely chosen a more
natural coding than triples of integers.

Making the table was easy.  I typed one copy of the triangle into an
editor, made a second copy of it, and put the jump(xx,) wrapper around
it.  I made 36 copies of the resulting clause, and zipped through
drawing in the peg- present (+) and peg-absent (-) marks.  The "5" here
was an arbitrary label for the move.  I never once had to count things;
all I had to be able to do was see straight lines.  I am sure that
Covington et al proof-read their book carefully; I attribute the two
typos in their jump/3 table to the fact that their representation was
peculiarly hard to check.


There was another interesting point in the Covington et al program.
The top level of their program looks roughly like this:

triangle(N) :-
	make_first_board(N, FirstBoard),
	triangle_solver(14, [FirstBoard], Solution),
	fast_reverse(Solution, ReversedSolution),
	show_triangle(ReversedSolution).

triangle_solver(1, Solution, Solution).
triangle_solver(N, [OldBoard|PastBoards], Solution) :-
	legal_jump(OldBoard, NewBoard),
	M is N-1,
	triangle_solver(M, [NewBoard,OldBoard|PastBoards], Solution).

The predicate they call "fast_reverse/2" is in fact the usual
implementation of reverse/2 using accumulator passing.  It is a pity
that they gave it a name which make it look exceptional, instead of
being the only reverse one ever uses except in the NREV benchmark...
But why bother reversing the list at all?  Why not build it in the
right order from the start?

triangle(N) :-
	make_first_board(N, FirstBoard),
	triangle(14, FirstBoard, Solution),
	show_triangle(Solution).

triangle(1, LastBoard, [LastBoard]).
triangle(N, OldBoard, [OldBoard|FutureBoards]) :-
	legal_jump(OldBoard, NewBoard),
	M is N-1,
	triangle(M, NewBoard, FutureBoards).

The name "show_triangle/1" is unfortunate, as it does nothing of the
sort.  It prints a solution, which is a list of triangles.  A good
name would have been "print_solution/1".  As it is, the command which
*does* print a triangle had to be called "show_board/1".

There are a lot of other things I am unhappy with in the original
code, but I think that's enough for one message.  The basic problem
seems to be that the authors are still thinking in Pascal/C/Lisp terms.
For example, they appear to conceive legal_jump/2 as "finding a legal
jump and constructing a new board" rather than as an entirely static
relation between two boards.  This is an important point.  If you
think of legal_jump/2 as a static relation (not unlike a boolean
matrix), you might think of taking relational products.  For example,
it turns out that there are
	   882 solutions to jump(_,A,B) & jump(_,B,C)
	14,712 solutions to jump(_,A,B) & jump(_,C,D)
Now 882/(36*36) = 0.68+, and 14,712/(36*36*36) = 0.315+, which suggests
another approach to the problem:  we are asking about
	jump*jump*...*jump*jump*jump
and we could well try bracketing it as
	(jump*jump*jump)*...*(jump*jump)
instead.  I don't know whether this is a good idea for this particular
problem or not.  But at least thinking of a relation as something like
a boolean matrix lets me come up with such ideas; somehow one never
thinks of taking products of Pascal procedures...

The book is not bad value, nevertheless.

bimbart@kulcs.uucp (Bart Demoen) (02/24/88)

In news letter, we found a solution to the triangle problem, to which we will
refer as the ......program: not naming the author nor the company he works for,
is not out of maliciousness, rather because the not mentioned author refuses
systematically to name BIMprolog when naming other prolog implementations.

During a coffee break (no, if you think ......program stands for KOffeeprogram,
your are wrong, yes you are :-), we asked ourselves 2 questions:

1. how easy is it to write a program that is faster than the ......program and
   still readable
2. how relevant is the figure 0.75 quoted for finding the first solution
   (to be honest: ...... himself says that this figure 'doesn't mean much')


Before we looked at the ......program, we wrote our own, which we will refer to
as the BIMprogram. 


Our findings are summarized in the following table: there are 15 possible
starting positions, numbered from 1 to 15, as in the triangle below:

                        1
                      2   3
                    4   5   6
                  7   8   9   10
                11  12  13  14  15


The figures mentioned in the column under BIMprogram and ......program,
represent the cputime in seconds needed to find the first solution.


start position		BIMprogram		......program
--------------		----------		-------------
 1			 0.500000		 0.660000
 2			 9.780001		12.740001
 3			42.760002		55.980000
 4			 0.539997		 0.680000
 5			25.719997		33.900002
 6			 0.059998		 0.080002
 7			 0.520004		 0.659996
 8			18.820000		24.659996
 9			10.680000		14.000000
10			 0.519997		 0.660004
11			 9.779999		12.779999
12			32.980003		43.180008
13			 0.520004		 0.659988
14			32.660004		42.800003
15			10.300003		14.079987

4 conclusions:

1. the BIMprogram is systematically about 30% faster than the ......program
2. the figure 0.75 is absolutely no indication of the quality
   of the prolog program or the prolog implementation: the order of the facts
   (or rules) for 'jump' is the most important factor determining the time
   needed to find the (a !) first solution
3. the BIMprogram is really a partially evaluated version of the ......program,
   but not at all less readable ...
   just to give you the flavour:
   
   the 12th startposition is represented by:
   
   	start(12,1,1,1,1,1,1,1,1,1,1,1,0,1,1,1).


   and the 'jump' facts are replaced by rules:
   
   jump(_A,1,_C,_D,1,_F,_G,_H,0,_J,_K,_L,_M,_N,_O,['2 to 9'|_restjumps],_n) :-
        _m is _n - 1,
        jump(_A,0,_C,_D,0,_F,_G,_H,1,_J,_K,_L,_M,_N,_O,_restjumps,_m) .


   the stop condition is :
   
   jump(_A,_B,_C,_D,_E,_F,_G,_H,_I,_J,_K,_L,_M,_N,_O,[],1) .

	/*put at the end and not first, although it is a simple case*/

   and the query to get the first solution from starting position 12 is:
   
   ?- start(12,_A,_B,_C,_D,_E,_F,_G,_H,_I,_J,_K,_L,_M,_N,_O,_s),
        jump(_A,_B,_C,_D,_E,_F,_G,_H,_I,_J,_K,_L,_M,_N,_O,_jumplist,14) ,
        write(_jumplist) .

4. why is the BIMprogram faster ?

   less ALLOCATE's
   no creation on the heap of new structures; no UNIFY's
   a lot of optimised away GET_'s and PUT_'s
   
   the disadvantage of having longer choicepoints does not outweight the above
   advantages
   
   moreover, a lot less heap and local stack are used !


bimbart@kulcs.uucp		andre@sunbim
Bart Demoen			Andre Marien
Dept. of Computer Science	BIM
Celestijnenlaan 200A		Kwikstraat 4
B-3030 Leuven			B-3078 Everberg
Belgium				Belgium

ok@quintus.UUCP (Richard A. O'Keefe) (02/26/88)

In article <1153@kulcs.UUCP>, bimbart@kulcs.uucp (Bart Demoen) writes:
> In news letter, we found a solution to the triangle problem, to which we will
> refer as the ......program: not naming the author nor the company he works for,
> is not out of maliciousness, rather because the not mentioned author refuses
> systematically to name BIMprolog when naming other prolog implementations.

Do you get the idea that he might be talking about me?  I did.
News for you, playmate:  I don't name BIM Prolog because I haven't
anything to say about it.  I have had some nasty things to say about
various Prolog implementations in this newsgroup, and to avoid legal
trouble, have avoided naming names.  If the people at BIM thought it was
their implementation which I have been criticising all along, I can only
say that I regret that they found this credible.  Here is my personal
assurance:  I do not recall intending to criticise BIM Prolog or its
implementors in this newsgroup in the last year.  If I have something
good to say about BIM Prolog, I shall certainly name it!

> 1. how easy is it to write a program that is faster than the ......program and
>    still readable

Readability is to some extent in the eye of the beholder.
I find something like this

>    jump(_A,1,_C,_D,1,_F,_G,_H,0,_J,_K,_L,_M,_N,_O,['2 to 9'|_restjumps],_n) :-
>         _m is _n - 1,
>         jump(_A,0,_C,_D,0,_F,_G,_H,1,_J,_K,_L,_M,_N,_O,_restjumps,_m) .

about as readable as a hex dump, whereas the same thing expressed as

jump(			A,
		      1,  C,
		    D,  1,  F,
		  G,  H,  0,  J,
		K,  L,  M,  N,  O,	['2 to 9'|Jumps], Count0) :-
	Count is Count0-1,
	jump(		A,
		      0,  C,
		    D,  0,  F,
		  G,  H,  1,  J,
		K,  L,  M,  N,  O,	Jumps, Count).

conveys quite clearly what is going on.  The triangular layout is
specific to this particular problem:  it is important to be able 
to SEE the jump (look for a line of numbers) so that you can check it.
The human eye is reasonably good at detecting straight lines; it is
not so good at seeing the same pattern in the flattened layout Demoen
(and Covington et al) used.  This is in fact the best example I have
ever seen to prove that a rigid layout style (such as I normally
advocate) is not always a good idea.

Why didn't I do this in the first place?  As Bart Demoen says:

> 3. the BIMprogram is really a partially evaluated version of the ......
>    program ...

Quite right.  However, the Covington et al book appears to be aimed at
micro-computer users.  (Special attention is given to Arity Prolog and
Turbo Prolog.)  One of the nicer Prologs on micro-computers is ALS Prolog,
which had a limit of 14 or 15 arguments to a predicate the last time I
looked.  The partially executed version has 17 arguments.  I would look
remarkably silly advising Covington et al's readers to do something
they COULDN'T do, wouldn't I?  (I assume that many readers of this
newsgroup are trying to use Prolog on PCs.  I think it's fair enough
for me to suggest things that I know will work in one affordable PC Prolog.)

> 1. the BIMprogram is systematically about 30% faster than the ......program

I'm not surprised that the improvement is so slight.  I have often found that
it wasn't worth the bother of unpacking a record.  This is about as good as
it gets.

> 2. the figure 0.75 is absolutely no indication of the quality
>    of the prolog program or the prolog implementation: the order of the facts
>    (or rules) for 'jump' is the most important factor determining the time
>    needed to find the (a !) first solution

Wrong.  It is correct that the order of the facts in the jump table is the
most significant thing.  That's why in my version of the program I was
careful to use exactly the same order of jump facts as Covington et al did.
I went through a back-of-an-envelope proof that my program searched the
same tree as theirs in the same order.  With that held constant, the time
IS an indication of the quality.  For example, Demoen's unfolded version
IS 30% faster than my version, and that DOES mean something.

> 4. why is the BIMprogram faster ?
> 
>    less ALLOCATE's
>    no creation on the heap of new structures; no UNIFY's
>    a lot of optimised away GET_'s and PUT_'s
>    
>    the disadvantage of having longer choicepoints does not outweigh the above
>    advantages
>    
>    moreover, a lot less heap and local stack are used !
> 

We can put it in less implementation-oriented terms.
The version that looked like
	driver(...) :- ...
	driver(...) :- jump(...), driver(...)

	jump(#, f(...), f(...)).
did three things at every step that Demoen's program doesn't.

(1) There was an extra procedure call driver->jump.
    The "clausal join" of driver with jump avoids this.
    This I take the "less ALLOCATEs" to mean.

(2) jump had to unpack the first f().  The joined version doesn't.
    This is the "no UNIFYs" bit.

(3) jump had to pack the second f() back together.  The joined
    version doesn't.  This is the "no creation on the heap" bit.

These are general features of this kind of unfolding.

There is another point.  I explicitly wanted to represent jumping
as a relation between two states.  With my program, it was possible
for me to ask questions like
    "how many solutions of jump(_,X,Y), jump(_,Y,Z) are there?"
    "how many solutions of jump(_,X,Y), jump(_,Y,Z), jump(_,Z,W)?"
It seemed plausible that it might be profitable to precompute a table
of two-step jumps and then search two jumps at a time.  It would also
be possible to make a table of *final* states and work backwards from
it, producing a table of all the states 3 (say) steps from the end.
One could then switch over to that table at the end.

This kind of change is also a form of partial execution.  The kind of
partial execution exemplified by Bart Demoen's program buys you a
constant factor (30% is not to be sneezed at), but that's all.  Doing
computations like double-stepping and backwards analysis from can buy
you an exponential speedup in some problems.  One of the things I was
trying to get across in my message about the triangle program (apart
from things like the importance of layout in making it easier to check
ones tables...) was this point about making more of a program
declarative so that this sort of "high-leverage" partial execution can
be done.

voda@ubc-cs (Paul Voda) (03/01/88)

This contribution was inspired by the recent discussion of the
Triangle Puzzle by Richard O'Keefe.

A wide class of problems, the triangle puzzle is one of them
(see below), calls for a natural solution in the form of a
sequence of complex data structures describing the successive states
of the problem being solved by a series of steps.

The general situation is as follows:

  Problem(initparams,Solution) <-
    Initialstate(initparams,State),
    Path(params,State,Solution).

  Path(params,State,[]) <-
    Endstate(params,State).
  Path(params,Oldstate,[onestep,Tail]) <-
    Onestep(params,Oldstate,Newstate),
    Path(params,Newstate,Tail).

Basically we deal with a class of graph traversal problems.
The adjacent nodes are described by the predicate "Onestep".
The states of the problem are usually described by complex lists which
are copied over and over with only slight changes. A state for the
triangle puzzle was given by a description of the board giving the
empty and occupied holes.

The declarative languages (Prolog and Lisp)
are clearly at disadvantage for two reasons:

 i) the new state must be obtained from the old one by creating
    a fresh copy of the old state.

 ii) A state must be described by a complicated list even if the problem
     naturally calls for arrays.

The solution of such a problem in a procedural language will modify the
state data structure in place. Clever Prolog programmers have discovered
long ago that certain degree of in-place-modification can be obtained
directly in Prolog by the employment of the "var" predicate. There is
only one list describing a state. The list consists initially of
unbound variables. As the solution progresses the unbound variables
are bound to values describing the new states. If a part of the state,
usually denoting a "not visited" situation, is
found unbound by a call to the "var" predicate, the part can be marked
by a value signifying the "visited" situation.

This technique applies only to such problems (maze traversal, tiling problems,
constraint satisfaction problems, etc.)
where the state changes exactly once for each of its parts.
I will mention here two examples, both of which appeared in the Prolog digest:
T. Evans's solution of the Cube Packing Problem and the Baage's solution
of the Christmas Puzzle. During the solution of the Triangle Puzzle
a hole in the board changes the state from occupied to empty and back many
times. This means that "var" cannot be used.

I would like to stress here that a logically clean solution of the Cube packing
and Christmas puzzles logically calls for the encoding of the situation by the
old state/new state technique.
Needless to say this would be terribly inefficient.
The reduction of the declarative Prolog to the procedural Pascal by the
use of "var" seems to be a lesser evil questioned only by the purists. 
The majority
of Prolog programmers grew up with the procedural languages and they simply
do not care about the logic. Ironically, quite often one hears
the same programmers to praise the declarative style
"of specifying only what and not how" just as they specify the "how"
by the use of "var" and "assert".

Is it possible to have both the cake and eat it?  The answer is yes
if one allows modifiable variables in a declarative setting.
A natural, and logically elegant, solution is to have the language
processor recognize the copying situation: the old state will
never be used after the new state has been obtained. The processor can reuse
the storage in such a case. There is a large amount of research going on
in this direction. The problem is a difficult one with no acceptable
solution in sight.

Alternatively, and admittedly as a slightly less elegant solution, one can
employ the declarative reading of procedural programs as proposed
by Rick Hehner and Tony Hoare. (See for instance the two 84 CACM papers
on the "Predicative Programming" by Hehner).
Certain arguments
can be designated as being 'input/output'. They will be modified in place
whereas logically they are a pair of arguments: one 'input' and one
'output'. For instance the following predicate

   Incr(x) iff x := x + 1

Is only an abbreviation for the predicate

   Incr(x_in,x_out) iff x_out = x_in + 1.

The formula

    x := 6 & Incr(x) & Incr(x) & P(x)

is only an abreviation for the formula

    x1 = 6 & Incr(x1,x2) & Incr(x2,x3) & P(x3)

Of course, only a madman would employ this style of programming
with short values such as integers, but with the list-typed arguments
the technique is certainly faster than copying and it is logically cleaner
than the use of the "var" predicate.

An implementation of reassignable variables calls for the specification
of modes for the arguments. I have employed this in the programming
language Trilogy. The arguments of Trilogy have four modes: 'input' (x:<T)
where the value x of type T is fully known upon the predicate call,
'output' (x:>T) where the argument x obtains a full value before the
predicate call is exited,
'input/output' (x:.T) which is logically a pair of variables, and finally
the 'symbolic' or 'logical' mode (x::T) where x is specified by constraints
(of which "no constraint" yields the "unbound" variable).

Following is the implementation of the Triangle Puzzle in Trilogy.
I briefly explain the constructs employed after the text of the program.

{   TRIANGLE PUZZLE IN TRILOGY }
{  Triangle Puzzle: A triangle-shaped board has 15 holes numbered
   0 to 14. There is a peg in each hole. Remove arbitrary peg
   and perform 13 jumps by jumping with a peg over another peg
   into a hole and removing the peg jumped over.
   At the end there will be only one peg on the board.

          0
        1   2
      3   4   5             the query:
    6   7   8   9              one Triangle(0,p)
  10 11   12  13  14        finds  a solution starting with the hole 0 empty
}

Hole = [0..14]      {Interval type describing the holes}
                    {Array type describing a state of the board:}
Board = Hole->I     { b(i) is 0 if i-th hole empty; 1 if there is a peg}

                    {Constant array of lists describing the legal jumps}
                    { "(o,t) in Jumprom(f)" holds if it is possible
                     to jump from the hole f over the hole o to the hole t}
Jumpfrom :< Hole->list (I,I) =
     [ ((1,3),(2,5),Nil),                       {from 0}
       ((3,6),(4,8),Nil),                       {from 1}
       ((4,7),(5,9),Nil),                       {from 2}
       ((1,0),(4,5),(7,12),(6,10),Nil),         {from 3}
       ((7,11),(8,13),Nil),                     {from 4}
       ((2,0),(4,3),(8,12),(9,14),Nil),         {from 5}
       ((3,1),(7,8),Nil),                       {from 6}
       ((4,2),(8,9),Nil),                       {from 7}
       ((7,6),(4,1),Nil),                       {from 8}
       ((8,7),(5,2),Nil),                       {from 9}
       ((6,3),(11,12),Nil),                     {from 10}
       ((7,4),(12,13),Nil),                     {from 11}
       ((11,10),(7,3),(8,5),(13,14),Nil),       {from 12}
       ((12,11),(8,4),Nil),                     {from 13}
       ((13,12),(9,5),Nil) ]                    {from 14}

pred Triangle(h:<Hole, p:>list(I,I,I)) iff
  { h is the starting hole and p solves the puzzle by giving a list
    of 13 triples of the form (from,over,to) }
  b:.Board & b := [1,1,1,1,1,1,1,1,1,1,1,1,1,1,1] & {all pegs in}
  b(h) := 0 &      {the starting hole is removed}
  Jumps(13,b,p)    {13 jumps are performed yielding p}

pred Jumps(i:<I, b:.Board, p:>list (I,I,I)) iff
  { i jumps given by p from the board in state b_in lead to b_out}
  if i > 0 then                    {there are jumps to be performed}
    b(from) = 1 &                  {from is a hole with a peg in it}
    (over,to) in Jumpfrom(from) &  {over,to is a jump from the hole from}
    b(over) = 1 & b(to) = 0 &      {the hole over contains a peg, to is empty}
    b(from) := 0 & b(over) := 0 & b(to) := 1 & {new situation on the board}
    Jumps(i-1,b,t) &               {t solves the puzzle from the board pos b}
    p = (from,over,to),t           {thus p is a solution for i-jumps}
  else                             {no jumps to be performed}
    p = Nil
  end

Explanation:

i) The variables of Trilogy start with small letters. Predicates,
  types and constants, being identified by proper names, are
  capitalized.

ii) "Hole" and "Board" are type declarations.
  Hole is an interval type whereas the type
    Board = Hole->I
  is an array (finite mapping) of integer values indexed by the holes.

iii) The constant array "Jumpfrom" of the type "Hole->list (I,I)"
  can be visualized as a set of indexed Prolog facts describing
  the possible jumps. The formula

      (over,to) in Jumpfrom(from)

  used in the predicate "Jumps" is to be read as follows: The
  array subscription "Jumpfrom(from)" denotes the list of possible
  jumps from the hole "from". Each element of the list is a pair
  "(over,to)" giving the jumped over and the destination holes.
  "in" is the infix list membership relation primitive in Trilogy.

  Thus the formula holds iff it is possible to jump from the hole "from"
  over the hole "over" to the hole "to".

iv) A state of the board is described by the 'input/output' array
    "b:.Board", where "b(i) = 1" if the i-th hole contains a peg,
    "b(i) = 0" otherwise.

v) A solution to the puzzle is found by the query

      one Triangle(0,p)

   which constructs the path "p" describing the solution of the
   puzzle as a list. The input argument "0" indicates that
   initially the hole zero is empty.
   The first solution is found on an 8MHz AT in 0.8 seconds as follows:

     p = (3,1,0),(5,4,3),(0,2,5),(6,3,1),(9,5,2),(11,7,4),(12,8,5),
         (1,4,8),(2,5,9),(14,9,5),(5,8,12),(13,12,11),(10,11,12),Nil

 vi) The predicate "Jumps" has an input/output argument "b" describing
   the states. It has the following declarative reading:

     Jumps(i,(b_in,b_out),p) holds iff the board b_out is obtained
     from the board b_in by performing i jumps given by the list p.

   The procedural reading is that given the number i and the state b
   the predicate will return the path p.

 vii) The reader will note that the arrays of Trilogy allow fast indexing
    as opposed to the list traversal of Prolog.

ok@quintus.UUCP (Richard A. O'Keefe) (03/02/88)

In article <1863@ubc-cs.UUCP>, voda@ubc-cs (Paul Voda) writes:
>  ii) A state must be described by a complicated list even if the problem
>      naturally calls for arrays.
Neither my program nor Bart Demoen's used a list to represent a state.
A compound term in Prolog, such as the f(_,_,_,_,_,_,_,_,_,_,_,_,_,_,_)
terms I used to represent states of the triangle puzzle, *is* an array;
the space required for such a term is no more than would be required for
an array with that many elements (+/- a small constant), and read access
to elements of such a data structure is constant time.

Yes, everyday Prolog does not have array *update*, but any competent Prolog
programmer would approximate updatable arrays by trees, not lists.

> This technique applies only to such problems (maze traversal, tiling problems,
> constraint satisfaction problems, etc.)
> where the state changes exactly once for each of its parts.
> I will mention here two examples, both of which appeared in the Prolog digest:
> T. Evans's solution of the Cube Packing Problem and the Baage's solution
That's Evan Tick, not Tick Evan.

> The formula
> 
>     x := 6 & Incr(x) & Incr(x) & P(x)
> 
> is only an abreviation for the formula
> 
>     x1 = 6 & Incr(x1,x2) & Incr(x2,x3) & P(x3)
> 
Interesting!  Please explain this some more.  If I write

	x := 6 & Incr(x) & y = x & Incr(x) & P(x)

which version of x does y get?  (The answer should be obvious, but I'd like
to see how it's done.)  What if we have some larger structure, and I do

	x := NewThing & Update(x,1) & y = x & Update(x,2) & Update(y,3)

How does one avoid interference between the updates to x and y?  Or is this
disallowed somehow?  {This is also a problem with the 'var' hack in Prolog,
by the way.  It is not a problem with pure versions using trees.}

> Following is the implementation of the Triangle Puzzle in Trilogy.
Great stuff.
> i) The variables of Trilogy start with small letters. Predicates,
>   types and constants, being identified by proper names, are
>   capitalized.
As a matter of fact, words like "hole" and "board" and so on are
_common_ nouns, not _proper_ nouns, so in English orthography should
_not_ take a capital letter.  I find it very confusing that "i" is a
variable, but "if" is a keyword.  If constants begin with capitals,
shouldn't keywords do the same?

>    The first solution is found on an 8MHz AT in 0.8 seconds as follows:
Sounds good.

>  vii) The reader will note that the arrays of Trilogy allow fast indexing
>     as opposed to the list traversal of Prolog.
Just a reminder:  Prolog doesn't require the use of lists for anything,
and a good Prolog programmer would not use them here.

But let's hear more about Trilogy.  Have I understood correctly that an
'in' or 'in out' parameter, cannot be unresolved, so that if the actual
parameter is defined by constraints, those constraints must be solved
before the call can happen?  Does this mean that an 'in' or 'in out'
parameter must be completely ground, or may such a parameter contain
constrained elements?

micha@ecrcvax.UUCP (Micha Meier) (03/07/88)

Since Paul Voda is travelling in Europe, I will try to answer some of
your questions (knowing the basic principles of Trilogy):

In article <721@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>But let's hear more about Trilogy.  Have I understood correctly that an
>'in' or 'in out' parameter, cannot be unresolved, so that if the actual
>parameter is defined by constraints, those constraints must be solved
>before the call can happen?  Does this mean that an 'in' or 'in out'
>parameter must be completely ground, or may such a parameter contain
>constrained elements?

Input variables are always ground, output variables will obtain ground values
and since an input-output variable stands for a pair (input, output),
it is ground before the assignment and stays so afterwards.
When one wants to use partially instantiated variables and constraints,
then one has to use symbolic (logical) variables.
When you don't use symbolic variables, your code can be as efficient
as in Pascal (or Turbo Prolog).

>Interesting!  Please explain this some more.  If I write
>
>	x := 6 & Incr(x) & y = x & Incr(x) & P(x)
>
>which version of x does y get?  (The answer should be obvious, but I'd like
>to see how it's done.) 

This is an abbreviation for

	x1 = 6 & Incr(x1, x2) & y = x2 & Incr(x2, x3) & P(x3)

and thus y is a copy of x at the moment of executing y = x and subsequent
changes of x don't affect y.

>What if we have some larger structure, and I do
>
>	x := NewThing & Update(x,1) & y = x & Update(x,2) & Update(y,3)
>
>How does one avoid interference between the updates to x and y?  Or is this
>disallowed somehow?  {This is also a problem with the 'var' hack in Prolog,
>by the way.  It is not a problem with pure versions using trees.}

This is an abbreviation for

	x1 = NewThing & Update(x1, x2, 1) & y1 = x2 & Update(x2, x3, 2) &
		Update(y1, y2, 3)

Since y is used as an input-output variable, the formula y = x is only
a test of the current values of y and x (both must be ground).
If there would be y := x instead of y = x, then y would be assigned a copy
of the current value of x and so there is no interference.

I think that in Prolog you could achieve similar results with a very
clever compiler (reusing the environemnts etc.) but only in a very
limited number of cases.


--Micha Meier

jha@its63b.ed.ac.uk (J Andrews) (03/10/88)

In article <508@ecrcvax.UUCP> micha@ecrcvax.UUCP (Micha Meier) writes:
>>	x := 6 & Incr(x) & y = x & Incr(x) & P(x)
  let's call this A
>
>This is an abbreviation for
>
>	x1 = 6 & Incr(x1, x2) & y = x2 & Incr(x2, x3) & P(x3)
  let's call this B

     I should just emphasise that what Micha means here by
"B is an abbreviation for A" is that the "meaning" of A, when
translated into standard logic-programming form, is B.  In the
implementation of Trilogy, however, the assignment is indeed
done destructively, without new variables being created.

     Some work has been done on detecting cases in Prolog in
which space for variables can be reused.  However, I think such
algorithms have to effectively put the program in disjunctive
normal form, and so are unlikely to be very efficient.  I think
the Trilogy approach of letting the programmer declare and
reassign input/output variables is cleaner.  (However, I am not
really an impartial observer. :-))

     This way of explaining assignment in logic programming
languages actually suggests a way of explaining it in imperative
languages.  Watch out -- we may soon see logic programming being
used as the semantic basis for conventional languages!

--Jamie.
  jha@lfcs.ed.ac.uk
"I am thinking of aurochs and angels, of the secrets of durable pigments"