r5103: *** empty log message ***
[reversi.git] / strategies.lisp
1 ;;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Base: 10; Package: reversi -*-
2 ;;;;***************************************************************************
3 ;;;;
4 ;;;; FILE IDENTIFICATION
5 ;;;; 
6 ;;;;  Name:           strategies.lisp
7 ;;;;  Purpose:        Strategy routines for reversi
8 ;;;;  Programer:      Kevin Rosenberg based on code by Peter Norvig
9 ;;;;  Date Started:   1 Nov 2001
10 ;;;;
11 ;;;; $Id: strategies.lisp,v 1.6 2003/06/12 12:42:13 kevin Exp $
12 ;;;;
13 ;;;; This file is Copyright (c) 2001-2003 by Kevin M. Rosenberg 
14 ;;;; and Copyright (c) 1998-2002 Peter Norvig
15 ;;;;
16 ;;;; Reversi users are granted the rights to distribute and use this software
17 ;;;; as governed by the terms of the Lisp Lesser GNU Public License
18 ;;;; (http://opensource.franz.com/preamble.html), also known as the LLGPL.
19 ;;;;***************************************************************************
20
21 (in-package #:reversi)
22
23 (defun random-strategy (player board)
24   "Make any legal move."
25   (declare (type player player)
26            (type board board))
27   (random-elt (legal-moves player board)))
28
29
30 (defun maximize-difference (player board)
31   "A strategy that maximizes the difference in pieces."
32   (declare (type player player)
33            (type board board))
34   (funcall (maximizer #'count-difference) player board))
35
36 (defun maximizer (eval-fn)
37   "Return a strategy that will consider every legal move,
38   apply EVAL-FN to each resulting board, and choose 
39   the move for which EVAL-FN returns the best score.
40   FN takes two arguments: the player-to-move and board"
41   #'(lambda (player board)
42       (declare (type player player)
43                (type board board))
44       (let* ((moves (legal-moves player board))
45              (scores (mapcar #'(lambda (move)
46                                  (funcall
47                                   eval-fn
48                                   player
49                                   (make-move move player
50                                              (copy-board board))))
51                              moves))
52              (best (apply #'max scores)))
53         (declare (fixnum best))
54         (elt moves (position best scores)))))
55
56 (eval-when (:compile-toplevel :load-toplevel :execute)
57   (defparameter *weights*
58       (make-array 100 :element-type 'fixnum 
59                   :fill-pointer nil :adjustable nil
60                   :initial-contents
61                   '(0   0   0  0  0  0  0   0  0 0
62                     0 120 -20 20  5  5 20 -20 120 0
63                     0 -20 -40 -5 -5 -5 -5 -40 -20 0
64                     0  20  -5 15  3  3 15  -5  20 0
65                     0   5  -5  3  3  3  3  -5   5 0
66                     0   5  -5  3  3  3  3  -5   5 0
67                     0  20  -5 15  3  3 15  -5  20 0
68                     0 -20 -40 -5 -5 -5 -5 -40 -20 0
69                     0 120 -20 20  5  5 20 -20 120 0
70                     0   0   0  0  0  0  0   0   0 0)))
71   (declaim (type (simple-array fixnum (100)) *weights*))
72 )
73
74 (eval-when (:compile-toplevel :load-toplevel :execute)
75   (setq all-squares 
76     (sort (loop for i from 11 to 88 
77               when (<= 1 (mod i 10) 8) collect i)
78           #'> :key #'(lambda (sq) (elt *weights* sq)))))
79
80
81 (defun weighted-squares (player board)
82   "Sum of the weights of player's squares minus opponent's."
83   (declare (type player player)
84            (type board board))
85   (let ((opp (opponent player)))
86     (loop for i in all-squares
87           when (= (bref board i) player) 
88           sum (aref *weights* i)
89           when (= (bref board i) opp)
90           sum (- (aref *weights* i)))))
91
92 (defconstant winning-value (- most-positive-fixnum 70))
93 (defconstant losing-value  (+ most-negative-fixnum 70))
94
95 (defun final-value (player board)
96   "Is this a win, loss, or draw for player?"
97   (declare (type player player)
98            (type board board))
99   (case (signum (count-difference player board))
100     (-1 losing-value)
101     ( 0 0)
102     (+1 winning-value)))
103
104 (defun final-value-weighted (player board)
105   "Is this a win, loss, or draw for player?"
106   (declare (type player player)
107            (type board board))
108   (let ((diff (count-difference player board)))
109     (case (signum diff)
110       (-1 (+ losing-value diff))
111       ( 0 0)
112       (+1 (+ winning-value diff)))))
113
114 (defun minimax (player board ply eval-fn)
115   "Find the best move, for PLAYER, according to EVAL-FN,
116   searching PLY levels deep and backing up values."
117   (declare (type player player)
118            (type board board)
119            (fixnum ply)
120            (optimize (speed 3) (space 0) (safety 0)))
121   (if (= ply 0)
122       (funcall eval-fn player board)
123       (let ((moves (legal-moves player board)))
124         (if (null moves)
125             (if (any-legal-move? (opponent player) board)
126                 (- (minimax (opponent player) board
127                             (- ply 1) eval-fn))
128                 (final-value player board))
129             (let ((best-move nil)
130                   (best-val nil))
131               (dolist (move moves)
132                 (let* ((board2 (make-move move player
133                                           (copy-board board)))
134                        (val (- (minimax
135                                  (opponent player) board2
136                                  (- ply 1) eval-fn))))
137                   (when (or (null best-val)
138                             (> val best-val))
139                     (setf best-val val)
140                     (setf best-move move))))
141               (values best-val best-move))))))
142
143 (defun minimax-searcher (ply eval-fn)
144   "A strategy that searches PLY levels and then uses EVAL-FN."
145   #'(lambda (player board)
146       (declare (type player player)
147                (type board board))
148       (multiple-value-bind (value move)
149           (minimax player board ply eval-fn) 
150         (declare (ignore value))
151         move)))
152
153 (defun alpha-beta (player board achievable cutoff ply eval-fn)
154   "Find the best move, for PLAYER, according to EVAL-FN,
155   searching PLY levels deep and backing up values,
156   using cutoffs whenever possible."
157   (declare (type player player)
158            (type board board)
159            (fixnum achievable cutoff ply)
160            (optimize (speed 3) (safety 0) (space 0)))
161   (if (= ply 0)
162       (funcall eval-fn player board)
163       (let ((moves (legal-moves player board)))
164         (if (null moves)
165             (if (any-legal-move? (opponent player) board)
166                 (- (alpha-beta (opponent player) board
167                                (- cutoff) (- achievable)
168                                (- ply 1) eval-fn))
169                 (final-value player board))
170           (let ((best-move (first moves)))
171             (declare (type move best-move))
172             (loop for move in moves do
173                   (let* ((board2 (make-move move player
174                                             (copy-board board)))
175                          (val (- (alpha-beta
176                                  (opponent player) board2
177                                  (- cutoff) (- achievable)
178                                  (- ply 1) eval-fn))))
179                   (when (> val achievable)
180                     (setf achievable val)
181                     (setf best-move move)))
182                 until (>= achievable cutoff))
183               (values achievable best-move))))))
184
185 (defun alpha-beta-searcher (depth eval-fn)
186   "A strategy that searches to DEPTH and then uses EVAL-FN."
187   (declare (fixnum depth))
188   #'(lambda (player board)
189       (declare (type board board)
190                (type player player))
191       (multiple-value-bind (value move)
192           (alpha-beta player board losing-value winning-value
193                       depth eval-fn) 
194         (declare (ignore value))
195         move)))
196
197 (defun modified-weighted-squares (player board)
198   "Like WEIGHTED-SQUARES, but don't take off for moving
199   near an occupied corner."
200   (declare (type player player)
201            (type board board)
202            (optimize (speed 3) (safety 0) (space 0)))
203   (let ((w (weighted-squares player board)))
204     (declare (fixnum w))
205     (dolist (corner '(11 18 81 88))
206       (declare (type square corner))
207       (when (not (= (bref board corner) empty))
208         (dolist (c (neighbors corner))
209           (declare (type square c))
210           (when (not (= (bref board c) empty))
211             (incf w (* (- 5 (aref *weights* c))
212                        (if (= (bref board c) player)
213                            +1 -1)))))))
214     w))
215
216 (eval-when (:compile-toplevel :load-toplevel :execute)
217 (let ((neighbor-table (make-array 100 :initial-element nil)))
218   ;; Initialize the neighbor table
219   (dolist (square all-squares)
220     (declare (type square square))
221     (dolist (dir +all-directions+)
222       (declare (type dir dir))
223       (if (valid-p (+ square dir))
224           (push (+ square dir)
225                 (aref neighbor-table square)))))
226
227   (defun neighbors (square)
228     "Return a list of all squares adjacent to a square."
229     (aref neighbor-table square))))
230
231
232 (defun mobility-simple (player board)
233   "The number of moves a player has."
234   (length (legal-moves player board)))
235
236
237
238 (defstruct (node) 
239   (square(missing-argument) :type square)
240   (board (missing-argument) :type board)
241   (value (missing-argument) :type integer))
242
243 (defun alpha-beta-searcher2 (depth eval-fn)
244   "Return a strategy that does A-B search with sorted moves."
245   #'(lambda (player board)
246       (declare (type player player)
247                (type board board))
248       (multiple-value-bind (value node)
249           (alpha-beta2
250             player (make-node :board board
251                               :value (funcall eval-fn player board))
252             losing-value winning-value depth eval-fn)
253         (declare (ignore value))
254         (node-square node))))
255
256 (defun alpha-beta2 (player node achievable cutoff ply eval-fn)
257   "A-B search, sorting moves by eval-fn"
258   ;; Returns two values: achievable-value and move-to-make
259   (declare (fixnum ply)
260            (optimize (speed 3) (space 0) (safety 0)))
261   (if (= ply 0)
262       (values (node-value node) node)
263       (let* ((board (node-board node))
264              (nodes (legal-nodes player board eval-fn)))
265         (if (null nodes)
266             (if (any-legal-move? (opponent player) board)
267                 (values (- (alpha-beta2 (opponent player)
268                                         (negate-value node)
269                                         (- cutoff) (- achievable)
270                                         (- ply 1) eval-fn))
271                         nil)
272                 (values (final-value player board) nil))
273           (let ((best-node (first nodes)))
274               (loop for move in nodes
275                     for val = (- (alpha-beta2
276                                    (opponent player)
277                                    (negate-value move)
278                                    (- cutoff) (- achievable)
279                                    (- ply 1) eval-fn))
280                     do (when (> val achievable)
281                          (setf achievable val)
282                          (setf best-node move))
283                     until (>= achievable cutoff))
284               (values achievable best-node))))))
285
286 (defun negate-value (node)
287   "Set the value of a node to its negative."
288   (declare (fixnum node)
289            (speed 3) (safety 0) (space 0))
290   (setf (node-value node) (- (node-value node)))
291   node)
292
293 (defun legal-nodes (player board eval-fn)
294   "Return a list of legal moves, each one packed into a node."
295   (let ((moves (legal-moves player board)))
296     (sort (map-into
297             moves
298             #'(lambda (move)
299                 (let ((new-board (make-move move player
300                                             (copy-board board))))
301                   (make-node
302                     :square move :board new-board
303                     :value (funcall eval-fn player new-board))))
304             moves)
305           #'> :key #'node-value)))
306
307 (defun alpha-beta3 (player board achievable cutoff ply eval-fn
308                     killer)
309   (declare (type board board)
310            (type player player)
311            (type fixnum achievable cutoff ply)
312            (optimize (speed 3) (space 0) (safety 0)))
313   "A-B search, putting killer move first."
314   (if (= ply 0)
315       (funcall eval-fn player board)
316       (let ((moves (put-first killer (legal-moves player board))))
317         (if (null moves)
318             (if (any-legal-move? (opponent player) board)
319                 (- (alpha-beta3 (opponent player) board
320                                 (- cutoff) (- achievable)
321                                 (- ply 1) eval-fn nil))
322                 (final-value player board))
323             (let ((best-move (first moves))
324                   (new-board (svref *ply-boards* ply))
325                   (killer2 nil)
326                   (killer2-val winning-value))
327               (declare (type move best-move)
328                        (type board new-board)
329                        (type fixnum killer2-val))
330               (loop for move in moves
331                   do (multiple-value-bind (val reply)
332                        (alpha-beta3
333                         (opponent player)
334                         (make-move move player
335                                    (replace-board new-board board))
336                         (- cutoff) (- achievable)
337                         (- ply 1) eval-fn killer2)
338                        (setf val (- val))
339                        (when (> val achievable)
340                          (setq achievable val)
341                          (setq best-move move))
342                        (when (and reply (< val killer2-val))
343                          (setq killer2 reply)
344                          (setq killer2-val val)))
345                   until (>= achievable cutoff))
346               (values achievable best-move))))))
347
348 (defun alpha-beta3w (player board achievable cutoff ply eval-fn
349                     killer)
350   (declare (type board board)
351            (type player player)
352            (type fixnum achievable cutoff ply)
353            (type move killer)
354            (optimize (speed 3) (safety 0) (space 0)))
355   "A-B search, putting killer move first."
356   (if (= ply 0)
357       (funcall eval-fn player board)
358       (let ((moves (put-first killer (legal-moves player board))))
359         (if (null moves)
360             (if (any-legal-move? (opponent player) board)
361                 (- (alpha-beta3 (opponent player) board
362                                 (- cutoff) (- achievable)
363                                 (- ply 1) eval-fn nil))
364                 (final-value-weighted player board))
365             (let ((best-move (first moves))
366                   (new-board (svref *ply-boards* ply))
367                   (killer2 nil)
368                   (killer2-val winning-value))
369               (declare (type move best-move)
370                        (type board new-board)
371                        (type fixnum killer2-val))
372               (loop for move in moves
373                   do (multiple-value-bind (val reply)
374                        (alpha-beta3
375                         (opponent player)
376                         (make-move move player
377                                    (replace-board new-board board))
378                         (- cutoff) (- achievable)
379                         (- ply 1) eval-fn killer2)
380                        (setf val (- val))
381                        (when (> val achievable)
382                          (setq achievable val)
383                          (setq best-move move))
384                        (when (and reply (< val killer2-val))
385                          (setq killer2 reply)
386                          (setq killer2-val val)))
387                   until (>= achievable cutoff))
388               (values achievable best-move))))))
389
390
391 (defun alpha-beta-searcher3 (depth eval-fn)
392   "Return a strategy that does A-B search with killer moves."
393   #'(lambda (player board)
394       (declare (type board board)
395                (type player player))
396       (multiple-value-bind (value move)
397           (alpha-beta3 player board losing-value winning-value
398                        depth eval-fn nil)
399         (declare (ignore value))
400         move)))
401
402 (defun alpha-beta-searcher3w (depth eval-fn)
403   "Return a strategy that does A-B search with killer moves."
404   #'(lambda (player board)
405       (multiple-value-bind (value move)
406           (alpha-beta3w player board losing-value winning-value
407                        depth eval-fn nil)
408         (declare (ignore value))
409         move)))
410
411 (defun put-first (killer moves)
412   "Move the killer move to the front of moves,
413   if the killer move is in fact a legal move."
414   (if (member killer moves)
415       (cons killer (delete killer moves))
416       moves))
417
418 (defun mobility (player board)
419   "Current Mobility is the number of legal moves.
420   Potential mobility is the number of blank squares
421   adjacent to an opponent that are not legal moves.
422   Returns current and potential mobility for player."
423   (declare (type board board)
424            (type player player)
425            (optimize (speed 3) (safety 0) (space 0)))
426   (let ((opp (opponent player))
427         (current 0)    ; player's current mobility
428         (potential 0))                  ; player's potential mobility
429     (declare (type player opp)
430              (type fixnum current potential))
431     (dolist (square all-squares)
432       (declare (type square square))
433       (when (= (bref board square) empty)
434         (cond ((legal-p square player board)
435                (incf current))
436               ((some-neighbors board opp (neighbors square))
437                (incf potential))
438               )))
439     (values current (the fixnum (+ current potential)))))
440
441
442 (defun some-neighbors (board opp neighbors)
443   (declare (type board board)
444            (type player opp)
445            (type cons neighbors)
446            (optimize (speed 3) (safety 0) (space 0)))
447   (block search
448     (dolist (sq neighbors)
449       (declare (type square sq))
450       (when (= (bref board sq) opp)
451         (return-from search t)))
452     (return-from search nil)))
453
454 (defun edge-stability (player board)
455   "Total edge evaluation for player to move on board."
456   (declare (type board board)
457            (type player player)
458            (optimize (speed 3) (safety 0) (space 0))
459   (loop for edge-list in *edge-and-x-lists*
460         sum (aref *edge-table*
461                   (edge-index player board edge-list))))
462
463 (defun iago-eval (player board)
464   "Combine edge-stability, current mobility and
465   potential mobility to arrive at an evaluation."
466   ;; The three factors are multiplied by coefficients
467   ;; that vary by move number:
468   (declare (type board board)
469            (type player player)
470            (optimize (speed 3) (safety 0) (space 0)))
471   (let ((c-edg  (+ 312000 (* 6240 *move-number*)))
472         (c-cur (if (< *move-number* 25)
473                    (+ 50000 (* 2000 *move-number*))
474                  (+ 75000 (* 1000 *move-number*))))
475         (c-pot 20000))
476     (declare (fixnum c-edg c-cur c-pot))
477     (multiple-value-bind (p-cur p-pot)
478         (mobility player board)
479       (multiple-value-bind (o-cur o-pot)
480           (mobility (opponent player) board)
481         ;; Combine the three factors into one sum:
482         (+ (round (* c-edg (edge-stability player board))
483                   32000)
484            (round (* c-cur (- p-cur o-cur))
485                   (+ p-cur o-cur 2))
486            (round (* c-pot (- p-pot o-pot))
487                   (+ p-pot o-pot 2)))))))
488
489
490 ;; Strategy Functions
491
492 (defun iago (depth)
493   "Use an approximation of Iago's evaluation function."
494   (alpha-beta-searcher3 depth #'iago-eval))
495
496 ;; Maximizer (1-ply)
497 (defun mx-df ()
498   (maximizer #'count-difference))
499
500 (defun mx-wt ()
501   (maximizer #'weighted-squares))
502
503 (defun mx-md-wt ()
504   (maximizer #'modified-weighted-squares))
505
506 ;; Minimax-searcher
507
508 (defun mm-df (ply)
509   (minimax-searcher ply #'count-difference))
510
511 (defun mm-wt (ply)
512   (minimax-searcher ply #'weighted-squares))
513
514 (defun mm-md-wt (ply)
515   (minimax-searcher ply #'modified-weighted-squares))
516
517 ;; Alpha-beta3 searcher
518 (defun ab3-df (ply)
519   (alpha-beta-searcher3 ply #'count-difference))
520
521 (defun ab3-wt (ply)
522   (alpha-beta-searcher3 ply #'weighted-squares))
523
524 (defun ab3-md-wt (ply)
525   (alpha-beta-searcher3 ply #'modified-weighted-squares))
526
527
528 (defun ab3w-df (ply)
529   (alpha-beta-searcher3w ply #'count-difference))
530
531 (defun ab3w-wt (ply)
532   (alpha-beta-searcher3w ply #'weighted-squares))
533
534 (defun ab3w-md-wt (ply)
535   (alpha-beta-searcher3w ply #'modified-weighted-squares))
536
537
538 (defun rr (ply n-pairs)
539   (round-robin 
540    (list #'random-strategy (ab3-df ply) (ab3-wt ply) (ab3-md-wt ply) (iago 3)) 
541    n-pairs 
542    10
543    '(random ab3-df ab3-wt ab3-md-wt iago)))
544
545   
546 (defun text-reversi ()
547   "Sets up a text game between player and computer"
548   )
549
550                                           
551