[comp.lang.prolog] PROLOG Digest V5 #95

PROLOG-REQUEST@SUSHI.STANFORD.EDU (Chuck Restivo, The Moderator) (12/09/87)

PROLOG Digest           Wednesday, 9 Dec 1987      Volume 5 : Issue 95

Today's Topics:
                        Query - termCompare/3,
                        Theory - Impediments,
                          Puzzle - Challenge
----------------------------------------------------------------------

Date: 3 Dec 87 06:18:39 GMT
From: ubc-vision!alberta!calgary!spooner@beaver.cs.washington.edu 
      (David Spooner)
Subject: NU-Prolog termCompare/3.


Does anyone have any thoughts on why the goal:

    ?- termCompare(T, [a], [b]).

succeeds with:

    T = =

This causes problems when generating sets of lists with solutions/3,
for example powerset/2.

Also, redefining termCompare/3 does not help.  The anomaly became apparent
when using addElement/3 in the osets library.

?- Is there a problem with performing recursive term comparison based not
only on cardinality.

------------------------------

Date: Tue, 01 Dec 87 11:01:51 PST
From: narain%pluto@rand-unix.ARPA
Subject: Theoretical impediments

My note did mention that PA is decidable. Since Horn clauses are not,
it is plausible that the latter are richer than the former. This
argument can be made exact.

Every effectively computable function is definable in Horn clauses.
In particular, we can encode any decision procedure for PA as a set of
Horn clauses. Now the Fischer-Rabin result would apply to this set.
Hence, we have a problem in Horn clauses which takes super-exponential
time to solve.

-- Sanjai Narain

=============================================================================

------------------------------

Date: Mon, 7 Dec 87 11:05:40+0900
From: STANFORD Tick Evan <tick%icot.jp@RELAY.CS.NET>
Subject: PROGRAMMING CHALLENGE

To Whom it May Concern,

I am challenging everyone involved in the research of committed-choice
parallel logic programming languages to solve the following problem
using such a language.  I am specifically interested in FGHC implementations.
The problem is the famous Puzzle Problem by F. Baskett, implemented in C,
FORTRAN, Pascal, Lisp, and Prolog.  The Puzzle Problem is one of the most
popular performance benchmarks in the world.  The problem is pack a 5x5x5
solid cube with 18 smaller pieces: 4x2x1 (13), 3x1x1 (3), 2x2x1 (1), and
2x2x2 (1).  All 2005 solutions must be calculated and counted, but not
printed.

I have a serious concern that this problem is beyond the capacity of
current FGHC technology -- I myself have written a version of the program
but it runs out of memory or runs forever (more than four hours) on the
systems available at ICOT.  I am not an expert programmer, however.
I therefore challege everyone in the programming
community to produce a better implementation that executes in a finite
amount of time.  NOTE: the Prolog version I wrote runs very efficiently --
more efficiently than the Lisp version in the Gabriel Benchmarks.  To show
that committed-choice languages REALLY deserve to be the foundation of
the 5th Generation Computer Project, I believe it is vital to solve this
problem.  I believe the difficulty in solving this problem reflects more
than the immature technology.  It reflects the inherent inefficiency of the
programming styles required by the language.  I hope someone can disprove
this hypothesis.

                                        Evan Tick
                                        ICOT
                                        tick%icot.jp@relay.cs.net

