module Exercise_10 where import Data.List import Test.QuickCheck {-H10.1-} data Player = V | H -- vertical or horizontal player deriving (Eq,Show) data Field = P Player | E -- a field is occupied by a player or empty deriving (Eq,Show) type Row = [Field] type Column = [Field] type Board = [Row] -- we assume that boards are squares and encode a board row by row data Game = Game Board Player -- stores the currenty board and player deriving (Eq,Show) -- get a given row of a board row :: Board -> Int -> Row row = (!!) -- get a given column of a board column :: Board -> Int -> Column column = row . transpose -- width of a board width :: Board -> Int width [] = 0 width (x:xs) = length x -- height of a board height :: Board -> Int height = length {-H10.1.1-} prettyShowBoard :: Board -> String prettyShowBoard [] = "" prettyShowBoard rs = concat [ (concat [icon f | f <- r]) ++ "\n" | r <-rs] where icon E = "+" icon (P a) = show a {-H10.1.2-} -- position on a board (row, column) -- (0,0) corresponds to the top left corner type Pos = (Int, Int) isValidMove :: Game -> Pos -> Bool isValidMove (Game [] _) _ = False isValidMove (Game b _) (r,c) | r<0 || c<0 || r>(height b)-1 || c>(width b)-1 = False isValidMove (Game b p) (r,c) = case p of V -> height b /= r+1 && (b!!r)!!c == E && (b!!(r+1))!!c == E H -> width b /= c+1 && (b!!r)!!c == E && (b!!r)!!(c+1) == E {-H10.1.3-} canMove :: Game -> Bool canMove g@(Game b p) = or [ isValidMove g (r,c) | r <- [0..(height b - 1)], c <- [0..(width b - 1)] ] {-H10.1.4-} updateBoard :: Board -> Pos -> Field -> Board updateBoard b (x,y) f = [ if r==x then updateRow (b!!r) else b!!r | r <- [0..(height b - 1)] ] where updateRow rw = [ if c==y then f else rw!!c | c <- [0..(width b - 1)] ] {-H10.1.5-} playMove :: Game -> Pos -> Game playMove (Game b p) pos@(r,c) = case p of V -> Game (updateBoard (updateBoard b (r+1,c) (P V)) pos (P V)) H H -> Game (updateBoard (updateBoard b (r,c+1) (P H)) pos (P H)) V {-H10.1.6-} -- the first paramter of a strategy is an infite list of -- random values between (0,1) (in case you wanna go wild with -- probabilistic methods) type Strategy = [Double] -> Game -> Pos {-WETT-} christmasAI :: Strategy -- receives a game and plays a move for the next player christmasAI rng g@(Game b p) = fst (head (filter (\(move, score) -> score==bestScore) scoredMoves)) where scoredMoves = [{-if rng!!(r*c) < 0.2 then-} ( (r,c) , numMoves (playMove g (r,c)) ) {-else ((r,c), 121)-} | r <- [0..(height b - 1)], c <- [0..(width b - 1)], isValidMove g (r,c) ] bestScore = minimum $ map (\x -> snd x) scoredMoves --eval move only with 20% chance numMoves :: Game -> Int numMoves g@(Game b p) = sum [ if (isValidMove g (r,c)) then 1 else 0 | r <- [0..(height b - 1)], c <- [0..(width b - 1)] ] {-TTEW-} {-H10.1.7-} play :: [[Double]] -> Int -> Strategy -> Strategy -> ([Board],Player) play rngs dim p1 p2 = ( boardlist, if null gamelist then H else player (last gamelist) ) where boardlist = map board gamelist gamelist = playhelper rngs (Game (genBoard dim) V) p1 p2 genBoard dim = take dim (repeat (take dim (repeat E))) player (Game b p) = case p of V -> H H -> V board (Game b p) = b playhelper (rng:rngs) g p1 p2 = if canMove g && isValidMove g (p1 rng g) then (playMove g (p1 rng g)):playhelper rngs (playMove g (p1 rng g) ) p2 p1 else [] -- generates infinite list of values between (0,1) genRandomZeroOne :: Gen [Double] genRandomZeroOne = mapM (const $ choose (0::Double,1)) [1..] -- plays a game and prints it to the console playAndPrint :: Int -> Strategy -> Strategy -> IO () playAndPrint dim sh sv = do rss <- generate $ mapM (const $ genRandomZeroOne) [1..] let (bs, w) = play rss dim sh sv putStr $ (unlines $ map prettyShowBoard bs) ++ "\nWinner: " ++ show w ++ "\n"