{-# LANGUAGE MultiParamTypeClasses #-} -- -- 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 import Control.Monad.State -- | instance the transition system for TZAAR games instance Transitions Board Move where actions = nextMoves transition = applyMove -- | An AI play strategy -- allows monad for pseudo-random computations -- (current strategies don't need it) type Strategy = Board -> State StdGen (Move, Value) -- | An AI player. data AI = AI { name :: String -- ^ Unique name , description :: String -- ^ Brief description of AI. , strategy :: Strategy -- ^ The AI 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"] -} aiLevels = aiPlayers 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, search) <- searches (txt2, valf) <- valuations ply <- [1..6] let label = txt0 ++ "_" ++ txt2 ++ "_" ++ show ply let desc = txt1 ++ " " ++ txt2 ++ " valuation, ply " ++ show ply return AI { name = label , description = desc , strategy = return . searchMove (search valf) ply } where searches = [ ("nmax", "Negamax", alphaBeta) , ("nscout", "Negascout", negascout) , ("pscout", "Parallel Negascout", jamboree) ] valuations = [ ("simple", simpleVal), ("full", fullVal)]