The following source program runs on Ueda's DEC-20 FGHC System...
--------------------------------  CUT HERE ------------------------------------
% Puzzle
% Evan Tick
% tick%icot.jp@relay.cs.net     (ICOT)
% 11-26-87
%
% PROGRAM:
% This program runs under Ueda's DEC-20 FGHC system.  To run, ?- ghc go.
% The puzzle problem requires packing 18 small pieces within a 5x5x5 cube.
% The pieces are: 4x2x1 (13), 3x1x1 (3), 2x2x1 (1), 2x2x2 (1).  All 2005
% solutions must be found and counted, but not printed.  This program
% runs out of CORE when solving the puzzle, therefore, a smaller puzzle
% (with only six solutions) is included for test purposes.  The 5x5x5
% puzzle is also included, but in comments.
%
% NOTES:
% This is a semi-distributed version, i.e., the partial solution is
% represented solely by a group of piece processes.  Each piece process
% can respond to the following commands:
%       echo(I-O) --
%               return D-list I-O of pieces
%       check(Piece, Answer) --
%               check Piece with the internal piece for consistency
%               if consistent, return "yes", otherwise return "no"
%
% A select process first selects a Piece from the piece list.
% Two processes are spawned, connected by a merge box for routing
% later requests made by the children.  The left child is a checkall
% and the right child is another select process.  The main idea is
% that the checkall will find all solutions including the selected
% piece and the other child will find all solutions NOT including
% the selected piece.
%
% The Piece is of the form: orient(N,Olist), where N is the number of
% identically shaped pieces available, and Olist is a list of identifiers
% indicating the orientations of the shape.  NOTE: the identifiers in
% all the Olist's of all the pieces are unique -- this trick is used
% to efficiently index during piece translation.  The checkall attempts
% to spawn one checker process for each orientation of the selected piece.
% The piece is placed within each process, starting at the same origin.
% The translation from this origin is done with translate/4.  If the
% translation produces an unsafe situation, i.e., the shape falls outside
% of the solid's boundaries, the checker process is not spawned.
% Each successfully spawned checker is connected serially with merge
% boxes.
%
% Calculation of the current origin (i.e., where to place the next
% selected piece) is made with two large lists (with a sum of 125 entries)
% representing the empty and filled squares of the solid.  Each time
% a piece is selected, it is placed at the origin specified by the
% first element of the empty list.  Subsequently, the empty list and
% full list must be updated to reflect this placement.  This update
% is of course different for each orientation.
%
% Checking is done sequentially, by checking the closest piece (in
% the tree) and then the next piece, etc.  If all pieces are ok,
% the check request arrives at a dummy piece ("special") at the
% top of the tree, which always sends a "yes" reply.  If a piece
% is not ok, it sends a "no" reply itself.  Thus checking is not
% done in parallel, like in the previous version, but work is
% actually saved by detecting early failure.
%
% This program cleans-up the pieces only AFTER all solutions have
% been found.  This is accomplished by serializing the output with the
% top-level  process.  In addition, there is incremental garbage
% collection, implemented by short-circuiting the boxes.  After
% incremental collection, at program completion, the only boxes remaining
% correspond to solution paths.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

go :- true |
        initial(Slist,Plist),
        special(Snd),
        select(Plist, Slist, [], Snd, X-[]),
        outconv(X, Y, 0),
        outstream(Y).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% [Y|Ys] list of candidate pieces
% Empty  list of empty squares
% NonC   list of non-candidate pieces
% Snd    communication streams to pieces above
% I-O    answer stream

% in this case, choose last instance of this shape...
select([orient(M,L)|Ys], Empty, NonC, Snd, I-O):- M=:=1 |
        append(Ys, NonC, Unused),
        merge(SndL, SndR, Snd),
        checkall(L, Unused, Empty, SndL, I-I1),
        select(Ys, Empty, [orient(M,L)|NonC], SndR, I1-O).

% more than one instance of this shape exists...
select([orient(M,L)|Ys], Empty, NonC, Snd, I-O):- M=\=1 |
        M1 := M-1,
        append([orient(M1, L)|Ys], NonC, Unused),
        merge(SndL, SndR, Snd),
        checkall(L, Unused, Empty, SndL, I-I1),
        select(Ys, Empty, [orient(M,L)|NonC], SndR, I1-O).

% no more shapes exist as candidates...
select([], _, [_|_], Snd, I-O):- true |
        Snd = [],               % remove unwanted box
        I=O.

% all shapes have been selected --> solution has been found...
select([], _, [], Snd, I-O):- true |
%       Snd = [echo(List-[])],
        Snd = [],               % remove box after you find solution
        List = [dummy],         % don't care about exact solution - just #
        I = [List|O].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% spawn checker process for each orientation in Piece

checkall([], _, _, Snd, I-O):- true |
        Snd = [],
        I=O.
checkall([O|Os], Unused, Empty, Snd, Answer) :- true |
        Empty = [E|_],
        translate(O, E, Piece),
        check_piece(Piece, Status),
        checkall1(Status, Os, Piece, O-E, Unused, Empty, Snd, Answer).

% translated piece falls outside of solid boundary...
checkall1(bad, Os, _, _, Unused, Empty, Snd, Answer) :- true |
        checkall(Os, Unused, Empty, Snd, Answer).
% translated piece falls completely inside of solid...
checkall1(good, Os, Piece, Pretty, Unused, Empty, Snd, Answer) :- true |
        remove(good, Piece, Empty, NewEmpty, Status),
        checkall2(Status, Os, Piece, Pretty, Unused, Empty,
                  NewEmpty, Snd, Answer).

% translated piece falls inside a previously chosen piece...
checkall2(bad, Os, _, _, Unused, Empty, _, Snd, Answer) :- true |
        checkall(Os, Unused, Empty, Snd, Answer).
