-- -- Static evaluation functions for board positions -- module AI.Eval ( simpleVal, fullVal ) where import Board import AI.Gametree import AI.Minimax import qualified Data.Vector.Unboxed as Vec -- simple static board valuation (material score only) simpleVal :: Board -> Value simpleVal b = if endGame b then (-maxBound) else material b -- better static board valuation (material and positional scores) fullVal :: Board -> Value fullVal b = if endGame b then (-maxBound) else material b + positional b -- | Material score -- * multiply sum of heights by counts -- * height weights for kinds with lowest counts material :: Board -> Value {-# INLINE material #-} material b = fromIntegral (Vec.sum (Vec.zipWith (\n h -> (30-n)^2*h) counts heights) - Vec.sum (Vec.zipWith (\n h -> (30-n)^2*h) counts' heights')) where -- stacks counts by piece kinds for each player counts = activeCounts b counts'= inactiveCounts b -- sum of heights by piece kinds heights = activeHeights b heights'= inactiveHeights b -- | Positional score -- for each kind, count opponent's pieces in each player's zone of control positional :: Board -> Value {-# INLINE positional #-} positional b = fromIntegral (Vec.sum (Vec.zipWith (\n m -> pw*m`quot`n) counts' zoc_counts) - Vec.sum (Vec.zipWith (\n m -> pw*m`quot`n) counts zoc_counts')) where counts = activeCounts b counts'= inactiveCounts b -- zone of control of each player zoc = zoneOfControl (active b) (pieces b) zoc'= zoneOfControl (inactive b) (pieces b) -- count pieces in each zone of control zoc_counts = Vec.fromList $ countStacks (inactive b) zoc zoc_counts'= Vec.fromList $ countStacks (active b) zoc' pw = 1000