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

  1.  
  2.  
  3. /*  ---------------------------------------------------------------------
  4. GAME of SQUARES                           January 1986
  5.  
  6. George Planansky
  7. Amethystems
  8. 11 Varnum St., Arlington, MA 02174,
  9. 617/641-3128.
  10.  
  11. This was written with  A.D.A PD PROLOG V 1.6a.
  12.     (Automata Design Associates
  13.      1570 Arran Way, Dresher, PA. 19025
  14.      215/646-4894.)
  15.  
  16. INSTRUCTIONS
  17.  
  18. This game file SQR_GAME.PRO, and the interpreter file PDPROLOG.EXE, need be
  19. in the active PC/MS -DOS directory.
  20.  
  21. Invoke the interpreter from DOS with:
  22. > "PDPROLOG <Return>".
  23.  
  24. Tell the interpreter to load game program by entering:
  25. ?- "consult(sqr_game). <Return>"
  26.  
  27. Start squares by entering:
  28. ?-"squares. <Return>"
  29.  
  30. Note that all entries must follow the above format; thus:
  31.  
  32. ?-"2. <Return>"
  33.  
  34. enters the integer "2" .
  35.  
  36. Press <Esc> to quit the game to the interpreter.
  37.  
  38. To return to DOS use:  ?- "exitsys. <Return>"
  39.  
  40. To replay the game you must exit the interpreter and start over,
  41. as retract and asserts are invoked during play.
  42. With my system and my version of PD PROLOG, I have to restart the
  43. computer to replay the game.  I used a Zenith 151 with 640 K.
  44.  
  45. Note from Bob Morein: You can reinitialize the game, without 
  46. exiting, by using the predicate command "forget( user )". This 
  47. retracts all clauses that have been asserted by the program.
  48.  
  49.  
  50.  
  51. COMMENTs
  52.  
  53. There would seem to be two ideal strategems in game playing:
  54. 1)  Look at:  the present board position alone could be evaluated according
  55. to some set of criteria, yielding the desired next move.
  56. 2)  Play ahead:  all possible lines of play could be followed, each to the
  57. end or determining point of the game.  The most favorable line of play
  58. would then give the next move.
  59.  
  60. A limited look-ahead would use both.
  61.  
  62. While PROLOG seems naturally suited to recursive searching, this program
  63. uses the first method.  A simple choice protocol is here coded in PROLOG
  64. using ordered facts and directed iterations to instill priorities.  A line
  65. is is chosen in accordance with two values:
  66.  
  67. 1. the line is a member of a square having a certain number of entries,
  68.    or "sq-entrity" (coded as S).
  69. 2. the adjoining square via that line has a certain number of entries,
  70.    the "adj-entrity" (coded as A).
  71.  
  72. For lines in the interior of the board, which each belong to two "regular"
  73. squares, the distinction of S vs A squares is moot.  Exterior lines in this
  74. program are deemed to all be the neighbor of a virtual exterior square, of
  75. Id zero, and this choice of fudge makes the S/A distinction, and some other
  76. supporting fudgework, necessary.
  77.  
  78. The nearest neighbor weighting assigned to lines in this program is not
  79. enough by which to read board configurations, and this program loses.
  80. Another version which also considers next-nearest neighbor effects does
  81. better until it runs out of symbol space after about 5 moves.
  82.  
  83. As long as no one has published a "solution", it might be fun to have a PROLOG
  84. game competition, using squares of 3 x 3 or 4 x 4 size.   PDPROLOG would be
  85. an appropriate instrument for run-offs -- it would be a further nice way of
  86. promoting interest in the language.  Something for PROLOG groups to pick up?
  87. I would enjoy hearing suggestions on this.
  88.  
  89.                  * * * * * * * * * * * * * * * * * *
  90.  
  91. We played this game for a while back in high school (class of '65).  I have
  92. no idea where it came from.  For all I know one of us re-invented it.  The
  93. funny thing is that we never figured out a winning strategy for a 3 x 3
  94. board, though we were sure one existed. Geometry had given us a taste of the
  95. power of logic, and it looked like things were going to make sense.
  96. Newton and Hutton, Godel and God, would come later.
  97.  
  98. Maybe it was the 4 x 4 that stumped us.  I hope the solution to squares
  99. ( => 3 by 3) is not painfully obvious.
  100.  
  101. My vigorous and appreciative thanks go to ADA for disseminating a nice
  102. public domain PROLOG.
  103.  
  104.                  * * * * * * * * * * * * * * * * * * * *
  105. F.W.I.W. ...
  106.  
  107. The structures square/2 and Gr:grid/12 demonstrate the two basic ways that
  108. data and structures are stored, accessed, and manipulated in PROLOG:
  109.  
  110. 1.  as arguments of a predicate (grid/12), and,
  111. 2.  as facts or components of facts in the database (square/5).
  112.  
  113. Notice that Gr is an argument of many of the predicates in this program,
  114. and is passed between them by sharing.
  115. Square/5 however is accessed by matching with the database, and, by revising
  116. the database via retract & asserta.
  117.  
  118. You might ponder what sort of lives Gr and square/5 lead, existentially,
  119. in this program.  The discussion to card_file (see CARDFILE.PRO) touches
  120. on this.  One use of retract/asserts data is within clauses that terminate
  121. with a cut-fail, to realize the contrary intentions of space reclamation
  122. and data survival.
  123.  
  124. Core PROLOG, like core Pascal, doesn't offer much by way of screen control.
  125. Here, do_show_display/1 uses available screen output predicates to display
  126. the current game board.
  127. Notice that do_show_display/1 receives Gr as an argument and accesses
  128. square/5 by matching.
  129.  
  130. The characters, on screen, of the displayed board consist of constants and
  131. variables.  The variables correspond to the parts of the display that may
  132. change from play to play, such as the lines.  do_show_display/1 tests
  133. the status of the components of Gr and of the squares to choose the
  134. appropriate instantiations of the display variables, and passes them to
  135. do_display/18.
  136.  
  137. There are two show_display/1 clauses so that do_show_display/1 can fail
  138. after its screen output occurs as a side effect.  On failure, tentatively
  139. instantiated variables in the tail of a clause become de-instantiated, and
  140. hopefully vaporize along with their trail.  This is a stab at saving
  141. memory, though I still run out of symbol space, whatever that is.
  142.  
  143. Some other items:
  144.  
  145. *  The predicates play_game/2 and which_move/3 demonstrate decison/switching
  146.    behavior.
  147. *  score/5 steps its way through the facts square/5.  What are the ultimate
  148.    and penultimate goals of score/5? Note the boundary case(s), and how the
  149.    scores are carried along, then delivered to the right arguments.  This
  150.    is a PROLOG version of a Pascal repeat-until iteration.
  151. *  open_grid/2 is similarly iterative with more than one possible exit.
  152. *  own_up demonstrates use of retract and asserta, and generates a flag for
  153.    which_move/3.  A later version of own_up uses retract and asserta on the
  154.    flag too, and has a cut-fail ending.
  155. *  I had originally used recursion (as, say, in C & M 's append) instead
  156.    of iteration (as in score/5) in some predicates, but changed to the
  157.    latter with intentions of efficiency.  It may be that this is less
  158.    efficient in PDPROLOG, the way I have done it.
  159. ----------------------------------------------------------------------- */
  160.  
  161. /* sqr_game.pro  V 2 (nearest neighbor entry priorities; iterations etc.
  162.                       not much optimized) */
  163.  
  164. /* ------------------- board data --------------------------------*/
  165.  
  166. /*    Id,            Si,      Ad,En,Ow     Si>sides, Ad>adjacent Id's,
  167.                                            Ow> owner.  */
  168. square(0,           [_],     [_], 0, 0).
  169. square(1, [10, 1, 2, 3], [0,2,4], 0, 1).
  170. square(2, [ 3, 4, 5, 6], [0,1,3], 0, 2).
  171. square(3, [ 6, 7, 8, 9], [0,2,4], 0, 3).
  172. square(4, [ 9,11,12,10], [0,1,3], 0, 4).
  173. /* Id = 0 is a "virtual" square for lines on the outer margins of the board.
  174.    This is a lame device to make some of the procedures work without
  175.    messy exceptions; but, messy exceptions are then required on its account */
  176.  
  177. /*  line_square gives a line number and its adjoining squares.  The order
  178.     of these lines affects the order of choice in choose_line */
  179.  
  180. /*         L,S1,S2  */
  181. line_square(1,1,0).
  182. line_square(2,1,0).
  183. line_square(3,1,2).
  184. line_square(4,2,0).
  185. line_square(5,2,0).
  186. line_square(6,2,3).
  187. line_square(7,3,0).
  188. line_square(8,3,0).
  189. line_square(9,3,4).
  190. line_square(10,1,4).
  191. line_square(11,4,0).
  192. line_square(12,4,0).
  193.  
  194. /* ---------------------------- grid ------------------------------------*/
  195.  
  196. /* Gr = grid(G1,G2,G3,G4,G5,G6,G7,G8,G9,G10,G11,G12).
  197.    Gr records the status of the lines.  Instantiated variables G#
  198.    indicate a line has been entered during play.  Functor and
  199.    arg are used, mostly, instead of simply writing out grid(etc...),
  200.    to save space and to make it easier to expand the number of lines. */
  201.  
  202. is_a_grid(Gr) :- functor(Gr, grid, 12).
  203.  
  204. open_line(Gr,L) :- arg(L,Gr,V), var(V).
  205.  
  206. open_grid(Gr,13) :- !,fail.
  207. open_grid(Gr, L) :- arg(L,Gr,V), var(V),print('\ngrid open'),!.
  208. open_grid(Gr, L) :- Ln is L + 1, open_grid(Gr,Ln).
  209.  
  210. /* ------------------------------ play_game ------------------------------*/
  211.  
  212. /* ///me_move/// */
  213.  
  214. /* priority(entries in a line's home square, entries in its adjacent square */
  215. priority(3,2) :- print('\nP 32 ').
  216. priority(3,_) :- print('\nP 3* ').
  217. priority(0,0) :- print('\nP 00 ').
  218. priority(0,1) :- print('\nP 01 ').
  219. priority(1,1) :- print('\nP 11 ').
  220. priority(2,0) :- print('\nP 20 ').
  221. priority(2,1) :- print('\nP 21 ').
  222. priority(1,2) :- print('\nP 12 ').
  223. priority(0,2) :- print('\nP 02 ').
  224. priority(_,_) :- print('\nP ** ').
  225.  
  226. me_move(Gr,Next) :- print('My move ...'),
  227.                     open_grid(Gr,1), print(' choosing line ...'),
  228.                     priority(S,A),
  229.                     choose_line(Gr,S,A,L),!, arg(L,Gr,L),
  230.                     print('& entered.'),
  231.                     print('\n ... check entries ... '),
  232.                     own_up(L,'M',XX),!,
  233.                     which_move(XX, me, Next).
  234. me_move(Gr,over) :- print('\nI have no more moves.'),!.
  235.  
  236. choose_line(Gr,En1,En2,L) :- square(Id1,_,_,En1,_),
  237.                              Id1 \= 0,
  238.                              square(Id2,_,_,En2,_),
  239.                              print(' ',Id1,Id2),
  240.                              match(L,Id1,Id2),
  241.                              open_line(Gr,L),
  242.                              print('\n',L,' chosen '), !.
  243.  
  244. match(L,Id1,Id2) :- line_square(L,Id1,Id2).
  245. match(L,Id1,Id2) :- line_square(L,Id2,Id1).
  246.  
  247. /* ////you_move//// */
  248.  
  249. you_move(Gr,Next) :- open_grid(Gr,1),
  250.                      get_line(Gr,L),!,
  251.                      print('\n...check entries...'),
  252.                      own_up(L,'Y',XX),!, which_move(XX, you, Next),!.
  253. you_move(Gr,over) :- print('\nYou have no more moves.'),!.
  254.  
  255. get_line(Gr,L) :- print('\nEnter the line number (1-12) of your move.>>'),
  256.                   read(  R), check(Gr,R,L), arg(L,Gr,L),
  257.                   print('\ & entered.'),!.
  258. get_line(Gr,L) :- print('\nillegal or unavailable entry, try again\n'),
  259.                   get_line(Gr,L).
  260.  
  261. check(Gr,R,R) :- print('<',R,'>'),integer(R),
  262.                  R > 0, R < 13,
  263.                  arg(R,Gr,V), var(V),
  264.                  print(' new entry, accepted ...').
  265.  
  266. /* ///common move/// */
  267.  
  268. own_up(L,Who,XX):- line_square(L,Id1,Id2),
  269.                    owner(Id1,Who,YY),
  270.                    owner(Id2,Who,ZZ),
  271.                    (  ((YY = xx ; ZZ = xx), XX = xx)
  272.                    ;  (XX = xy) ),
  273.                    print('... checked ').
  274.  
  275. owner(Id,Who,WW) :- Id \= 0,
  276.                  square(Id,Si,Ad,En,Ow), Ena is En+1,
  277.                  retract(square(Id,Si,Ad,En,Ow)),
  278.                  ( (Ena = 4, Owa = Who, WW = xx, print('\n',Who,' owns ',Id))
  279.                    ; (Owa = Ow, WW = xy) ),
  280.                  asserta(square(Id,Si,Ad,Ena,Owa)).
  281. owner(_,_,xy).
  282.  
  283. which_move(xx, This, This) :- !.
  284. which_move(xy,   me,  you) :- !.
  285. which_move(xy,  you,   me) :- !.
  286.  
  287. /* ///main/// */
  288. play_game(Gr,you) :- show_display(Gr), you_move(Gr,Next),!,play_game(Gr,Next).
  289. play_game(Gr, me) :- show_display(Gr),  me_move(Gr,Next),!,play_game(Gr,Next).
  290. play_game(Gr,over).
  291.  
  292. /* .........................end play_game................................*/
  293.  
  294. /* ----------------------  Display predicates -------------------------- */
  295. show_display(Gr) :- do_show_display(Gr).
  296. show_display( _).
  297.  
  298. do_show_display(Gr) :-
  299.      P = '.',  V = '|',  H = '-', SP = ' ',  DT = '*',
  300.      Gr = grid(G1,G2,G3,G4,G5,G6,G7,G8,G9,G10,G11,G12),
  301.      ( (var(G1),  L1 = P) ; (L1 = V) ),
  302.      ( (var(G2),  L2 = P) ; (L2 = H) ),
  303.      ( (var(G3),  L3 = P) ; (L3 = V) ),
  304.      ( (var(G4),  L4 = P) ; (L4 = H) ),
  305.      ( (var(G5),  L5 = P) ; (L5 = V) ),
  306.      ( (var(G6),  L6 = P) ; (L6 = H) ),
  307.      ( (var(G7),  L7 = P) ; (L7 = V) ),
  308.      ( (var(G8),  L8 = P) ; (L8 = H) ),
  309.      ( (var(G9),  L9 = P) ; (L9 = V) ),
  310.      ( (var(G10), L10 = P) ; (L10 = H) ),
  311.      ( (var(G11), L11 = P) ; (L11 = V) ),
  312.      ( (var(G12), L12 = P) ; (L12 = H) ),
  313.      square(1,_,_,_,O1), square(2,_,_,_,O2),
  314.      square(3,_,_,_,O3), square(4,_,_,_,O4),
  315.      do_display(L1,L2,L3,L4,L5,L6,L7,L8,L9,L10,L11,L12,SP,DT,O1,O2,O3,O4),
  316.      !, fail.
  317.  
  318. do_display(L1,L2,L3,L4,L5,L6,L7,L8,L9,M0,M1,M2,SP,DT,O1,O2,O3,O4) :-
  319.    nl,tab(10),
  320.    print(DT,L2,L2,L2,L2, 2,L2,L2,L2,L2,DT,L4,L4,L4,L4, 4,L4,L4,L4,L4,DT),
  321.    nl,tab(10),
  322.    print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
  323.    nl,tab(10),
  324.    print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
  325.    nl,tab(10),
  326.    print( 1,SP,SP,SP,SP,O1,SP,SP,SP,SP, 3,SP,SP,SP,SP,O2,SP,SP,SP,SP, 5),
  327.    nl,tab(10),
  328.    print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
  329.    nl,tab(10),
  330.    print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
  331.    nl,tab(10),
  332.    print(DT,M0,M0,M0, 1, 0,M0,M0,M0,M0,DT,L6,L6,L6,L6, 6,L6,L6,L6,L6,DT),
  333.    nl,tab(10),
  334.    print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
  335.    nl,tab(10),
  336.    print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
  337.    nl,tab(10),
  338.    print( 1, 1,SP,SP,SP,O4,SP,SP,SP,SP, 9,SP,SP,SP,SP,O3,SP,SP,SP,SP, 7),
  339.    nl,tab(10),
  340.    print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
  341.    nl,tab(10),
  342.    print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
  343.    nl,tab(10),
  344.    print(DT,M2,M2,M2, 1, 2,M2,M2,M2,M2,DT,L8,L8,L8,L8, 8,L8,L8,L8,L8,DT),
  345.    nl,!.
  346. /* .............................end display.............................. */
  347.  
  348. intro_squares:-
  349.    print('\nGAME of SQUARES\n\n'),
  350.    print('players:  There are two players, you (a.k.a "Y") and mr (a.k.a. "M").\n'),
  351.    print('goal   :  The player who gains the most squares, wins.\n'),
  352.    print('            The player that completes a square will own that square.\n'),
  353.    print('board  :  A grid of 4 squares, corners indicated by the stars (*),\n'),
  354.    print('            sides indicated by the dotted lines.\n'),
  355.    print('            Initially all sides are blank and nonr are owned.\n'),
  356.    print('a play :  A play consists of filling in a side of a square, with a line.\n'),
  357.    print('a turn :  A player MUST make a play if it is his or her turn.\n'),
  358.    print('            If a play completes a square, the player MUST make a further play.\n'),
  359.    print('            If a play does not complete a square, that turn ends.\n\n'),!.
  360.  
  361. play :-
  362.     print('\nShall I start? (enter y/n):  '),
  363.     ( (read(y), Who = me) ; (Who = you) ),
  364.     print('\nGAME of SQUARES ... let the play begin!'),
  365.     is_a_grid(Gr),
  366.     play_game(Gr,Who), !.
  367.  
  368. /* --------------------- Scoring & Winner -------------------------- */
  369. get_winner :- score(Y,M,0,0,1),
  370.               print('\nGame over -- the outcome is:'),
  371.               print('\n     your squares> ',Y),
  372.               print('\n       my squares> ',M),
  373.               nl, winner(Y,M).
  374.  
  375. score(Y, M, Y,M,5).
  376. score(Yt,Mt,Y,M,I) :- square(I,_,_,_,'Y'), Y2 is Y+1, I2 is I+1,
  377.                       score(Yt,Mt,Y2,M,I2).
  378. score(Yt,Mt,Y,M,I) :- square(I,_,_,_,'M'), M2 is M+1, I2 is I+1,
  379.                       score(Yt,Mt,Y,M2,I2).
  380.  
  381. winner(4,_) :- print('\nYou won.  Ever play this game before?.').
  382. winner(3,_) :- print('\nYou win ...\n\n   how about a little bet on the side?').
  383. winner(2,_) :- print('\nA tie.  Close call, n\'est-ce pas? .').
  384. winner(1,_) :- print('\nI win.  But what did you expect?').
  385. winner(0,_) :- print('\nI win.  Pay up, sucker!').
  386. /* .....................end scoring & winner.......................... */
  387.  
  388.  
  389. /* starting clause */
  390. squares:-
  391.     intro_squares,
  392.     play,
  393.     get_winner.
  394.  
  395. /* end of game.pro */