% translated piece falls outside all previously chosen pieces...
checkall2(good, Os, Piece, Pretty, Unused, Empty, NewEmpty, Snd, I0-I2) :-
        true |
        merge(SndL, SndR, Snd),
        checker(maybe, NewEmpty, Piece, Pretty, Unused, SndL, I0-I1),
        checkall(Os, Unused, Empty, SndR, I1-I2).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% checker process

% request check from piece above...
checker(maybe, Empty, Piece, Pretty, N, Snd, Answer):- true|
        Snd = [check(Piece,Reply)|Snds],
        checker(Reply, Empty, Piece, Pretty, N, Snds, Answer).
% special piece replied "yes", so Piece is ok...
checker(yes, Empty, Piece, Pretty, N, Snd, Answer) :- true |
        piece(Snd1, Snd, Piece, Pretty),
        select(N, Empty, [], Snd1, Answer).
% piece replied "no", so Piece is no good -- terminate process
checker(no, _, _, _, _, Snd, I-O) :- true |
        Snd = [],                       % remove unwanted merge
        I=O.

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% piece processes

piece([], Snd, _, _) :- true |
        Snd = [].
% echo back Piece
piece([echo(A-B)|Rcv], Snd, Piece, Pretty) :- true |
        A = [Pretty|C],                         % append # to reply
        Snd = [echo(C-B)|Snds],                 % send request up
        piece(Rcv, Snds, Piece, Pretty).
piece([check(Piece1,Answer)|Rcv], Snd, Piece2, Pretty) :- true |
        compare(Piece1, Piece2, Status),
        piece2(Status, check(Piece1,Answer), Rcv, Snd, Piece2, Pretty).

% check succeeds...
piece2(yes, Request, Rcv, Snd, Piece, Pretty) :- true |
        Snd = [Request|Snds],
        piece(Rcv, Snds, Piece, Pretty).
% check fails...
piece2(no, check(_,Answer), Rcv, Snd, Piece, Pretty) :- true |
        Answer = no,
        piece(Rcv, Snd, Piece, Pretty).

% if list intersection is empty, Status=yes
% if list intersection is non-empty, Status=no
compare([], _, Status) :- true |
        Status = yes.
compare([H|T], List, Status) :- true |
        compare(List, H, T, List, Status).

compare([], _, T, List, Status) :- true |
        compare(T, List, Status).
compare([Y|_], X, _, _, Status) :- X=Y |
        Status = no.
compare([Y|Ys], X, T, List, Status) :- X \= Y |
        compare(Ys, X, T, List, Status).

% special piece is dummy node at top-of-tree
special([]).                                    % kill yourself
special([echo(A-B)|Rcv]) :- true |
        A = B,                                  % finish echo
        special(Rcv).
special([check(_,Answer)|Rcv]) :- true |
        Answer = yes,                           % always answer yes
        special(Rcv).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% remove(good, Vector, Empty, NewEmpty, Status)
% remove all elements in Vector from Empty
% return Status of removal: "good" if Vector was a subset of Empty
%                           "bad" if Vector contained elements not in Empty

remove(bad, _, _, _, Status) :- true |
        Status = bad.
remove(good, [], Empty, NewEmpty, Status) :- true |
        Status = good,
        NewEmpty = Empty.
remove(good, [H|T], Empty, NewEmpty, Status) :- true |
        remove2(Empty, H, NextEmpty, SubStatus),
        remove(SubStatus, T, NextEmpty, NewEmpty, Status).

remove2([], _, Empty, Status) :- true |
        Status = bad.
remove2([E|Es], H, Empty, Status) :- E=H |
        Status = good,
        Es = Empty.
remove2([E|Es], H, Empty, Status) :- E \= H |
        Empty = [E|NewEmpty],
        remove2(Es, H, NewEmpty, Status).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% 4x2x1 (6 orientations)
translate(a, o(X,Y,Z), List) :- true |
        X1 := X+1, X2 := X+2, X3 := X+3, Y1 := Y+1,
        List = [o(X,Y, Z),o(X1,Y, Z),o(X2,Y, Z),o(X3,Y, Z),
                o(X,Y1,Z),o(X1,Y1,Z),o(X2,Y1,Z),o(X3,Y1,Z)].
translate(b, o(X,Y,Z), List) :- true |
        X1 := X+1, X2 := X+2, X3 := X+3, Z1 := Z+1,
        List = [o(X,Y,Z), o(X1,Y,Z), o(X2,Y,Z), o(X3,Y,Z),
                o(X,Y,Z1),o(X1,Y,Z1),o(X2,Y,Z1),o(X3,Y,Z1)].
