-- -- Library of AI players -- module AI where import Board import System.Random import Data.Map(Map) import qualified Data.Map as Map import Data.Maybe(catMaybes) import AI.Gametree import AI.Minimax import AI.Eval -- | instance the gametree class for TZAAR instance Gametree Board where children b = [applyMove m b | m<-nextMoves b] is_terminal b = null (nextMoves b) -- | An AI play strategy -- takes a board and pseudo-random generator -- yields evaluation, next move and new random generator type Playing = Board -> StdGen -> (Int, Move, StdGen) -- | An AI player. data AI = AI { name :: String -- ^ Unique name , description :: String -- ^ Brief description of AI. , playing :: Playing -- ^ The play strategy. } aiLevels :: [AI] aiLevels = catMaybes [lookupAI label aiPlayers | label<-list] where list = ["nscout_simple_1", "nscout_simple_3", "nscout_full_1", "nscout_full_3", "nscout_full_6", "pscout_full_3", "pscout_full_6"] lookupAI :: String -> [AI] -> Maybe AI lookupAI label ai_list = case [ai | ai<-ai_list, name ai==label] of [] -> Nothing (ai : _) -> Just ai aiPlayers :: [AI] aiPlayers = do (txt0,txt1,strat) <- list (val,txt2) <- zip [simple_val, full_val] ["simple", "full"] ply <- [1..9] let label = txt0 ++ "_" ++ txt2 ++ "_" ++ show ply let desc = txt1 ++ " " ++ txt2 ++ " valuation, ply " ++ show ply return AI { name = label , description = desc , playing = play (strat val ply) } where list = [ ("nmax", "Negamax", negamax_alpha_beta), ("nscout", "Negascout", negascout), ("pscout", "Parallel negascout", jamboree) ] play strat b rndgen | m `elem` nextMoves b = (score, m, rndgen) | otherwise = error "panic: AI gave invalid move!" where vpos = strat b score = value vpos -- next move in principal variation m = (reverse $ moves $ unvalued vpos) !! move b