home *** CD-ROM | disk | FTP | other *** search
/ Power-Programmierung / CD1.mdf / prolog / pdprolog / hanoi.pro < prev    next >
Text File  |  1986-05-05  |  3KB  |  116 lines

  1. /*
  2. Note: Carl is an A.D.A. PROLOG user who has contributed this program for
  3. the enjoyment of others. 
  4.  
  5.                  Towers of Hanoi by Carl Bredlau
  6.                         909 Rahway Avenue
  7.                    Westfield, New Jersey 07090
  8. */
  9.  
  10.  
  11. %   stuff for prolog 86
  12. %   print is changed to prin
  13.  
  14. put(X) :- ascii(C,X), putc(C).
  15.  
  16. makelist(1,[1]).
  17. makelist(N, [N|Y]) :- N1 is N - 1, makelist(N1,Y).
  18.  
  19. biggie(1,X,[X]).
  20. biggie(N,X,[X|Z]) :- N1 is N - 1, X1 is X + 1, biggie(N1,X1,Z).
  21.  
  22. alist(N,Y) :- biggie(N,1,Y).
  23.  
  24. %/* get the size of a list  */
  25.  
  26. size([],0) :-  !.
  27. size([_|X],Num) :- size(X,N1), Num is N1 + 1.
  28.  
  29. %/* Might as well keep track of the disks on the poles.  This is
  30. %   not really necessary; all we need to know is how many
  31. %   disks are on a pole  */
  32.  
  33.  
  34.  
  35. readtop(N,Y)  :- retract(pole(N,[Y|X])), asserta(pole(N,X)).
  36.  
  37. writetop(N,Y) :- retract(pole(N,X)),  asserta(pole(N,[Y|X])).
  38.  
  39. makepoles(N) :- alist(N,Y), asserta( pole(1,Y)),
  40.                 asserta(pole(2,[])), asserta(pole(3,[])).
  41.  
  42. %/* stuff for pretty printing   */
  43. %/* Note: the CONFIG.SYS file must contain the line ANSI.SYS.  Also,
  44. %   the ANSI.SYS file must be on the disk when the system is booted     */
  45.  
  46. out(X) :- put(27), prin(X).
  47. clear  :- out('[2J'). % /* clear screen */
  48.  
  49. goto(X,Y)  :- put(27),prin('[',X),put(59),prin(Y,'H').  % /* 59 is ; */
  50.  
  51.  
  52. stuff(1,X) :- prin(X), !.
  53. stuff(N,X) :- prin(X), N1 is N - 1, stuff(N1,X).
  54.  
  55.  
  56.  
  57. newhanoi(1,A,B,C) :- move(1,A,B).
  58. newhanoi(N,A,B,C) :- !,  N1 is N - 1,
  59.                        newhanoi(N1,A,C,B),
  60.                        move(N,A,B),
  61.                        newhanoi(N1,C,B,A).
  62.  
  63.  
  64.  
  65. %/*  As mentioned earlier size and readtop are not really needed,
  66. %    but I threw them in so that you can see what's there.             */
  67.  
  68. move(N,A,B)  :- !,   pole(A,Adisk), size(Adisk,ANum),readtop(A,N),
  69.                    X1 is 20 - ANum, Y1 is 5 + (A - 1)* 15,
  70.                    goto(X1,Y1), stuff(N,' '),
  71.                    writetop(B,N), pole(B,Bdisk), size(Bdisk,BNum),
  72.                    X2 is 20 - BNum, Y2 is 5 + (B - 1)* 15,
  73.                    goto(X2,Y2), stuff(N,'*'),
  74.                    goto(24,1),
  75.                    prin('Move disk ',N,' from ',A,' to ',B,'         ').
  76.  
  77.  
  78. firstpole(N,1)  :- X1 is 20 - N, goto(X1,5),
  79.                    stuff(1,'*'), !.
  80.  
  81. firstpole(N,L) :-  X1 is (20 - N) + (L - 1), goto(X1,5),
  82.                    stuff(L,'*'),
  83.                    L1 is L - 1, firstpole(N,L1).
  84.  
  85.  
  86.  
  87. start :- prin('How many disks? '), read(N), clear, firstpole(N,N),
  88.             makepoles(N), newhanoi(N,1,2,3), !.
  89.  
  90.  
  91.  
  92.  
  93. factor(0,Y) :- Y is 1, !.
  94. factor(X,Y) :- Z is X - 1, factor(Z,W), Y is X*W.
  95.  
  96. %/* recursive version a n! and towers of hanoi  */
  97. hanoi(1,A,B,C) :- prin('Move disk ',1,' from ',A,' to ',B),nl, !.
  98. hanoi(N,A,B,C) :-   N1 is N - 1,
  99.                     hanoi(N1,A,C,B), !,
  100.                     prin('Move disk ',N,' from ',A,' to ',B), nl,
  101.                     hanoi(N1,C,B,A), !.
  102.  
  103.  
  104.  
  105.  
  106.  
  107.  
  108.  
  109.  
  110.  
  111.  
  112.  
  113.  
  114.  
  115.  
  116.