Draft a very stupid AI and simplify Automaton states a bit

This commit is contained in:
Tissevert 2019-08-20 18:19:54 +02:00
parent 00d88dcc83
commit 62223eb84f
2 changed files with 29 additions and 21 deletions

View File

@ -1,9 +1,21 @@
{-# LANGUAGE NamedFieldPuns #-}
module AI ( module AI (
move move
) where ) where
import Hanafuda.KoiKoi (Move(..), PlayerKey) import Data.Map ((!))
import Hanafuda (cardsOfPack, sameMonth)
import Hanafuda.Player (Player(..), Players(..))
import Hanafuda.KoiKoi (GameBlueprint(..), Move(..), PlayerKey, Step(..))
import Hanafuda.Message (PublicGame) import Hanafuda.Message (PublicGame)
move :: PlayerKey -> PublicGame -> Move move :: PlayerKey -> PublicGame -> Move
move = undefined move me (Game {step = ToPlay, players = Players p}) =
Play . head . cardsOfPack . hand $ p ! me
move me (Game {step = Turned card, river}) =
Choose . last . cardsOfPack $ sameMonth card river
where
last [] = error "Empty list"
last [x] = x
last (x:xs) = last xs
move me _ = KoiKoi True

View File

@ -15,27 +15,24 @@ import Control.Concurrent (threadDelay)
import Control.Monad.Reader (ReaderT, ask) import Control.Monad.Reader (ReaderT, ask)
import Control.Monad.State (StateT) import Control.Monad.State (StateT)
import Control.Monad.Trans (lift) import Control.Monad.Trans (lift)
import Hanafuda.KoiKoi (Game, GameBlueprint(..), PlayerKey) import Hanafuda.KoiKoi (Game, GameBlueprint(..), PlayerKey, Step(..))
import qualified Hanafuda.Message as Message (T(..), FromClient(..), PublicGame, Room) import qualified Hanafuda.Message as Message (T(..), FromClient(..), PublicGame)
import Network.WebSockets (Connection, receiveData, sendTextData) import Network.WebSockets (Connection, receiveData, sendTextData)
import Prelude hiding (error, putStrLn) import Prelude hiding (error, putStrLn)
import System.Exit (exitSuccess)
data State = data State =
Initial Initial
| Connected { | Connected {
key :: PlayerKey key :: PlayerKey
, room :: Message.Room
} }
| LoggedIn { | LoggedIn {
key :: PlayerKey key :: PlayerKey
, room :: Message.Room
, name :: Text , name :: Text
} }
| Playing { | Playing {
key :: PlayerKey key :: PlayerKey
, room :: Message.Room
, name :: Text , name :: Text
, game :: Message.PublicGame
} }
deriving Show deriving Show
@ -66,27 +63,26 @@ debug message = lift $ putStrLn message
answer :: Message.T -> State -> App State answer :: Message.T -> State -> App State
answer welcome@(Message.Welcome {}) Initial = do answer welcome@(Message.Welcome {}) Initial = do
send $ Message.LogIn {Message.name = "Hannah"} send $ Message.LogIn {Message.name = "Hannah"}
return $ Connected { return $ Connected {key = Message.key welcome}
key = Message.key welcome
, room = Message.room welcome
}
answer (Message.Relay {Message.from, Message.message = Message.LogIn {Message.name}}) (Connected {key, room}) answer (Message.Relay {Message.from, Message.message = Message.LogIn {Message.name}}) (Connected {key})
| from == key = return $ LoggedIn {key, room, name} | from == key = return $ LoggedIn {key, name}
answer (Message.Relay {Message.message = Message.Invitation {}}) state@(LoggedIn {key, room, name}) = do answer (Message.Relay {Message.message = Message.Invitation {}}) (LoggedIn {key, name}) = do
send $ Message.Answer {Message.accept = True} send $ Message.Answer {Message.accept = True}
return $ Playing {key, room, name, game = undefined} return $ Playing {key, name}
answer (Message.Relay {Message.message = Message.Invitation {}}) state = do answer (Message.Relay {Message.message = Message.Invitation {}}) state = do
send $ Message.Answer {Message.accept = False} send $ Message.Answer {Message.accept = False}
return state return state
answer (Message.Game {Message.game, Message.logs}) state@(Playing {key}) = do answer (Message.Game {Message.game, Message.logs}) state@(Playing {key, name}) = do
if playing game == key if playing game == key
then send $ Message.Play {Message.move = AI.move key game} then do
else return () case step game of
return $ state {game} Over -> send Message.Quit >> return (LoggedIn {key, name})
_ -> send (Message.Play {Message.move = AI.move key game}) >> return state
else return state
answer Message.Pong state = ping >> return state answer Message.Pong state = ping >> return state
@ -102,7 +98,7 @@ answer message state = do
ping = do ping = do
connection <- ask connection <- ask
setTimeout (2*s) (sendIO Message.Ping connection) setTimeout (20*s) (sendIO Message.Ping connection)
where where
setTimeout delay callback = setTimeout delay callback =
const () <$> (lift $ forkIO (threadDelay delay >> callback)) const () <$> (lift $ forkIO (threadDelay delay >> callback))