-- | Utilities for AI players. module AI.Utils ( winOrPreventLoss , pruneDepth, pruneBreadth , highFirst, lowFirst , withNPieces, withBoard , dontPass, singleCaptures --, nubDoubleCaptures ) 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 winning = [ (m1, b1) | (m1,b1@(GameTree _ branches'))<-branches, (m2, GameTree _ []) <- branches'] branches1 = (if not (null winning) then [head winning] else if length branches 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] {- -- eliminate double-captures that lead to identical boards nubDoubleCaptures :: Strategy -> Strategy nubDoubleCaptures s g rndgen = s (narrow g) rndgen where narrow (GameTree node branches) = GameTree node $ nubBy equiv [(t, narrow g) | (t,g)<-branches] equiv ((m1,Just m2),_) ((m2', Just m1'),_) = fst m1/=fst m2 && m1==m1' && m2==m2' equiv _ _ = False -}