home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 December
/
simtel1292_SIMTEL_1292_Walnut_Creek.iso
/
msdos
/
prolog
/
prolog19.arc
/
HANOI.PRO
< prev
next >
Wrap
Text File
|
1986-05-05
|
3KB
|
116 lines
/*
Note: Carl is an A.D.A. PROLOG user who has contributed this program for
the enjoyment of others.
Towers of Hanoi by Carl Bredlau
909 Rahway Avenue
Westfield, New Jersey 07090
*/
% stuff for prolog 86
% print is changed to prin
put(X) :- ascii(C,X), putc(C).
makelist(1,[1]).
makelist(N, [N|Y]) :- N1 is N - 1, makelist(N1,Y).
biggie(1,X,[X]).
biggie(N,X,[X|Z]) :- N1 is N - 1, X1 is X + 1, biggie(N1,X1,Z).
alist(N,Y) :- biggie(N,1,Y).
%/* get the size of a list */
size([],0) :- !.
size([_|X],Num) :- size(X,N1), Num is N1 + 1.
%/* Might as well keep track of the disks on the poles. This is
% not really necessary; all we need to know is how many
% disks are on a pole */
readtop(N,Y) :- retract(pole(N,[Y|X])), asserta(pole(N,X)).
writetop(N,Y) :- retract(pole(N,X)), asserta(pole(N,[Y|X])).
makepoles(N) :- alist(N,Y), asserta( pole(1,Y)),
asserta(pole(2,[])), asserta(pole(3,[])).
%/* stuff for pretty printing */
%/* Note: the CONFIG.SYS file must contain the line ANSI.SYS. Also,
% the ANSI.SYS file must be on the disk when the system is booted */
out(X) :- put(27), prin(X).
clear :- out('[2J'). % /* clear screen */
goto(X,Y) :- put(27),prin('[',X),put(59),prin(Y,'H'). % /* 59 is ; */
stuff(1,X) :- prin(X), !.
stuff(N,X) :- prin(X), N1 is N - 1, stuff(N1,X).
newhanoi(1,A,B,C) :- move(1,A,B).
newhanoi(N,A,B,C) :- !, N1 is N - 1,
newhanoi(N1,A,C,B),
move(N,A,B),
newhanoi(N1,C,B,A).
%/* As mentioned earlier size and readtop are not really needed,
% but I threw them in so that you can see what's there. */
move(N,A,B) :- !, pole(A,Adisk), size(Adisk,ANum),readtop(A,N),
X1 is 20 - ANum, Y1 is 5 + (A - 1)* 15,
goto(X1,Y1), stuff(N,' '),
writetop(B,N), pole(B,Bdisk), size(Bdisk,BNum),
X2 is 20 - BNum, Y2 is 5 + (B - 1)* 15,
goto(X2,Y2), stuff(N,'*'),
goto(24,1),
prin('Move disk ',N,' from ',A,' to ',B,' ').
firstpole(N,1) :- X1 is 20 - N, goto(X1,5),
stuff(1,'*'), !.
firstpole(N,L) :- X1 is (20 - N) + (L - 1), goto(X1,5),
stuff(L,'*'),
L1 is L - 1, firstpole(N,L1).
start :- prin('How many disks? '), read(N), clear, firstpole(N,N),
makepoles(N), newhanoi(N,1,2,3), !.
factor(0,Y) :- Y is 1, !.
factor(X,Y) :- Z is X - 1, factor(Z,W), Y is X*W.
%/* recursive version a n! and towers of hanoi */
hanoi(1,A,B,C) :- prin('Move disk ',1,' from ',A,' to ',B),nl, !.
hanoi(N,A,B,C) :- N1 is N - 1,
hanoi(N1,A,C,B), !,
prin('Move disk ',N,' from ',A,' to ',B), nl,
hanoi(N1,C,B,A), !.