1 #include "chess.h"
2 #include "evaluate.h"
3 #include "data.h"
4 /* last modified 08/03/16 */
5 /*
6  *******************************************************************************
7  *                                                                             *
8  *   Evaluate() is used to evaluate the chess board.  Broadly, it addresses    *
9  *   four (4) distinct areas:  (1) material score which is simply a summing of *
10  *   piece types multiplied by piece values;  (2) pawn scoring which considers *
11  *   placement of pawns and also evaluates passed pawns, particularly in end-  *
12  *   game situations;  (3) piece scoring which evaluates the placement of each *
13  *   piece as well as things like piece mobility;  (4) king safety which       *
14  *   considers the pawn shelter around the king and enemy pieces and how close *
15  *   they are to assist in a king-side attack.                                 *
16  *                                                                             *
17  *******************************************************************************
18  */
Evaluate(TREE * RESTRICT tree,int ply,int wtm,int alpha,int beta)19 int Evaluate(TREE * RESTRICT tree, int ply, int wtm, int alpha, int beta) {
20   PAWN_HASH_ENTRY *ptable;
21   PXOR *pxtable;
22   int score, side, can_win = 3, phase, lscore, cutoff;
23 
24 /*
25  *************************************************************
26  *                                                           *
27  *  First thing we do is if -DSKILL was passed in to the     *
28  *  compiler, we burn some time to slow the search down,     *
29  *  then we fall into the normal evaluation code.            *
30  *                                                           *
31  *************************************************************
32  */
33 #if defined(SKILL)
34   if (skill < 100) {
35     int i, j;
36     for (i = 0; i < burnc[skill / 10] && !abort_search; i++)
37       for (j = 1; j < 10 && !abort_search; j++)
38         burner[j - 1] = burner[j - 1] * burner[j];
39     if (TimeCheck(tree, 1))
40       abort_search = 1;
41   }
42 #endif
43 /*
44  *************************************************************
45  *                                                           *
46  *  First lazy cutoff attempt.  If the material score is way *
47  *  below alpha or way above beta (way above means so far    *
48  *  above it is very unlikely the positional score can bring *
49  *  the total score back into the alpha / beta window) then  *
50  *  we take what is known as a "lazy evaluation exit" and    *
51  *  avoid the computational cost of a full evaluation in a   *
52  *  position where one side is way ahead or behind.          *
53  *                                                           *
54  *************************************************************
55  */
56   cutoff = (TotalPieces(white, occupied) && TotalPieces(black, occupied))
57       ? KNIGHT_VALUE : ROOK_VALUE;
58   lscore = MaterialSTM(wtm);
59   if (lscore + cutoff < alpha)
60     return alpha;
61   if (lscore - cutoff > beta)
62     return beta;
63 /*
64  *************************************************************
65  *                                                           *
66  *  Check for draws where one side seems to be ahead, but    *
67  *  has no actual winning chances.  One simple example is a  *
68  *  king, bishop and rook pawn, with the wrong colored       *
69  *  bishop and the enemy king too close to the promotion     *
70  *  square.                                                  *
71  *                                                           *
72  *  The variable "can_win" uses 2 bits.  If White can        *
73  *  actually win in this position, bit 1 is set.  If Black   *
74  *  can actually win in this position, bit 0 is set.  If     *
75  *  both sides can win, both bits are set.  This is used     *
76  *  later to drag the score closer to a draw score if the    *
77  *  side with the better score can't actually win.           *
78  *                                                           *
79  *  Note that we only set these bits in minimal material     *
80  *  positions (both sides have < 13 points of material       *
81  *  total).  Otherwise we assume normal scoring should       *
82  *  apply.                                                   *
83  *                                                           *
84  *************************************************************
85  */
86   tree->evaluations++;
87   tree->score_mg = 0;
88   tree->score_eg = 0;
89   EvaluateMaterial(tree, wtm);
90   if (TotalPieces(white, occupied) < 13 && TotalPieces(black, occupied) < 13)
91     for (side = black; side <= white; side++)
92       if (!EvaluateWinningChances(tree, side, wtm))
93         can_win ^= (1 << side);
94 /*
95  *************************************************************
96  *                                                           *
97  *  Determine if this position should be evaluated to force  *
98  *  mate (neither side has pawns) or if it should be         *
99  *  evaluated normally.                                      *
100  *                                                           *
101  *  Note the special case of no pawns, one side is ahead in  *
102  *  total material, but the game is a hopeless draw.  KRN vs *
103  *  KR is one example.  If EvaluateWinningChances()          *
104  *  determines that the side with extra material can not     *
105  *  win, the score is pulled closer to a draw although it    *
106  *  can not collapse completely to the drawscore as it is    *
107  *  possible to lose KRB vs KR if the KR side lets the king  *
108  *  get trapped on the edge of the board.                    *
109  *                                                           *
110  *************************************************************
111  */
112   tree->all_pawns = Pawns(black) | Pawns(white);
113   if (!tree->all_pawns) {
114     if (TotalPieces(white, occupied) > 3 || TotalPieces(black, occupied) > 3) {
115       if (Material > 0)
116         EvaluateMate(tree, white);
117       else if (Material < 0)
118         EvaluateMate(tree, black);
119       if (tree->score_eg > DrawScore(1) && !(can_win & 2))
120         tree->score_eg = tree->score_eg / 16;
121       if (tree->score_eg < DrawScore(1) && !(can_win & 1))
122         tree->score_eg = tree->score_eg / 16;
123 #if defined(SKILL)
124       if (skill < 100)
125         tree->score_eg =
126             skill * tree->score_eg / 100 + ((100 -
127                 skill) * PAWN_VALUE * (uint64_t) Random32() /
128             0x100000000ull) / 100;
129 #endif
130       return (wtm) ? tree->score_eg : -tree->score_eg;
131     }
132   }
133 /*
134  *************************************************************
135  *                                                           *
136  *  Now evaluate pawns.  If the pawn hash signature has not  *
137  *  changed from the last entry to Evaluate() then we        *
138  *  already have everything we need in the pawn hash entry.  *
139  *  In this case, we do not need to call EvaluatePawns() at  *
140  *  all.  EvaluatePawns() does all of the analysis for       *
141  *  information specifically regarding only pawns.  In many  *
142  *  cases, it merely records the presence/absence of         *
143  *  positional pawn features because those features also     *
144  *  depends on pieces.                                       *
145  *                                                           *
146  *  Note that anything put into EvaluatePawns() can only     *
147  *  consider the placement of pawns.  Kings or other pieces  *
148  *  can not influence the score because those pieces are not *
149  *  hashed into the pawn hash signature.  Violating this     *
150  *  principle leads to lots of very difficult and            *
151  *  challenging debugging problems.                          *
152  *                                                           *
153  *************************************************************
154  */
155   else {
156     if (PawnHashKey == tree->pawn_score.key) {
157       tree->score_mg += tree->pawn_score.score_mg;
158       tree->score_eg += tree->pawn_score.score_eg;
159     }
160 /*
161  *************************************************************
162  *                                                           *
163  *  First check to see if this position has been handled     *
164  *  before.  If so, we can skip the work saved in the pawn   *
165  *  hash table.                                              *
166  *                                                           *
167  *************************************************************
168  */
169     else {
170       ptable = pawn_hash_table + (PawnHashKey & pawn_hash_mask);
171       pxtable = (PXOR *) & (tree->pawn_score);
172       tree->pawn_score = *ptable;
173       tree->pawn_score.key ^= pxtable->entry[1] ^ pxtable->entry[2];
174       if (tree->pawn_score.key != PawnHashKey) {
175         tree->pawn_score.key = PawnHashKey;
176         tree->pawn_score.score_mg = 0;
177         tree->pawn_score.score_eg = 0;
178         for (side = black; side <= white; side++)
179           EvaluatePawns(tree, side);
180         ptable->key =
181             pxtable->entry[0] ^ pxtable->entry[1] ^ pxtable->entry[2];
182         memcpy((char *) ptable + 8, (char *) &(tree->pawn_score) + 8,
183             sizeof(PAWN_HASH_ENTRY) - 8);
184       }
185       tree->score_mg += tree->pawn_score.score_mg;
186       tree->score_eg += tree->pawn_score.score_eg;
187     }
188 /*
189  *************************************************************
190  *                                                           *
191  *  If there are any passed pawns, first call                *
192  *  EvaluatePassedPawns() to evaluate them.  Then, if one    *
193  *  side has a passed pawn and the other side has no pieces, *
194  *  call EvaluatePassedPawnRaces() to see if the passed pawn *
195  *  can be stopped from promoting.                           *
196  *                                                           *
197  *************************************************************
198  */
199     if (tree->pawn_score.passed[black] || tree->pawn_score.passed[white]) {
200       for (side = black; side <= white; side++)
201         if (tree->pawn_score.passed[side])
202           EvaluatePassedPawns(tree, side, wtm);
203       if ((TotalPieces(white, occupied) == 0 &&
204               tree->pawn_score.passed[black])
205           || (TotalPieces(black, occupied) == 0 &&
206               tree->pawn_score.passed[white]))
207         EvaluatePassedPawnRaces(tree, wtm);
208     }
209   }
210 /*
211  *************************************************************
212  *                                                           *
213  *  Call EvaluateCastling() to evaluate castling potential.  *
214  *   Note we  only do this when that side has not castled at *
215  *  the root.                                                *
216  *                                                           *
217  *************************************************************
218  */
219   for (side = black; side <= white; side++)
220     if (Castle(1, side) > 0)
221       EvaluateCastling(tree, ply, side);
222 /*
223  *************************************************************
224  *                                                           *
225  *  The "dangerous" flag simply indicates whether that side  *
226  *  has enough material to whip up a mating attack if the    *
227  *  other side is careless (Q + minor or better, or RR + two *
228  *  minors or better).                                       *
229  *                                                           *
230  *************************************************************
231  */
232   tree->dangerous[white] = (Queens(white) && TotalPieces(white, occupied) > 9)
233       || (TotalPieces(white, rook) > 1 && TotalPieces(white, occupied) > 15);
234   tree->dangerous[black] = (Queens(black) && TotalPieces(black, occupied) > 9)
235       || (TotalPieces(black, rook) > 1 && TotalPieces(black, occupied) > 15);
236 /*
237  *************************************************************
238  *                                                           *
239  *  Second lazy evaluation test.  We have computed the large *
240  *  positional scores (except for king safety).  If the      *
241  *  score is too far outside the alpha/beta window, we skip  *
242  *  the piece scoring which is the most expensive of all the *
243  *  evaluation terms, and simply use what we have at this    *
244  *  point.                                                   *
245  *                                                           *
246  *************************************************************
247  */
248   phase =
249       Min(62, TotalPieces(white, occupied) + TotalPieces(black, occupied));
250   score = ((tree->score_mg * phase) + (tree->score_eg * (62 - phase))) / 62;
251   lscore = (wtm) ? score : -score;
252   int w_mat = (2 * TotalPieces(white, rook)) + TotalPieces(white,
253       knight) + TotalPieces(white, bishop);
254   int b_mat = (2 * TotalPieces(black, rook)) + TotalPieces(black,
255       knight) + TotalPieces(black, bishop);
256   cutoff = 72 + (w_mat + b_mat) * 8 + abs(w_mat - b_mat) * 16;
257   if (tree->dangerous[white] || tree->dangerous[black])
258     cutoff += 35;
259 /*
260  *************************************************************
261  *                                                           *
262  *  Then evaluate pieces if the lazy eval test fails.        *
263  *                                                           *
264  *  Note:  We MUST evaluate kings last, since their scoring  *
265  *  depends on the tropism scores computed by the other      *
266  *  piece evaluators.  Do NOT try to collapse the following  *
267  *  loops into one loop.  That will break things since it    *
268  *  would violate the kings last rule.  More importantly     *
269  *  there is no benefit as the loops below are unrolled by   *
270  *  the compiler anyway.                                     *
271  *                                                           *
272  *************************************************************
273  */
274   if (lscore + cutoff > alpha && lscore - cutoff < beta) {
275     tree->tropism[white] = 0;
276     tree->tropism[black] = 0;
277     for (side = black; side <= white; side++)
278       if (Knights(side))
279         EvaluateKnights(tree, side);
280     for (side = black; side <= white; side++)
281       if (Bishops(side))
282         EvaluateBishops(tree, side);
283     for (side = black; side <= white; side++)
284       if (Rooks(side))
285         EvaluateRooks(tree, side);
286     for (side = black; side <= white; side++)
287       if (Queens(side))
288         EvaluateQueens(tree, side);
289     for (side = black; side <= white; side++)
290       EvaluateKing(tree, ply, side);
291   }
292 /*
293  *************************************************************
294  *                                                           *
295  *  Caclulate the final score, which is interpolated between *
296  *  the middlegame score and endgame score based on the      *
297  *  material left on the board.                              *
298  *                                                           *
299  *  Adjust the score if one side can't win, but the score    *
300  *  actually favors that side significantly.                 *
301  *                                                           *
302  *************************************************************
303  */
304   score = ((tree->score_mg * phase) + (tree->score_eg * (62 - phase))) / 62;
305   score = EvaluateDraws(tree, ply, can_win, score);
306 #if defined(SKILL)
307   if (skill < 100)
308     score =
309         skill * score / 100 + ((100 -
310             skill) * PAWN_VALUE * (uint64_t) Random32() / 0x100000000ull) /
311         100;
312 #endif
313   return (wtm) ? score : -score;
314 }
315 
316 /* last modified 10/19/15 */
317 /*
318  *******************************************************************************
319  *                                                                             *
320  *  EvaluateBishops() is used to evaluate bishops.                             *
321  *                                                                             *
322  *******************************************************************************
323  */
EvaluateBishops(TREE * RESTRICT tree,int side)324 void EvaluateBishops(TREE * RESTRICT tree, int side) {
325   uint64_t temp, moves;
326   int square, special, i, mobility;
327   int score_eg = 0, score_mg = 0, enemy = Flip(side), tpawns;
328 /*
329  ************************************************************
330  *                                                          *
331  *  First, locate each bishop and add in its piece/square   *
332  *  table score.                                            *
333  *                                                          *
334  ************************************************************
335  */
336   for (temp = Bishops(side); temp; temp &= temp - 1) {
337     square = LSB(temp);
338     score_mg += bval[mg][side][square];
339     score_eg += bval[eg][side][square];
340 /*
341  ************************************************************
342  *                                                          *
343  *  Evaluate for "outposts" which is a bishop that can't be *
344  *  driven off by an enemy pawn, and which is supported by  *
345  *  a friendly pawn.                                        *
346  *                                                          *
347  *  If the enemy has NO minor to take this bishop, then     *
348  *  increase the bonus.                                     *
349  *                                                          *
350  ************************************************************
351  */
352     special = bishop_outpost[side][square];
353     if (special) {
354       if (!(mask_pattacks[enemy][square] & Pawns(enemy))) {
355         if (pawn_attacks[enemy][square] & Pawns(side)) {
356           special += special / 2;
357           if (!Knights(enemy) && !(Color(square) & Bishops(enemy)))
358             special += bishop_outpost[side][square];
359         }
360         score_eg += special;
361         score_mg += special;
362       }
363     }
364 /*
365  ************************************************************
366  *                                                          *
367  *  Next we count the number of friendly pawns on the same  *
368  *  color squares as the bishop.  This is a bad thing since *
369  *  it restricts the bishop's ability to move.  We only do  *
370  *  this if there is only one bishop for this side.         *
371  *                                                          *
372  ************************************************************
373  */
374     if (TotalPieces(side, bishop) == 1) {
375       if (dark_squares & SetMask(square))
376         tpawns = PopCnt(dark_squares & Pawns(side));
377       else
378         tpawns = PopCnt(~dark_squares & Pawns(side));
379       score_mg -= tpawns * bishop_pawns_on_color[mg];
380       score_eg -= tpawns * bishop_pawns_on_color[eg];
381     }
382 /*
383  ************************************************************
384  *                                                          *
385  *  Mobility counts the number of squares the bishop        *
386  *  attacks, excluding squares with friendly pieces, and    *
387  *  weighs each square according to centralization.         *
388  *                                                          *
389  ************************************************************
390  */
391     mobility = BishopMobility(square, OccupiedSquares);
392     if (mobility < 0 && (pawn_attacks[enemy][square] & Pawns(side))
393         && (File(square) == FILEA || File(square) == FILEH))
394       mobility -= 8;
395     score_mg += mobility;
396     score_eg += mobility;
397 /*
398  ************************************************************
399  *                                                          *
400  *  Adjust the tropism count for this piece.                *
401  *                                                          *
402  ************************************************************
403  */
404     if (tree->dangerous[side]) {
405       moves = king_attacks[KingSQ(enemy)];
406       i = ((bishop_attacks[square] & moves) &&
407           ((BishopAttacks(square, OccupiedSquares & ~Queens(side))) & moves))
408           ? 1 : Distance(square, KingSQ(enemy));
409       tree->tropism[side] += king_tropism_b[i];
410     }
411   }
412 /*
413  ************************************************************
414  *                                                          *
415  *  Add a bonus if this side has a pair of bishops, which   *
416  *  can become very strong in open positions.               *
417  *                                                          *
418  ************************************************************
419  */
420   if (TotalPieces(side, bishop) > 1) {
421     score_mg += bishop_pair[mg];
422     score_eg += bishop_pair[eg];
423   }
424 /*
425  ************************************************************
426  *                                                          *
427  *  Check for pawns on both wings, which makes a bishop     *
428  *  even more valuable against an enemy knight              *
429  *                                                          *
430  ************************************************************
431  */
432   else {
433     if (tree->all_pawns & mask_fgh && tree->all_pawns & mask_abc) {
434       score_mg += bishop_wing_pawns[mg];
435       score_eg += bishop_wing_pawns[eg];
436     }
437   }
438   tree->score_mg += sign[side] * score_mg;
439   tree->score_eg += sign[side] * score_eg;
440 }
441 
442 /* last modified 01/03/15 */
443 /*
444  *******************************************************************************
445  *                                                                             *
446  *   EvaluateCastling() is called when "side" has not castled at the root.     *
447  *   Its main purpose is to determine if it has either castled somewhere in    *
448  *   the tree, or else has lost all (or some) castling rights, which reduces   *
449  *   options significantly.                                                    *
450  *                                                                             *
451  *******************************************************************************
452  */
EvaluateCastling(TREE * RESTRICT tree,int ply,int side)453 void EvaluateCastling(TREE * RESTRICT tree, int ply, int side) {
454   int enemy = Flip(side), oq, score_mg = 0;;
455 
456 /*
457  ************************************************************
458  *                                                          *
459  *  If the king castled during the search, we are done and  *
460  *  we leave it to EvaluateKing() to figure out how safe it *
461  *  is.  If it has not castled, we give a significant       *
462  *  penalty if the king moves since that loses all castling *
463  *  rights, otherwise we give a smaller penalty for moving  *
464  *  a rook and giving up castling rights to that side of    *
465  *  the board.  The penalty is always increased if the      *
466  *  opponent has a queen since the position is much more    *
467  *  dangerous.                                              *
468  *                                                          *
469  ************************************************************
470  */
471   oq = (Queens(enemy)) ? 3 : 1;
472   if (Castle(ply, side) != Castle(1, side)) {
473     if (Castle(ply, side) == 0)
474       score_mg -= oq * development_losing_castle;
475     else if (Castle(ply, side) > 0)
476       score_mg -= (oq * development_losing_castle) / 2;
477   } else
478     score_mg -= oq * development_not_castled;
479   tree->score_mg += sign[side] * score_mg;
480 }
481 
482 /* last modified 01/03/15 */
483 /*
484  *******************************************************************************
485  *                                                                             *
486  *   EvaluateDraws() is used to adjust the score based on whether the side     *
487  *   that appears to be better according the computed score can actually win   *
488  *   the game or not.  If the answer is "no" then the score is reduced         *
489  *   significantly to reflect the lack of winning chances.                     *
490  *                                                                             *
491  *******************************************************************************
492  */
EvaluateDraws(TREE * RESTRICT tree,int ply,int can_win,int score)493 int EvaluateDraws(TREE * RESTRICT tree, int ply, int can_win, int score) {
494 /*
495  ************************************************************
496  *                                                          *
497  *  If the ending has only bishops of opposite colors, the  *
498  *  score is pulled closer to a draw.                       *
499  *                                                          *
500  *  If this is a pure BOC ending, it is very drawish unless *
501  *  one side has at least 4 pawns.  More pawns makes it     *
502  *  harder for a bishop and king to stop them all from      *
503  *  advancing.                                              *
504  *                                                          *
505  *  If the following are both true:                         *
506  *                                                          *
507  *    black and white have less than a queen left (pieces   *
508  *    only).                                                *
509  *                                                          *
510  *    both have one bishop and they are opposite colored.   *
511  *                                                          *
512  *  then either                                             *
513  *                                                          *
514  *    (a) both have just one bishop, both have less than 4  *
515  *    pawns or one side has only one more pawn than the     *
516  *    other side then score is divided by 2 with draw score *
517  *    added in; or                                          *
518  *                                                          *
519  *    (b) pieces are equal, then score is reduced by 25%    *
520  *    with draw score added in.                             *
521  *                                                          *
522  ************************************************************
523  */
524   if (TotalPieces(white, occupied) <= 8 && TotalPieces(black, occupied) <= 8) {
525     if (TotalPieces(white, bishop) == 1 && TotalPieces(black, bishop) == 1)
526       if (square_color[LSB(Bishops(black))] !=
527           square_color[LSB(Bishops(white))]) {
528         if (TotalPieces(white, occupied) == 3 &&
529             TotalPieces(black, occupied) == 3 &&
530             ((TotalPieces(white, pawn) < 4 && TotalPieces(black, pawn) < 4)
531                 || Abs(TotalPieces(white, pawn) - TotalPieces(black,
532                         pawn)) < 2))
533           score = score / 2 + DrawScore(1);
534         else if (TotalPieces(white, occupied) == TotalPieces(black, occupied))
535           score = 3 * score / 4 + DrawScore(1);
536       }
537   }
538 /*
539  ************************************************************
540  *                                                          *
541  *  Final score adjustment.  If the score says white is     *
542  *  better, but can_win says white can not win, or if the   *
543  *  score says black is better, but can_win says black can  *
544  *  not win, then we divide the score by 16, and then add   *
545  *  in the draw score.  If the can_win says neither side    *
546  *  can win, we just set the score to draw score and exit.  *
547  *                                                          *
548  ************************************************************
549  */
550   if (can_win != 3) {
551     if (can_win & 1) {
552       if (score > DrawScore(1))
553         score = score / 16 + DrawScore(1);
554     } else if (can_win & 2) {
555       if (score < DrawScore(1))
556         score = score / 16 + DrawScore(1);
557     } else
558       score = DrawScore(1);
559   }
560 /*
561  ************************************************************
562  *                                                          *
563  *  If we are running into the 50-move rule, then start     *
564  *  dragging the score toward draw.  This is the idea of a  *
565  *  "weariness factor" as mentioned by Dave Slate many      *
566  *  times.  This avoids slamming into a draw at move 50 and *
567  *  having to move something quickly, rather than slowly    *
568  *  discovering that the score is dropping and that pushing *
569  *  a pawn or capturing something will cause it to go back  *
570  *  to its correct value a bit more smoothly.               *
571  *                                                          *
572  ************************************************************
573  */
574   if (Reversible(ply) > 80) {
575     int closeness = 101 - Reversible(ply);
576 
577     score = DrawScore(1) + score * closeness / 20;
578   }
579   return score;
580 }
581 
582 /* last modified 01/03/15 */
583 /*
584  *******************************************************************************
585  *                                                                             *
586  *   EvaluateHasOpposition() is used to determine if one king stands in        *
587  *   "opposition" to the other.  If the kings are opposed on the same file or  *
588  *   else are opposed on the same diagonal, then the side not-to-move has the  *
589  *   opposition and the side-to-move must give way.                            *
590  *                                                                             *
591  *******************************************************************************
592  */
EvaluateHasOpposition(int on_move,int king,int enemy_king)593 int EvaluateHasOpposition(int on_move, int king, int enemy_king) {
594   int file_distance, rank_distance;
595 
596   file_distance = FileDistance(king, enemy_king);
597   rank_distance = RankDistance(king, enemy_king);
598   if (rank_distance < 2)
599     return 1;
600   if (on_move) {
601     if (rank_distance & 1)
602       rank_distance--;
603     if (file_distance & 1)
604       file_distance--;
605   }
606   if (!(file_distance & 1) && !(rank_distance & 1))
607     return 1;
608   return 0;
609 }
610 
611 /* last modified 01/03/15 */
612 /*
613  *******************************************************************************
614  *                                                                             *
615  *   EvaluateKing() is used to evaluate a king.                                *
616  *                                                                             *
617  *******************************************************************************
618  */
EvaluateKing(TREE * RESTRICT tree,int ply,int side)619 void EvaluateKing(TREE * RESTRICT tree, int ply, int side) {
620   int score_eg = 0, score_mg = 0, defects;
621   int ksq = KingSQ(side), enemy = Flip(side);
622 
623 /*
624  ************************************************************
625  *                                                          *
626  *  First, check for where the king should be if this is an *
627  *  endgame.  The basic idea is to centralize unless the    *
628  *  king is needed to deal with a passed enemy pawn.        *
629  *                                                          *
630  ************************************************************
631  */
632   score_eg += kval[side][ksq];
633 /*
634  ************************************************************
635  *                                                          *
636  *  Do castle scoring, if the king has castled, the pawns   *
637  *  in front are important.  If not castled yet, the pawns  *
638  *  on the kingside should be preserved for this.           *
639  *                                                          *
640  ************************************************************
641  */
642   if (tree->dangerous[enemy]) {
643     defects = 0;
644     if (Castle(ply, side) <= 0) {
645       if (File(ksq) > FILEE)
646         defects = tree->pawn_score.defects_k[side];
647       else if (File(ksq) < FILED)
648         defects = tree->pawn_score.defects_q[side];
649       else
650         defects = tree->pawn_score.defects_m[side];
651     } else {
652       if (Castle(ply, side) == 3)
653         defects =
654             Min(Min(tree->pawn_score.defects_k[side],
655                 tree->pawn_score.defects_m[side]),
656             tree->pawn_score.defects_q[side]);
657       else if (Castle(ply, side) == 1)
658         defects =
659             Min(tree->pawn_score.defects_k[side],
660             tree->pawn_score.defects_m[side]);
661       else
662         defects =
663             Min(tree->pawn_score.defects_q[side],
664             tree->pawn_score.defects_m[side]);
665       if (defects < 3)
666         defects = 3;
667     }
668 /*
669  ************************************************************
670  *                                                          *
671  *  Fold in the king tropism and king pawn shelter scores   *
672  *  together.                                               *
673  *                                                          *
674  ************************************************************
675  */
676     if (tree->tropism[enemy] < 0)
677       tree->tropism[enemy] = 0;
678     else if (tree->tropism[enemy] > 15)
679       tree->tropism[enemy] = 15;
680     if (defects > 15)
681       defects = 15;
682     score_mg -= king_safety[defects][tree->tropism[enemy]];
683   }
684   tree->score_mg += sign[side] * score_mg;
685   tree->score_eg += sign[side] * score_eg;
686 }
687 
688 /* last modified 01/03/15 */
689 /*
690  *******************************************************************************
691  *                                                                             *
692  *   EvaluateKingsFile computes defects for a file, based on whether the file  *
693  *   is open or half-open.  If there are friendly pawns still on the file,     *
694  *   they are penalized for advancing in front of the king.                    *
695  *                                                                             *
696  *******************************************************************************
697  */
EvaluateKingsFile(TREE * RESTRICT tree,int side,int first,int last)698 int EvaluateKingsFile(TREE * RESTRICT tree, int side, int first, int last) {
699   int defects = 0, file, enemy = Flip(side);
700 
701   for (file = first; file <= last; file++)
702     if (!(file_mask[file] & tree->all_pawns))
703       defects += open_file[file];
704     else {
705       if (!(file_mask[file] & Pawns(enemy)))
706         defects += half_open_file[file] / 2;
707       else
708         defects +=
709             pawn_defects[side][Rank(MostAdvanced(enemy,
710                     file_mask[file] & Pawns(enemy)))];
711       if (!(file_mask[file] & Pawns(side)))
712         defects += half_open_file[file];
713       else if (!(Pawns(side) & SetMask(sqflip[side][A2] + file))) {
714         defects++;
715         if (!(Pawns(side) & SetMask(sqflip[side][A3] + file)))
716           defects++;
717       }
718     }
719   return defects;
720 }
721 
722 /* last modified 10/19/15 */
723 /*
724  *******************************************************************************
725  *                                                                             *
726  *   EvaluateKnights() is used to evaluate knights.                            *
727  *                                                                             *
728  *******************************************************************************
729  */
EvaluateKnights(TREE * RESTRICT tree,int side)730 void EvaluateKnights(TREE * RESTRICT tree, int side) {
731   uint64_t temp;
732   int square, special, i, score_eg = 0, score_mg = 0, enemy = Flip(side);
733 
734 /*
735  ************************************************************
736  *                                                          *
737  *  First fold in centralization score from the piece/      *
738  *  square table "nval".                                    *
739  *                                                          *
740  ************************************************************
741  */
742   for (temp = Knights(side); temp; temp &= temp - 1) {
743     square = LSB(temp);
744     score_mg += nval[mg][side][square];
745     score_eg += nval[eg][side][square];
746 /*
747  ************************************************************
748  *                                                          *
749  *  Evaluate for "outposts" which is a knight that can't    *
750  *  be driven off by an enemy pawn, and which is supported  *
751  *  by a friendly pawn.                                     *
752  *                                                          *
753  *  If the enemy has NO minor to take this knight, then     *
754  *  increase the bonus.                                     *
755  *                                                          *
756  ************************************************************
757  */
758     special = knight_outpost[side][square];
759     if (special && !(mask_pattacks[enemy][square] & Pawns(enemy))) {
760       if (pawn_attacks[enemy][square] & Pawns(side)) {
761         special += special / 2;
762         if (!Knights(enemy) && !(Color(square) & Bishops(enemy)))
763           special += knight_outpost[side][square];
764       }
765       score_eg += special;
766       score_mg += special;
767     }
768 /*
769  ************************************************************
770  *                                                          *
771  *  Adjust the tropism count for this piece.                *
772  *                                                          *
773  ************************************************************
774  */
775     if (tree->dangerous[side]) {
776       i = Distance(square, KingSQ(enemy));
777       tree->tropism[side] += king_tropism_n[i];
778     }
779   }
780   tree->score_mg += sign[side] * score_mg;
781   tree->score_eg += sign[side] * score_eg;
782 }
783 
784 /* last modified 03/30/15 */
785 /*
786  *******************************************************************************
787  *                                                                             *
788  *   EvaluateMate() is used to evaluate positions where neither side has pawns *
789  *   and one side has enough material to force checkmate.  It simply trys to   *
790  *   force the losing king to the edge of the board, and then to the corner    *
791  *   where mates are easier to find.                                           *
792  *                                                                             *
793  *******************************************************************************
794  */
EvaluateMate(TREE * RESTRICT tree,int side)795 void EvaluateMate(TREE * RESTRICT tree, int side) {
796   int mate_score = 0, enemy = Flip(side);
797 
798 /*
799  ************************************************************
800  *                                                          *
801  *  If the winning side has a bishop + knight and the other *
802  *  side has no pieces or pawns, then use the special       *
803  *  bishop_knight scoring board for the losing king to      *
804  *  force it to the right corner for mate.                  *
805  *                                                          *
806  ************************************************************
807  */
808   if (!TotalPieces(enemy, occupied) && TotalPieces(side, bishop) == 1 &&
809       TotalPieces(side, knight) == 1) {
810     if (dark_squares & Bishops(side))
811       mate_score = b_n_mate_dark_squares[KingSQ(enemy)];
812     else
813       mate_score = b_n_mate_light_squares[KingSQ(enemy)];
814   }
815 /*
816  ************************************************************
817  *                                                          *
818  *  The winning side has to force the losing king to the    *
819  *  edge of the board.                                      *
820  *                                                          *
821  ************************************************************
822  */
823   else
824     mate_score = mate[KingSQ(enemy)];
825 /*
826  ************************************************************
827  *                                                          *
828  *  And for either, it is important to bring the winning    *
829  *  king to help force mate.                                *
830  *                                                          *
831  ************************************************************
832  */
833   mate_score -= Distance(KingSQ(side), KingSQ(enemy)) * king_king_tropism;
834   tree->score_eg += sign[side] * mate_score;
835 }
836 
837 /* last modified 10/19/15 */
838 /*
839  *******************************************************************************
840  *                                                                             *
841  *  EvaluateMaterial() is used to evaluate material on the board.  It really   *
842  *  accomplishes detecting cases where one side has made a 'bad trade' as the  *
843  *  comments below show.                                                       *
844  *                                                                             *
845  *******************************************************************************
846  */
EvaluateMaterial(TREE * RESTRICT tree,int wtm)847 void EvaluateMaterial(TREE * RESTRICT tree, int wtm) {
848   int score_mg, score_eg, majors, minors;
849 
850 /*
851  *************************************************************
852  *                                                           *
853  *  We start with the raw Material balance for the current   *
854  *  position, then adjust this with a small bonus for the    *
855  *  side on move.                                            *
856  *                                                           *
857  *************************************************************
858  */
859   score_mg = Material + ((wtm) ? wtm_bonus[mg] : -wtm_bonus[mg]);
860   score_eg = Material + ((wtm) ? wtm_bonus[eg] : -wtm_bonus[eg]);
861 /*
862  *************************************************************
863  *                                                           *
864  *  test 1.  if Majors or Minors are not balanced, then if   *
865  *  one side is only an exchange up or down, we give a       *
866  *  penalty to the side that is an exchange down, but not as *
867  *  big a penalty as the bad trade case below.               *
868  *                                                           *
869  *  test 2.  if Majors or Minors are not balanced, then if   *
870  *  one side has more piece material points than the other   *
871  *  (using normal piece values of 3, 3, 5, 9 for N, B, R     *
872  *  and Q) then the side that is behind in piece material    *
873  *  gets a penalty.                                          *
874  *                                                           *
875  *************************************************************
876  */
877   majors =
878       TotalPieces(white, rook) + 2 * TotalPieces(white,
879       queen) - TotalPieces(black, rook) - 2 * TotalPieces(black, queen);
880   minors =
881       TotalPieces(white, knight) + TotalPieces(white,
882       bishop) - TotalPieces(black, knight) - TotalPieces(black, bishop);
883   if (majors || minors) {
884     if (Abs(TotalPieces(white, occupied) - TotalPieces(black, occupied)) != 2
885         && TotalPieces(white, occupied) - TotalPieces(black, occupied) != 0) {
886       score_mg +=
887           Sign(TotalPieces(white, occupied) - TotalPieces(black,
888               occupied)) * bad_trade;
889       score_eg +=
890           Sign(TotalPieces(white, occupied) - TotalPieces(black,
891               occupied)) * bad_trade;
892     }
893   }
894   tree->score_mg += score_mg;
895   tree->score_eg += score_eg;
896 }
897 
898 /* last modified 11/27/15 */
899 /*
900  *******************************************************************************
901  *                                                                             *
902  *   EvaluatePassedPawns() is used to evaluate passed pawns and the danger     *
903  *   they produce.  This code considers pieces as well, so it MUST NOT be done *
904  *   in the normal EvaluatePawns() code since that hashes information based    *
905  *   only on the position of pawns.                                            *
906  *                                                                             *
907  *   This is a significant rewrite of passed pawn evaluation, with the primary *
908  *   change being to collect the passed pawn scoring into one place, rather    *
909  *   than have it scattered around all over the place.  One example is the old *
910  *   rook_behind_passed_pawn scoring term that was done in rook scoring.  It   *
911  *   is now done here along with other passed pawn terms such as blockaded and *
912  *   the ability to advance or not.                                            *
913  *                                                                             *
914  *******************************************************************************
915  */
EvaluatePassedPawns(TREE * RESTRICT tree,int side,int wtm)916 void EvaluatePassedPawns(TREE * RESTRICT tree, int side, int wtm) {
917   uint64_t behind, forward, backward, attacked, defended, thispawn;
918   int file, square, score, score_mg = 0, score_eg = 0, next_sq;
919   int pawns, rank, mg_base, eg_base, bonus, enemy = Flip(side);
920   uint64_t fsliders = Queens(side) | Rooks(side);
921   uint64_t esliders = Queens(enemy) | Rooks(enemy);
922 
923 /*
924  ************************************************************
925  *                                                          *
926  *  Initialize.  The base value "passed_pawn[rank]" is      *
927  *  almost the "square" of the rank.  That got a bit too    *
928  *  big, so a hand-tuned set of values, one per rank,       *
929  *  proved to be a better value.                            *
930  *                                                          *
931  ************************************************************
932  */
933   for (pawns = tree->pawn_score.passed[side]; pawns; pawns &= pawns - 1) {
934     file = LSB8Bit(pawns);
935     thispawn = Pawns(side) & file_mask[file];
936     if (thispawn) {
937       square = MostAdvanced(side, thispawn);
938       rank = rankflip[side][Rank(square)];
939       score = passed_pawn[rank];
940 /*
941  ************************************************************
942  *                                                          *
943  *  For endgame only, we add in a bonus based on how close  *
944  *  our king is to this pawn and a penalty based on how     *
945  *  close the enemy king is.  We also try to keep our king  *
946  *  ahead of the pawn so it can escort it to promotion.  We *
947  *  only do this for passed pawns whose base score value is *
948  *  greater than zero (ie pawns on ranks 4-7 since those    *
949  *  are the ones threatening to become a major problem.)    *
950  *  Also, if you happen to think that a small bonus for a   *
951  *  passed pawn on the 3rd rank might be useful, consider   *
952  *  speed.  If the 3rd rank score is non-zero, that will    *
953  *  trigger a significant amount of work below.  In testing *
954  *  the additional cost more than offset the gain and so it *
955  *  is basically ignored unless rank > 3.                   *
956  *                                                          *
957  ************************************************************
958  */
959       if (score) {
960         mg_base = score * passed_pawn_base[mg];
961         eg_base = score * passed_pawn_base[eg];
962         next_sq = square + direction[side];
963         eg_base +=
964             Distance(KingSQ(enemy),
965             next_sq) * 2 * score - Distance(KingSQ(side), next_sq) * score;
966         if (rank < RANK7)
967           eg_base -=
968               Distance(KingSQ(side), next_sq + direction[side]) * score / 2;
969 /*
970  ************************************************************
971  *                                                          *
972  *  If the pawn is not blockaded, we need to see whether it *
973  *  can actually advance or not.  Note that this directly   *
974  *  gives a bonus for blockading a passed pawn since the    *
975  *  mobility evaluation below will not be applied when the  *
976  *  pawn is blockaded by any piece.                         *
977  *                                                          *
978  *  Step one is to determine if the squares in front of the *
979  *  pawn are attacked by the enemy.  If not, we add in a    *
980  *  significant score bonus.  If some are attacked, we look *
981  *  to see if at least the square directly in front of the  *
982  *  pawn is not attacked so that we can advance one square, *
983  *  anyway.  This gets a smaller score bonus.               *
984  *                                                          *
985  ************************************************************
986  */
987         if (!(OccupiedSquares & SetMask(next_sq))) {
988           bonus = 0;
989           if (Pawns(side) & pawn_attacks[enemy][next_sq])
990             bonus = passed_pawn_free_advance;
991           else {
992             attacked = 0;
993             forward = (side) ? plus8dir[square] : minus8dir[square];
994             backward = (side) ? minus8dir[square] : plus8dir[square];
995             if ((behind = backward & esliders) &&
996                 (FileAttacks(square) & behind))
997               attacked = forward;
998             else
999               attacked = Attacked(tree, enemy, forward);
1000             if (!attacked)
1001               bonus = passed_pawn_free_advance;
1002             else if (!(attacked & SetMask(next_sq)))
1003               bonus = passed_pawn_free_advance_1;
1004 /*
1005  ************************************************************
1006  *                                                          *
1007  *  Step two is to determine if the squares in front of the *
1008  *  pawn are are defended by the friendly side.  If all are *
1009  *  defended (such as with a rook or queen behind the pawn  *
1010  *  or the king in front and to one side of the pawn, then  *
1011  *  we give a bonus (but smaller than the previous cases).  *
1012  *  As a last resort, if we at least defend the square in   *
1013  *  front of the pawn, we give a small bonus.               *
1014  *                                                          *
1015  ************************************************************
1016  */
1017             if ((behind = backward & fsliders) &&
1018                 (FileAttacks(square) & behind))
1019               defended = forward;
1020             else
1021               defended = Attacked(tree, side, forward);
1022             if (defended == forward)
1023               bonus += passed_pawn_defended;
1024             else if (defended & SetMask(next_sq))
1025               bonus += passed_pawn_defended_1;
1026           }
1027 /*
1028  ************************************************************
1029  *                                                          *
1030  *  Fold in the bonus for this pawn and move on to the next *
1031  *  (if there is one).  Note that the bonus computed above  *
1032  *  is multiplied by the base passed pawn score for this    *
1033  *  particular rank.                                        *
1034  *                                                          *
1035  ************************************************************
1036  */
1037           mg_base += bonus * score;
1038           eg_base += bonus * score;
1039         }
1040         score_mg += mg_base;
1041         score_eg += eg_base;
1042       } else
1043         score_eg += 4;
1044     }
1045   }
1046 /*
1047  ************************************************************
1048  *                                                          *
1049  *  All pawns done, add score to the two evaluation values  *
1050  *  and return.                                             *
1051  *                                                          *
1052  ************************************************************
1053  */
1054   tree->score_mg += sign[side] * score_mg;
1055   tree->score_eg += sign[side] * score_eg;
1056 }
1057 
1058 /* last modified 11/27/15 */
1059 /*
1060  *******************************************************************************
1061  *                                                                             *
1062  *   EvaluatePassedPawnRaces() is used to evaluate passed pawns when one       *
1063  *   side has passed pawns and the other side (or neither) has pieces.  In     *
1064  *   such a case, the critical question is can the defending king stop the     *
1065  *   pawn from queening or is it too far away?  If only one side has pawns     *
1066  *   that can "run" then the situation is simple.  When both sides have pawns  *
1067  *   that can "run" it becomes more complex as it then becomes necessary to    *
1068  *   see if one side can use a forced king move to stop the other side, while  *
1069  *   the other side doesn't have the same ability to stop ours.                *
1070  *                                                                             *
1071  *   In the case of king and pawn endings with exactly one pawn, the simple    *
1072  *   evaluation rules are used:  if the king is two squares in front of the    *
1073  *   pawn then it is a win, if the king is one one square in front with the    *
1074  *   opposition, then it is a win,  if the king is on the 6th rank with the    *
1075  *   pawn close by, it is a win.  Rook pawns are handled separately and are    *
1076  *   more difficult to queen because the king can get trapped in front of the  *
1077  *   pawn blocking promotion.                                                  *
1078  *                                                                             *
1079  *******************************************************************************
1080  */
EvaluatePassedPawnRaces(TREE * RESTRICT tree,int wtm)1081 void EvaluatePassedPawnRaces(TREE * RESTRICT tree, int wtm) {
1082   uint64_t pawns, thispawn;
1083   int file, square, queen_distance, pawnsq, passed, side, enemy;
1084   int queener[2] = { 8, 8 };
1085 /*
1086  ************************************************************
1087  *                                                          *
1088  *  Check to see if side has one pawn and neither side has  *
1089  *  any pieces.  If so, use the simple pawn evaluation      *
1090  *  logic.                                                  *
1091  *                                                          *
1092  ************************************************************
1093  */
1094   for (side = black; side <= white; side++) {
1095     enemy = Flip(side);
1096     if (Pawns(side) && !Pawns(enemy) && TotalPieces(white, occupied) == 0 &&
1097         TotalPieces(black, occupied) == 0) {
1098       for (pawns = Pawns(side); pawns; pawns &= pawns - 1) {
1099         pawnsq = LSB(pawns);
1100 /*
1101  ************************************************************
1102  *                                                          *
1103  *  King must be in front of the pawn or we go no further.  *
1104  *                                                          *
1105  ************************************************************
1106  */
1107         if (sign[side] * Rank(KingSQ(side)) <= sign[side] * Rank(pawnsq))
1108           continue;
1109 /*
1110  ************************************************************
1111  *                                                          *
1112  *  First a special case.  If this is a rook pawn, then the *
1113  *  king must be on the adjacent file, and be closer to the *
1114  *  queening square than the opposing king.                 *
1115  *                                                          *
1116  ************************************************************
1117  */
1118         if (File(pawnsq) == FILEA) {
1119           if (File(KingSQ(side)) == FILEB &&
1120               Distance(KingSQ(side),
1121                   sqflip[side][A8]) < Distance(KingSQ(enemy),
1122                   sqflip[side][A8])) {
1123             tree->score_eg += sign[side] * pawn_can_promote;
1124             return;
1125           }
1126           continue;
1127         } else if (File(pawnsq) == FILEH) {
1128           if (File(KingSQ(side)) == FILEG &&
1129               Distance(KingSQ(side),
1130                   sqflip[side][H8]) < Distance(KingSQ(enemy),
1131                   sqflip[side][H8])) {
1132             tree->score_eg += sign[side] * pawn_can_promote;
1133             return;
1134           }
1135           continue;
1136         }
1137 /*
1138  ************************************************************
1139  *                                                          *
1140  *  If king is two squares in front of the pawn then it's a *
1141  *  win immediately.  If the king is on the 6th rank and    *
1142  *  closer to the pawn than the opposing king, it's also a  *
1143  *  win.                                                    *
1144  *                                                          *
1145  ************************************************************
1146  */
1147         if (Distance(KingSQ(side), pawnsq) < Distance(KingSQ(enemy), pawnsq)) {
1148           if (sign[side] * Rank(KingSQ(side)) >
1149               sign[side] * (Rank(pawnsq) - 1 + 2 * side)) {
1150             tree->score_eg += sign[side] * pawn_can_promote;
1151             return;
1152           }
1153           if (Rank(KingSQ(side)) == rank6[side]) {
1154             tree->score_eg += sign[side] * pawn_can_promote;
1155             return;
1156           }
1157 /*
1158  ************************************************************
1159  *                                                          *
1160  *  Last chance:  if the king is one square in front of the *
1161  *  pawn and has the opposition, then it's still a win.     *
1162  *                                                          *
1163  ************************************************************
1164  */
1165           if (Rank(KingSQ(side)) == Rank(pawnsq) - 1 + 2 * side &&
1166               EvaluateHasOpposition(wtm == side, KingSQ(side),
1167                   KingSQ(enemy))) {
1168             tree->score_eg += sign[side] * pawn_can_promote;
1169             return;
1170           }
1171         }
1172       }
1173     }
1174 /*
1175  ************************************************************
1176  *                                                          *
1177  *  Check to see if enemy is out of pieces and stm has      *
1178  *  passed pawns.  If so, see if any of these passed pawns  *
1179  *  can outrun the defending king and promote.              *
1180  *                                                          *
1181  ************************************************************
1182  */
1183     if (TotalPieces(enemy, occupied) == 0 && tree->pawn_score.passed[side]) {
1184       passed = tree->pawn_score.passed[side];
1185       for (; passed; passed &= passed - 1) {
1186         file = LSB8Bit(passed);
1187         thispawn = Pawns(side) & file_mask[file];
1188         if (thispawn) {
1189           square = MostAdvanced(side, thispawn);
1190           if (!(pawn_race[side][wtm][square] & Kings(enemy))) {
1191             queen_distance = Abs(rank8[side] - Rank(square));
1192             if (Kings(side) & ((side) ? plus8dir[square] : minus8dir[square])) {
1193               if (file == FILEA || file == FILEH)
1194                 queen_distance = 99;
1195               queen_distance++;
1196             }
1197             if (Rank(square) == rank2[side])
1198               queen_distance--;
1199             if (queen_distance < queener[side])
1200               queener[side] = queen_distance;
1201           }
1202         }
1203       }
1204     }
1205   }
1206 /*
1207  ************************************************************
1208  *                                                          *
1209  *  Now that we know which pawns can outrun the kings for   *
1210  *  each side, we need to do determine if one side queens   *
1211  *  before the other.  If so, that side wins.  If they      *
1212  *  queen at the same time, then we will have to rely on    *
1213  *  the search to handle queening with check or queening    *
1214  *  and attacking the opponent's queening square.           *
1215  *                                                          *
1216  ************************************************************
1217  */
1218   if (queener[white] < queener[black])
1219     tree->score_eg += pawn_can_promote + (5 - queener[white]) * 10;
1220   else if (queener[black] < queener[white])
1221     tree->score_eg -= pawn_can_promote + (5 - queener[black]) * 10;
1222 }
1223 
1224 /* last modified 11/27/15 */
1225 /*
1226  *******************************************************************************
1227  *                                                                             *
1228  *   EvaluatePawns() is used to evaluate pawns.  It evaluates pawns for only   *
1229  *   one side, and fills in the pawn hash entry information.  It requires two  *
1230  *   calls to evaluate all pawns on the board.  Comments below indicate the    *
1231  *   particular pawn structure features that are evaluated.                    *
1232  *                                                                             *
1233  *   This procedure also flags which pawns are passed, since this is scored in *
1234  *   another part of the evaluation because that includes piece information    *
1235  *   which can not be used here since the pawn hash signature does not include *
1236  *   piece information of any kind.                                            *
1237  *                                                                             *
1238  *   Note that a pawn is not penalized for two different reasons.  If it is    *
1239  *   isolated, it is not backward.  Etc.  This simplifies evaluation tuning    *
1240  *   not to mention eliminating the overlap and interaction that was happening *
1241  *   previously when multiple penalties could be applied.                      *
1242  *                                                                             *
1243  *******************************************************************************
1244  */
EvaluatePawns(TREE * RESTRICT tree,int side)1245 void EvaluatePawns(TREE * RESTRICT tree, int side) {
1246   uint64_t pawns, attackers, defenders;
1247   uint64_t doubled, supported, connected, passed, backward;
1248   int square, file, rank, score_eg = 0, score_mg = 0, enemy = Flip(side);
1249   unsigned int isolated, pawn_files = 0;
1250 
1251 /*
1252  ************************************************************
1253  *                                                          *
1254  *  Loop through all pawns for this side.                   *
1255  *                                                          *
1256  ************************************************************
1257  */
1258   tree->pawn_score.passed[side] = 0;
1259   for (pawns = Pawns(side); pawns; pawns &= pawns - 1) {
1260     square = LSB(pawns);
1261     file = File(square);
1262     rank = rankflip[side][Rank(square)];
1263     pawn_files |= 1 << file;
1264 /*
1265  ************************************************************
1266  *                                                          *
1267  *  Evaluate pawn advances.  Center pawns are encouraged to *
1268  *  occupy central squares, edge pawns are penalized on all *
1269  *  edge squares to encourage capture toward the center,    *
1270  *  the rest are neutral.                                   *
1271  *                                                          *
1272  ************************************************************
1273  */
1274     score_mg += pval[side][square];
1275 /*
1276  ************************************************************
1277  *                                                          *
1278  *  Evaluate isolated pawns, which are penalized based on   *
1279  *  which file they occupy.                                 *
1280  *                                                          *
1281  ************************************************************
1282  */
1283     isolated = !(Pawns(side) & mask_pawn_isolated[square]);
1284     if (isolated) {
1285       score_mg -= pawn_isolated[mg][file];
1286       score_eg -= pawn_isolated[eg][file];
1287     }
1288 /*
1289  ************************************************************
1290  *                                                          *
1291  *  Evaluate unsupported pawns, which provide a target      *
1292  *  since they are undefended by a pawn.  We exclude pawns  *
1293  *  that are isolated since they have already been given a  *
1294  *  penalty.                                                *
1295  *                                                          *
1296  ************************************************************
1297  */
1298     supported = Pawns(side) & pawn_attacks[enemy][square];
1299     if (!isolated && !supported) {
1300       score_mg += pawn_unsupported[mg];
1301       score_eg += pawn_unsupported[eg];
1302     }
1303 /*
1304  ************************************************************
1305  *                                                          *
1306  *  Evaluate doubled pawns.  If there are other pawns on    *
1307  *  this file in front of this pawn, penalize this pawn.    *
1308  *  Note that this will NOT penalize both pawns, just the   *
1309  *  most rearward one that is really almost worthless.      *
1310  *                                                          *
1311  *  The farther apart two doubled pawns (same file) are,    *
1312  *  the less weak they are, so the penalty is reduced as    *
1313  *  this distance increases.                                *
1314  *                                                          *
1315  ************************************************************
1316  */
1317     doubled = Pawns(side) & ((side) ? plus8dir[square] : minus8dir[square]);
1318     if (doubled) {
1319       score_mg -=
1320           pawn_doubled[mg][file] / RankDistance(square, MostAdvanced(side,
1321               doubled));
1322       score_eg -=
1323           pawn_doubled[eg][file] / RankDistance(square, MostAdvanced(side,
1324               doubled));
1325     }
1326 /*
1327  ************************************************************
1328  *                                                          *
1329  *  Test the pawn to see if it is connected to a neighbor   *
1330  *  which makes it easier to defend.                        *
1331  *                                                          *
1332  ************************************************************
1333  */
1334     connected = Pawns(side) & mask_pawn_connected[side][square];
1335     if (connected) {
1336       score_mg += pawn_connected[mg][rank][file];
1337       score_eg += pawn_connected[eg][rank][file];
1338     }
1339 /*
1340  ************************************************************
1341  *                                                          *
1342  *  Flag passed pawns for use later when we finally call    *
1343  *  EvaluatePassedPawns.                                    *
1344  *                                                          *
1345  ************************************************************
1346  */
1347     passed = !(Pawns(enemy) & mask_passed[side][square]);
1348     if (passed)
1349       tree->pawn_score.passed[side] |= 1 << file;
1350 /*
1351  ************************************************************
1352  *                                                          *
1353  *  Test the pawn to see if it is backward which makes it a *
1354  *  target that ties down pieces to defend it.              *
1355  *                                                          *
1356  ************************************************************
1357  */
1358     backward = 0;
1359     if (!(passed | isolated | connected | (Pawns(side) &
1360                 mask_pattacks[side][square]) | (Pawns(enemy) &
1361                 PawnAttacks(side, square))))
1362       backward = Pawns(enemy) & PawnAttacks(side, square + direction[side]);
1363     if (backward) {
1364       score_mg -= pawn_backward[mg][file];
1365       score_eg -= pawn_backward[eg][file];
1366     }
1367 /*
1368  ************************************************************
1369  *                                                          *
1370  *  Determine if this pawn is a candidate passed pawn,      *
1371  *  which is a pawn on a file with no enemy pawns in front  *
1372  *  of it, and if it advances until it contacts an enemy    *
1373  *  pawn, and it is defended at least as many times as it   *
1374  *  is attacked when it reaches that pawn, then it will end *
1375  *  up passed.                                              *
1376  *                                                          *
1377  ************************************************************
1378  */
1379     if (!(passed | backward | isolated) &&
1380         !(Pawns(enemy) & ((side) ? plus8dir[square] : minus8dir[square]))) {
1381       defenders = mask_pattacks[side][square + direction[side]] & Pawns(side);
1382       attackers = mask_pattacks[enemy][square] & Pawns(enemy);
1383       if (PopCnt(defenders) >= PopCnt(attackers)) {
1384         score_mg += passed_pawn_candidate[mg][rank];
1385         score_eg += passed_pawn_candidate[eg][rank];
1386       }
1387     }
1388   }
1389 /*
1390  ************************************************************
1391  *                                                          *
1392  *  Give a bonus for distance between left-most pawn and    *
1393  *  right-most pawn.  The idea is that the wider the gap    *
1394  *  between the pawns, the harder they are for a lone king  *
1395  *  to control in the endgame.  Botvinnik referred to this  *
1396  *  concept as "trousers" (pants with two legs, the farther *
1397  *  the legs are apart, the better for the side with those  *
1398  *  pawns).                                                 *
1399  *                                                          *
1400  ************************************************************
1401  */
1402   score_eg += pawn_file_width * (MSB8Bit(pawn_files) - LSB8Bit(pawn_files));
1403 /*
1404  ************************************************************
1405  *                                                          *
1406  *  Evaluate king safety.                                   *
1407  *                                                          *
1408  *  This uses the function EvaluateKingsFile() and looks at *
1409  *  three possible positions for the king, either castled   *
1410  *  kingside, queenside or else standing on the d or e file *
1411  *  stuck in the middle.  This essentially is about the     *
1412  *  pawns in front of the king and what kind of "shelter"   *
1413  *  they provide for the king during the middlegame.        *
1414  *                                                          *
1415  ************************************************************
1416  */
1417   tree->pawn_score.defects_q[side] =
1418       EvaluateKingsFile(tree, side, FILEA, FILEC);
1419   tree->pawn_score.defects_m[side] =
1420       EvaluateKingsFile(tree, side, FILEC, FILEF);
1421   tree->pawn_score.defects_k[side] =
1422       EvaluateKingsFile(tree, side, FILEF, FILEH);
1423 /*
1424  ************************************************************
1425  *                                                          *
1426  *  Done.  Add mg/eg scores to final result (sign-corrected *
1427  *  so that black = -, white = +) and return.               *
1428  *                                                          *
1429  ************************************************************
1430  */
1431   tree->pawn_score.score_mg += sign[side] * score_mg;
1432   tree->pawn_score.score_eg += sign[side] * score_eg;
1433 }
1434 
1435 /* last modified 10/19/15 */
1436 /*
1437  *******************************************************************************
1438  *                                                                             *
1439  *   EvaluateQueens() is used to evaluate queens.                              *
1440  *                                                                             *
1441  *******************************************************************************
1442  */
EvaluateQueens(TREE * RESTRICT tree,int side)1443 void EvaluateQueens(TREE * RESTRICT tree, int side) {
1444   uint64_t temp;
1445   int square, i, score_mg = 0, score_eg = 0, enemy = Flip(side);
1446 
1447 /*
1448  ************************************************************
1449  *                                                          *
1450  *  First locate each queen and obtain it's centralization  *
1451  *  score from the static piece/square table for queens.    *
1452  *                                                          *
1453  ************************************************************
1454  */
1455   for (temp = Queens(side); temp; temp &= temp - 1) {
1456     square = LSB(temp);
1457 /*
1458  ************************************************************
1459  *                                                          *
1460  *  Then, add in the piece/square table value for the       *
1461  *  queen.                                                  *
1462  *                                                          *
1463  ************************************************************
1464 */
1465     score_mg += qval[mg][side][square];
1466     score_eg += qval[eg][side][square];
1467 /*
1468  ************************************************************
1469  *                                                          *
1470  *  Adjust the tropism count for this piece.                *
1471  *                                                          *
1472  ************************************************************
1473  */
1474     if (tree->dangerous[side]) {
1475       i = KingSQ(enemy);
1476       tree->tropism[side] += king_tropism_q[Distance(square, i)];
1477       i = 8 - (RankDistance(square, i) + FileDistance(square, i));
1478       score_mg += i;
1479       score_eg += i;
1480     }
1481   }
1482   tree->score_mg += sign[side] * score_mg;
1483   tree->score_eg += sign[side] * score_eg;
1484 }
1485 
1486 /* last modified 10/19/15 */
1487 /*
1488  *******************************************************************************
1489  *                                                                             *
1490  *   EvaluateRooks() is used to evaluate rooks.                                *
1491  *                                                                             *
1492  *******************************************************************************
1493  */
EvaluateRooks(TREE * RESTRICT tree,int side)1494 void EvaluateRooks(TREE * RESTRICT tree, int side) {
1495   uint64_t temp, moves;
1496   int square, rank, file, i, mobility, score_mg = 0, score_eg = 0;
1497   int enemy = Flip(side);
1498 
1499 /*
1500  ************************************************************
1501  *                                                          *
1502  *  Initialize.                                             *
1503  *                                                          *
1504  ************************************************************
1505  */
1506   for (temp = Rooks(side); temp; temp &= temp - 1) {
1507     square = LSB(temp);
1508     file = File(square);
1509     rank = Rank(square);
1510 /*
1511  ************************************************************
1512  *                                                          *
1513  *  Determine if the rook is on an open file or on a half-  *
1514  *  open file, either of which increases its ability to     *
1515  *  attack important squares.                               *
1516  *                                                          *
1517  ************************************************************
1518  */
1519     if (!(file_mask[file] & Pawns(side))) {
1520       if (!(file_mask[file] & Pawns(enemy))) {
1521         score_mg += rook_open_file[mg];
1522         score_eg += rook_open_file[eg];
1523       } else {
1524         score_mg += rook_half_open_file[mg];
1525         score_eg += rook_half_open_file[eg];
1526       }
1527     }
1528 /*
1529  ************************************************************
1530  *                                                          *
1531  *  Mobility counts the number of squares the rook attacks, *
1532  *  excluding squares with friendly pieces, and weighs each *
1533  *  square according to a complex formula that includes     *
1534  *  files as well as total number of squares attacked.      *
1535  *                                                          *
1536  ************************************************************
1537  */
1538     mobility = RookMobility(square, OccupiedSquares);
1539     score_mg += mobility;
1540     score_eg += mobility;
1541 /*
1542  ************************************************************
1543  *                                                          *
1544  *  Check to see if the king has been forced to move and    *
1545  *  has trapped a rook at a1/b1/g1/h1, if so, then penalize *
1546  *  the trapped rook to help extricate it.  We only need to *
1547  *  check this if the rooks mobility is very low.           *
1548  *                                                          *
1549  ************************************************************
1550  */
1551     if (mobility < 0 && rank == rank1[side] && rank == Rank(KingSQ(side))) {
1552       i = File(KingSQ(side));
1553       if (i > FILEE) {
1554         if (file > i) {
1555           score_mg += mobility * 3;
1556           score_eg += mobility * 3;
1557         }
1558       } else if (i < FILED && file < i) {
1559         score_mg += mobility * 3;
1560         score_eg += mobility * 3;
1561       }
1562     }
1563 /*
1564  ************************************************************
1565  *                                                          *
1566  *   finally check to see if any rooks are on the 7th rank, *
1567  *   with the opponent having pawns on that rank or the     *
1568  *   opponent's king being hemmed in on the 7th/8th rank.   *
1569  *   If so, we give a bonus for the strong rook.  If there  *
1570  *   is another rook or queen on the 7th that is connected  *
1571  *   with this one, then the positional advantage is even   *
1572  *   stronger.                                              *
1573  *                                                          *
1574  ************************************************************
1575  */
1576     else if (rank == rank7[side] && (Rank(KingSQ(enemy)) == rank8[side]
1577             || Pawns(enemy) & rank_mask[rank])) {
1578       score_mg += rook_on_7th[mg];
1579       score_eg += rook_on_7th[eg];
1580       if (RankAttacks(square) & (Queens(side) | Rooks(side))) {
1581         score_mg += rook_connected_7th[mg];
1582         score_eg += rook_connected_7th[eg];
1583       }
1584     }
1585 /*
1586  ************************************************************
1587  *                                                          *
1588  *  Adjust the tropism count for this piece.                *
1589  *                                                          *
1590  ************************************************************
1591  */
1592     if (tree->dangerous[side]) {
1593       moves = king_attacks[KingSQ(enemy)];
1594       i = (rook_attacks[square] & moves &&
1595           RookAttacks(square,
1596               OccupiedSquares & ~(Queens(side) | Rooks(side))) & moves) ? 1 :
1597           Distance(square, KingSQ(enemy));
1598       tree->tropism[side] += king_tropism_r[i];
1599     }
1600   }
1601   tree->score_mg += sign[side] * score_mg;
1602   tree->score_eg += sign[side] * score_eg;
1603 }
1604 
1605 /* last modified 01/03/15 */
1606 /*
1607  *******************************************************************************
1608  *                                                                             *
1609  *   EvaluateWinningChances() is used to determine if one side has reached a   *
1610  *   position which can not be won, period, even though side may be ahead in   *
1611  *   material in some way.                                                     *
1612  *                                                                             *
1613  *   Return values:                                                            *
1614  *          0    ->     side on move can not win.                              *
1615  *          1    ->     side on move can win.                                  *
1616  *                                                                             *
1617  *******************************************************************************
1618  */
EvaluateWinningChances(TREE * RESTRICT tree,int side,int wtm)1619 int EvaluateWinningChances(TREE * RESTRICT tree, int side, int wtm) {
1620   int square, ekd, promote, majors, minors, enemy = Flip(side);
1621 
1622   if (!Pawns(side)) {
1623 /*
1624  ************************************************************
1625  *                                                          *
1626  *  If side has a piece and no pawn, it can not possibly    *
1627  *  win.  If side is a piece ahead, the only way it can win *
1628  *  is if the enemy is already trapped on the edge of the   *
1629  *  board (special case to handle KRB vs KR which can be    *
1630  *  won if the king gets trapped).                          *
1631  *                                                          *
1632  ************************************************************
1633  */
1634     if (TotalPieces(side, occupied) <= 3)
1635       return 0;
1636     if (TotalPieces(side, occupied) - TotalPieces(enemy, occupied) <= 3 &&
1637         mask_not_edge & Kings(enemy))
1638       return 0;
1639 /*
1640  ************************************************************
1641  *                                                          *
1642  *  If one side is an exchange up, but has no pawns, then   *
1643  *  that side can not possibly win.                         *
1644  *                                                          *
1645  ************************************************************
1646  */
1647     majors =
1648         TotalPieces(white, rook) + 2 * TotalPieces(white,
1649         queen) - TotalPieces(black, rook) - 2 * TotalPieces(black, queen);
1650     if (Abs(majors) == 1) {
1651       minors =
1652           TotalPieces(black, knight) + TotalPieces(black,
1653           bishop) - TotalPieces(white, knight) - TotalPieces(white, bishop);
1654       if (majors == minors)
1655         return 0;
1656     }
1657   } else {
1658 /*
1659  ************************************************************
1660  *                                                          *
1661  *  If neither side has any pieces, and both sides have     *
1662  *  non-rookpawns, then either side can win.                *
1663  *                                                          *
1664  ************************************************************
1665  */
1666     if (TotalPieces(white, occupied) == 0 && TotalPieces(black, occupied) == 0
1667         && Pawns(white) & not_rook_pawns && Pawns(black) & not_rook_pawns)
1668       return 1;
1669   }
1670 /*
1671  ************************************************************
1672  *                                                          *
1673  *  If "side" has a pawn, then either the pawn had better   *
1674  *  not be a rook pawn, or else side had better have the    *
1675  *  right color bishop or any other piece, otherwise it is  *
1676  *  not winnable if the enemy king can get to the queening  *
1677  *  square first.                                           *
1678  *                                                          *
1679  ************************************************************
1680  */
1681   if (!(Pawns(side) & not_rook_pawns))
1682     do {
1683       if (TotalPieces(side, occupied) > 3 || (TotalPieces(side, occupied) == 3
1684               && Knights(side)))
1685         continue;
1686       if (file_mask[FILEA] & Pawns(side) && file_mask[FILEH] & Pawns(side))
1687         continue;
1688       if (Bishops(side)) {
1689         if (Bishops(side) & dark_squares) {
1690           if (file_mask[dark_corner[side]] & Pawns(side))
1691             continue;
1692         } else if (file_mask[light_corner[side]] & Pawns(side))
1693           continue;
1694       }
1695       if (Pawns(side) & file_mask[FILEA])
1696         promote = A8;
1697       else
1698         promote = H8;
1699       ekd = Distance(KingSQ(enemy), sqflip[side][promote]) - (wtm != side);
1700       if (ekd <= 1)
1701         return 0;
1702     } while (0);
1703 /*
1704  ************************************************************
1705  *                                                          *
1706  *  Check to see if this is a KRP vs KR ending.  If so, and *
1707  *  the losing king is in front of the passer, then this is *
1708  *  a drawish ending.                                       *
1709  *                                                          *
1710  ************************************************************
1711  */
1712   if (TotalPieces(side, pawn) == 1 && TotalPieces(enemy, pawn) == 0 &&
1713       TotalPieces(side, occupied) == 5 && TotalPieces(enemy, occupied) == 5) {
1714     square = LSB(Pawns(side));
1715     if (FileDistance(KingSQ(enemy), square) <= 1 &&
1716         InFront(side, Rank(KingSQ(enemy)), Rank(square)))
1717       return 0;
1718   }
1719 /*
1720  ************************************************************
1721  *                                                          *
1722  *  If this side has pawns, and we have made it through the *
1723  *  previous tests, then this side has winning chances.     *
1724  *                                                          *
1725  ************************************************************
1726  */
1727   if (TotalPieces(side, pawn))
1728     return 1;
1729 /*
1730  ************************************************************
1731  *                                                          *
1732  *  If this side has two bishops, and the enemy has only a  *
1733  *  single kinght, the two bishops win.                     *
1734  *                                                          *
1735  ************************************************************
1736  */
1737   if (TotalPieces(side, occupied) == 6)
1738     if (TotalPieces(enemy, occupied) == 3 && (Knights(side)
1739             || !Knights(enemy)))
1740       return 0;
1741 /*
1742  ************************************************************
1743  *                                                          *
1744  *  If one side is two knights ahead and the opponent has   *
1745  *  no remaining material, it is a draw.                    *
1746  *                                                          *
1747  ************************************************************
1748  */
1749   if (TotalPieces(side, occupied) == 6 && !Bishops(side)
1750       && TotalPieces(enemy, occupied) + TotalPieces(enemy, pawn) == 0)
1751     return 0;
1752 /*
1753  ************************************************************
1754  *                                                          *
1755  *  If we make it through all the above tests, then "side"  *
1756  *  can win so we return 1.                                 *
1757  *                                                          *
1758  ************************************************************
1759  */
1760   return 1;
1761 }
1762 
1763 /*
1764  *******************************************************************************
1765  *                                                                             *
1766  *   InitializeKingSafety() is used to initialize the king safety matrix.      *
1767  *   This is set so that the matrix, indexed by king safety pawn structure     *
1768  *   index and by king safety piece tropism, combines the two indices to       *
1769  *   produce a single score.  As either index rises, the king safety score     *
1770  *   tracks along, but as both rise, the king safety score rises much more     *
1771  *   quickly.                                                                  *
1772  *                                                                             *
1773  *******************************************************************************
1774  */
InitializeKingSafety()1775 void InitializeKingSafety() {
1776   int safety, tropism;
1777 
1778   for (safety = 0; safety < 16; safety++) {
1779     for (tropism = 0; tropism < 16; tropism++) {
1780       king_safety[safety][tropism] =
1781           180 * ((safety_vector[safety] + 100) * (tropism_vector[tropism] +
1782               100) / 100 - 100) / 100;
1783     }
1784   }
1785 }
1786