translate(c, o(X,Y,Z), List) :- true |
        Y1 := Y+1, Y2 := Y+2, Y3 := Y+3, Z1 := Z+1,
        List = [o(X,Y,Z), o(X,Y1,Z), o(X,Y2,Z), o(X,Y3,Z),
                o(X,Y,Z1),o(X,Y1,Z1),o(X,Y2,Z1),o(X,Y3,Z1)].
translate(d, o(X,Y,Z), List) :- true |
        Y1 := Y+1, Y2 := Y+2, Y3 := Y+3, X1 := X+1,
        List = [o(X, Y,Z),o(X, Y1,Z),o(X, Y2,Z),o(X, Y3,Z),
                o(X1,Y,Z),o(X1,Y1,Z),o(X1,Y2,Z),o(X1,Y3,Z)].
translate(e, o(X,Y,Z), List) :- true |
        Z1 := Z+1, Z2 := Z+2, Z3 := Z+3, X1 := X+1,
        List = [o(X, Y,Z),o(X, Y,Z1),o(X, Y,Z2),o(X, Y,Z3),
                o(X1,Y,Z),o(X1,Y,Z1),o(X1,Y,Z2),o(X1,Y,Z3)].
translate(f, o(X,Y,Z), List) :- true |
        Z1 := Z+1, Z2 := Z+2, Z3 := Z+3, Y1 := Y+1,
        List = [o(X,Y, Z),o(X,Y, Z1),o(X,Y, Z2),o(X,Y, Z3),
                o(X,Y1,Z),o(X,Y1,Z1),o(X,Y1,Z2),o(X,Y1,Z3)].
% 3x1x1 (3 orientations)
translate(g, o(X,Y,Z), List) :- true |
        X1 := X+1, X2 := X+2,
        List = [o(X,Y,Z),o(X1,Y,Z),o(X2,Y,Z)].
translate(h, o(X,Y,Z), List) :- true |
        Y1 := Y+1, Y2 := Y+2,
        List = [o(X,Y,Z),o(X,Y1,Z),o(X,Y2,Z)].
translate(i, o(X,Y,Z), List) :- true |
        Z1 := Z+1, Z2 := Z+2,
        List = [o(X,Y,Z),o(X,Y,Z1),o(X,Y,Z2)].
% 2x2x1 (3 orientations)
translate(j, o(X,Y,Z), List) :- true |
        X1 := X+1, Y1 := Y+1,
        List = [o(X,Y,Z),o(X1,Y,Z),o(X,Y1,Z),o(X1,Y1,Z)].
translate(k, o(X,Y,Z), List) :- true |
        X1 := X+1, Z1 := Z+1,
        List = [o(X,Y,Z),o(X1,Y,Z),o(X,Y,Z1),o(X1,Y,Z1)].
translate(l, o(X,Y,Z), List) :- true |
        Y1 := Y+1, Z1 := Z+1,
        List = [o(X,Y,Z),o(X,Y1,Z),o(X,Y,Z1),o(X,Y1,Z1)].
% 2x2x2 (1 orientation)
translate(m, o(X,Y,Z), List) :- true |
        X1 := X+1, Y1 := Y+1, Z1 := Z+1,
        List = [o(X,Y,Z), o(X1,Y,Z), o(X,Y1,Z), o(X1,Y1,Z),
                o(X,Y,Z1),o(X1,Y,Z1),o(X,Y1,Z1),o(X1,Y1,Z1)].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% utilities...

append([A|X],Y,Z):- true |
        Z=[A|Z1], append(X,Y,Z1).
append([],   Y,Z):- true | Z=Y.

merge([], SndR, Snd) :- true | Snd = SndR.
merge(SndL, [], Snd) :- true | Snd = SndL.
merge([R|SndL], SndR, Snd) :- true | Snd = [R|Snds], merge(SndL, SndR, Snds).
merge(SndL, [R|SndR], Snd) :- true | Snd = [R|Snds], merge(SndL, SndR, Snds).

% outconv is used to prepare the output stream for outstream/1.
outconv([X|Xs1], Os0, N) :- true |
%       Os0 = [write(X), nl|Os1],
        Os0 = Os1,
        N1 := N+1,
        outconv(Xs1, Os1, N1).
outconv([], Os0, N) :- true |
        Os0 = [write(N), write(' solutions'), nl].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% puzzles...
initial(Slist,Plist) :- true |
        squares(Slist),
        piece_list(Plist).

% 6 solutions...
check_piece([o(X,Y,Z)|Rest], Status) :- X > 3 | Status = bad.
check_piece([o(X,Y,Z)|Rest], Status) :- Y > 0 | Status = bad.
check_piece([o(X,Y,Z)|Rest], Status) :- Z > 4 | Status = bad.
check_piece([o(X,Y,Z)|Rest], Status) :- X<4, Y<1, Z<5 |
        check_piece(Rest, Status).
