-- | Utilities for AI players. module AI.Utils ( winOrPreventLoss , mapTree , prunedepth , prunebreadth , highfirst , lowfirst ) where import Board import Data.List (sortBy, minimumBy) -- | Searches BoardTree to a depth of 1 looking for a -- | guaranteed win or a preventable loss. winOrPreventLoss :: Strategy -> Strategy winOrPreventLoss s (GameTree a branches) = s $ GameTree a branches2 where winning = [ (t, b) | (t, b@(GameTree _ [])) <- branches ] losing = [ t | (t, (GameTree _ branches')) <- branches, (_, (GameTree _ [])) <- branches' ] branches1 = if not $ null winning then [head winning] else if length branches<100 then [ (t, b) | (t, b) <- branches, notElem t losing ] else branches branches2 = if null branches1 then [head branches] else branches1 -- | some auxiliary functions over game trees -- apply a function to each node mapTree :: (a->b) -> GameTree a m -> GameTree b m mapTree f (GameTree x branches) = GameTree (f x) [(m,mapTree f t) | (m,t)<-branches] -- apply a function to each edge mapTree' :: (a->b) -> GameTree s a -> GameTree s b mapTree' f (GameTree x branches) = GameTree x [(f m,mapTree' f t) | (m,t)<-branches] -- heuristic to order subtrees with highest values first highfirst, lowfirst :: (Ord a) => GameTree a m -> GameTree a m highfirst (GameTree x branches) = GameTree x $ sortBy cmp [(m,lowfirst t) | (m,t)<-branches] where cmp (_,GameTree x _) (_,GameTree y _) = compare y x lowfirst (GameTree x branches) = GameTree x $ sortBy cmp [(m,highfirst t) | (m,t)<-branches] where cmp (_,GameTree x _) (_, GameTree y _) = compare x y -- 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 n (GameTree x branches) = GameTree x [(m, prunebreadth n t) | (m,t)<-take n branches]