{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} module Game.Hanabi.Strategies.SimpleStrategy where import Game.Hanabi hiding (main) import System.Random -- An example of a simple and stupid strategy. data Simple = S instance Monad m => Strategy Simple m where strategyName ms = return "Stupid example strategy" move (pv:_) (Hint 1 (Left c) : _) s = return (Play $ length $ takeWhile ((/=Just c) . fst) $ head $ givenHints $ publicView pv, s) move (pv:_) _mvs s = let pub = publicView pv tsuginohitoNoTe = head $ handsPV pv ::[Card] tsuginohitoNoHint = givenHints pub !! 1 numHand = length $ head $ givenHints pub mov | hintTokens pub >= 1 = case filter (\(ix, te, hint) -> hint == (Nothing,Nothing) && isCritical pub te) $ zip3 [0..] tsuginohitoNoTe tsuginohitoNoHint of [] -> foo us -> Hint 1 $ Right (number $ sndOf3 $ last us) | otherwise = foo where foo = case filter ((==(Nothing,Nothing)) . snd) $ zip [0..] $ head $ givenHints pub of ts@(_:_) | hintTokens pub < 4 -> Drop (fst $ last ts) | otherwise -> case break (isPlayable pub) tsuginohitoNoTe of (_,d:_) -> Hint 1 $ Left $ color d (_,[]) | hintTokens pub < 8 -> Drop (fst $ last ts) | otherwise -> Hint 1 $ Right $ number $ last $ tsuginohitoNoTe _ | hintTokens pub < 1 -> Drop $ pred $ length $ head $ givenHints pub | otherwise -> Hint 1 $ Right $ number $ last $ tsuginohitoNoTe in return (mov, s) sndOf3 (_,b,_) = b main = do g <- newStdGen -- ((eg,_),_) <- start defaultGS [] ([S],[stdio]) g -- Play it with standard I/O (human player). ((eg,_),_) <- start defaultGS [peek] [S,S] g -- Play it with itself. putStrLn $ prettyEndGame eg