check_piece([], Status) :- true | Status = good.

piece_list(List) :- true |                      % shape  #  orientation
        List = [orient( 1,[a,b,c,d,e,f]),       % 4x2x1 (1)x(6)
                orient( 4,[g,h,i])].            % 3x1x1 (4)x(3)

squares(List) :- true |
        List =
        [o(0,0,0),o(1,0,0),o(2,0,0),o(3,0,0),
         o(0,0,1),o(1,0,1),o(2,0,1),o(3,0,1),
         o(0,0,2),o(1,0,2),o(2,0,2),o(3,0,2),
         o(0,0,3),o(1,0,3),o(2,0,3),o(3,0,3),
         o(0,0,4),o(1,0,4),o(2,0,4),o(3,0,4)].

/*
% 2005 solutions...
check_piece([o(X,Y,Z)|Rest], Status) :- X<6, Y<6, Z<6 |
        check_piece(Rest, Status).
check_piece([], Status) :- true | Status = good.
check_piece([o(X,Y,Z)|Rest], Status) :- X > 5 | Status = bad.
check_piece([o(X,Y,Z)|Rest], Status) :- Y > 5 | Status = bad.
check_piece([o(X,Y,Z)|Rest], Status) :- Z > 5 | Status = bad.

piece_list(List) :- true |                      % shape  #  orientation
        List = [orient(13,[a,b,c,d,e,f]),       % 4x2x1 (13)x(6)
                orient( 3,[g,h,i]),             % 3x1x1 (3)x(3)
                orient( 1,[j,k,l]),             % 2x2x1 (1)x(3)
                orient( 1,[m])].                % 2x2x2 (1)x(1)

squares(List) :- true |
        List =
        [o(0,0,0),o(1,0,0),o(2,0,0),o(3,0,0),o(4,0,0),
         o(0,1,0),o(1,1,0),o(2,1,0),o(3,1,0),o(4,1,0),
         o(0,2,0),o(1,2,0),o(2,2,0),o(3,2,0),o(4,2,0),
         o(0,3,0),o(1,3,0),o(2,3,0),o(3,3,0),o(4,3,0),
         o(0,4,0),o(1,4,0),o(2,4,0),o(3,4,0),o(4,4,0),

         o(0,0,1),o(1,0,1),o(2,0,1),o(3,0,1),o(4,0,1),
         o(0,1,1),o(1,1,1),o(2,1,1),o(3,1,1),o(4,1,1),
         o(0,2,1),o(1,2,1),o(2,2,1),o(3,2,1),o(4,2,1),
         o(0,3,1),o(1,3,1),o(2,3,1),o(3,3,1),o(4,3,1),
         o(0,4,1),o(1,4,1),o(2,4,1),o(3,4,1),o(4,4,1),

         o(0,0,2),o(1,0,2),o(2,0,2),o(3,0,2),o(4,0,2),
         o(0,1,2),o(1,1,2),o(2,1,2),o(3,1,2),o(4,1,2),
         o(0,2,2),o(1,2,2),o(2,2,2),o(3,2,2),o(4,2,2),
         o(0,3,2),o(1,3,2),o(2,3,2),o(3,3,2),o(4,3,2),
         o(0,4,2),o(1,4,2),o(2,4,2),o(3,4,2),o(4,4,2),

         o(0,0,3),o(1,0,3),o(2,0,3),o(3,0,3),o(4,0,3),
         o(0,1,3),o(1,1,3),o(2,1,3),o(3,1,3),o(4,1,3),
         o(0,2,3),o(1,2,3),o(2,2,3),o(3,2,3),o(4,2,3),
         o(0,3,3),o(1,3,3),o(2,3,3),o(3,3,3),o(4,3,3),
         o(0,4,3),o(1,4,3),o(2,4,3),o(3,4,3),o(4,4,3),

         o(0,0,4),o(1,0,4),o(2,0,4),o(3,0,4),o(4,0,4),
         o(0,1,4),o(1,1,4),o(2,1,4),o(3,1,4),o(4,1,4),
         o(0,2,4),o(1,2,4),o(2,2,4),o(3,2,4),o(4,2,4),
         o(0,3,4),o(1,3,4),o(2,3,4),o(3,3,4),o(4,3,4),
         o(0,4,4),o(1,4,4),o(2,4,4),o(3,4,4),o(4,4,4)].
*/

------------------------------

End of PROLOG Digest
********************