-- | Utilities for AI players. module AI.Utils ( winOrPreventLoss , pruneDepth, pruneBreadth , highFirst, lowFirst , withNPieces, withBoard , dontPass, singleCaptures , zoneOfControl ) where import Board import Data.List (nubBy, sortBy, minimumBy) import qualified Data.IntMap as IntMap import System.Random -- order subtrees with ascending or descending order of static evaluation highFirst, lowFirst :: GameTree Int m -> GameTree Int m highFirst (GameTree x branches) = GameTree x [(m,highFirst t) | (m,t)<-sortBy cmp branches] where cmp (_,x) (_,y) = compare (value y) (value x) value (GameTree n _) = n lowFirst (GameTree x branches) = GameTree x [(m,lowFirst t) | (m,t)<-sortBy cmp branches] where cmp (_,x) (_, y) = compare (value x) (value y) value (GameTree n _) = n -- prune to a fixed depth pruneDepth :: Int -> GameTree a m -> GameTree a m pruneDepth n (GameTree x branches) | n>0 = GameTree x [(m,pruneDepth (n-1) t) | (m,t)<-branches] | otherwise= GameTree x [] -- prune to a fixed breadth pruneBreadth :: Int -> GameTree a m -> GameTree a m pruneBreadth k (GameTree node branches) = GameTree node [(m,pruneBreadth k t) | (m,t)<-take k branches] -- conditional strategies withBoard :: (Board -> Strategy) -> Strategy withBoard f t@(GameTree b _) g = f b t g withNPieces :: (Int -> Strategy) -> Strategy withNPieces f = withBoard $ \b -> f (IntMap.size (active b) + IntMap.size (inactive b)) -- | Searches BoardTree to a depth of 1 looking for a -- | guaranteed win or a preventable loss. winOrPreventLoss :: Strategy -> Strategy winOrPreventLoss s (GameTree node branches) = s $ GameTree node branches2 where -- ensure a win in 1 or 2 captures winning = [ (m, t) | (m,t@(GameTree b _))<-branches, endGame b] -- prevent a loss prevent_loss = [(m1,t1) | (m1,t1@(GameTree _ branches'))<-branches, (m2,t2)<- branches', not_losing t2] branches1 = (if not (null winning) then [head winning] else prevent_loss ) branches2 = if null branches1 then [head branches] else branches1 not_losing (GameTree _ branches) = null [m | (m, GameTree b _) <- branches, endGame b] cutoff = 1000 -- braching upper bound for searching losing moves -- narrow the search space: don't consider double-capture or pass moves singleCaptures :: Strategy -> Strategy singleCaptures s g@(GameTree _ branches) rndgen | null branches' = s g rndgen | otherwise = s g' rndgen where g'@(GameTree _ branches') = narrow g narrow :: BoardTree -> BoardTree narrow (GameTree board branches) = GameTree board [ (m, narrow g) | (m,g)<-branches, move board==1 || isStacking m ] isStacking (Stack _ _) = True isStacking _ = False -- don't consider passing moves dontPass :: Strategy -> Strategy dontPass s g rndgen = s (narrow g) rndgen where narrow :: BoardTree -> BoardTree narrow (GameTree node branches) | null branches' = GameTree node branches | otherwise = GameTree node branches' where branches' = [(m, narrow g) | (m,g)<-branches, m/=Pass] -- Estimate the zone of control of the active player -- i.e., the set of opponent pieces reachable in a turn (two capture moves) zoneOfControl :: Board -> HalfBoard zoneOfControl board = IntMap.filterWithKey forPiece1 other where you = active board other = inactive board who = player board -- white pieces that can make at least one capture captures = IntMap.filterWithKey forPiece2 you forPiece1, forPiece2 :: Position -> Piece -> Bool forPiece1 p (_, i) = or $ map (downLine0 i) $ sixLines p forPiece2 p (_, h) = or $ map (downLine2 h) $ sixLines p downLine0, downLine1, downLine2 :: Int -> [Position] -> Bool downLine0 i [] = False downLine0 i (p:ps) = case atPosition board p of Nothing -> downLine0 i ps Just (who', (_, h)) | who'==who -> h>=i || (p`IntMap.member`captures && downLine1 i ps) Just (_, (_, j)) -> or $ map (downLine1 (max i j)) $ sixLines p downLine1 i [] = False downLine1 i (p:ps) = case atPosition board p of Nothing -> downLine1 i ps Just (who', (_, h)) | who'==who -> h>=i _ -> False downLine2 h [] = False downLine2 h (p:ps) = case atPosition board p of Nothing -> downLine2 h ps Just (who', (_, i)) | who'/=who -> h>=i _ -> False