module Exercise08 where import Data.Array.MArray.Safe import Data.Bits import Data.List import qualified Data.Set as S --import Debug.Trace import System.Random (Random, mkStdGen, randomIO, randoms) -- Player is either 1 or -1 type Player = Int -- A field is just an Int value where the absolute gives the number of pieces on the field -- and the sign corresponds to the player -- e.g. -3 would mean there are three blobs in this field of player -1 type Field = Int type Row = [Field] type Column = [Field] -- boards are rectangles represented as a list of rows type Board = [Row] -- A position on the board is represented as (row, column) -- (0,0) is the top left corner, coordinate values increase towards the bottom right type Pos = (Int, Int) -- A size represented as (height,width) type Size = (Int, Int) -- A strategy takes the player who's move it is, optionally takes a list of double values -- to allow for probabilistic strategies, takes the current board and gives back the position -- of the move the player should do type Strategy = [Double] -> Player -> Board -> Pos -- A stateful strategy can additionally pass some object between invocations type StatefulStrategyFunc a = a -> [Double] -> Player -> Board -> (Pos, a) -- first value is the state object to pass to the first invocation of each game type StatefulStrategy a = (a, StatefulStrategyFunc a) defaultSize :: (Int, Int) defaultSize = (9, 6) -- Some useful helper functions row :: Board -> Int -> Row row = (!!) column :: Board -> Int -> Column column = row . transpose width :: Board -> Int width (x : _) = length x width _ = 0 height :: Board -> Int height = length size :: Board -> Size size b = (height b, width b) getCell :: Pos -> Board -> Field getCell (y, x) b = b !! y !! x -- pretty print a single cell showCell :: Field -> String showCell c = "- +" !! succ (signum c) : show (abs c) -- pretty print the given board showBoard :: Board -> String showBoard = unlines . map (unwords . map showCell) -- print a board to the console printBoard :: Board -> IO () printBoard = putStr . showBoard -- check if a position is one a board of the given size isValidPos :: Size -> Pos -> Bool isValidPos (r, c) (y, x) = y >= 0 && y < r && x >= 0 && x < c {- x.1 -} -- Check if the given player can put an orb on the given position canPlaceOrb :: Player -> Pos -> Board -> Bool canPlaceOrb pl pos b = let cell = getCell pos b in (signum cell == pl || cell == 0) && isValidPos (size b) pos -- Check if the given player has won the game, -- you can assume that the opponent has made at least one move before hasWon :: Player -> Board -> Bool hasWon p b = not (any (\x -> signum x /= signum p && x /= 0) (concat b)) --hasWon _ _ = False -- the list of neighbors of a cell neighbors :: Size -> Pos -> [Pos] neighbors (r, c) (y, x) = filter (isValidPos (r, c)) [(y + 1, x), (y -1, x), (y, x + 1), (y, x -1)] -- update a single position on the board -- f: function that modifies the number of orbs in the cell -- p: player to whom the updated cell should belong updatePos :: (Int -> Int) -> Player -> Pos -> Board -> Board updatePos f p (y, x) b = let ro = row b y in take y b ++ [take x ro ++ [signum p * abs (f (abs (ro !! x)))] ++ drop (x + 1) ro] ++ drop (y + 1) b {- x.2 -} -- place an orb for the given player in the given cell putOrb :: Player -> Pos -> Board -> Board putOrb p (y, x) b | any (/= 0) (concat b) && hasWon p b = b | am + 1 == length nei = foldl' (flip (putOrb p)) (updatePos (const 0) p (y, x) b) nei | otherwise = updatePos (+ 1) p (y, x) b where am = abs (getCell (y, x) b) dim = size b nei = neighbors dim (y, x) {- x.3 -} -- Your strategy strategy2 :: Strategy strategy2 _ p b | canPlaceOrb p c1 b = c1 | canPlaceOrb p c2 b = c2 | canPlaceOrb p c3 b = c3 | canPlaceOrb p c4 b = c4 | otherwise = minimumBy ( \ap bp -> let ca = getCell ap b cb = getCell bp b wa = (length (neighbors (y, x) ap) - abs ca) wb = (length (neighbors (y, x) bp) - abs cb) in if wa == wb then EQ else if wa > wb then GT else LT ) (filter (flip (canPlaceOrb p) b) [(yi, xi) | xi <- [0 .. x - 1], yi <- [0 .. y - 1]]) where (y, x) = size b c1 = (0, 0) c2 = (0, x -1) c3 = (y -1, x -1) c4 = (y -1, 0) {-WETT-} --Basically maximizes not loosing, wich surprisingly works really well strategy :: Strategy strategy _ p b --the best choice is always the greatest one (obviously) | length lpegp == 1 = head lpegp --we place something near other tokens, which does not explode | length nonexpl > 1 = neartok p b nonexpl --we place somewhere explosive | length lpegp > 1 = neartok p b lpegp --this should not happen, but this prevents us from doing dodgy illegal stuff | otherwise = strategy2 [] p b where --prevents the strat from pointlessly exploding stuff, since we do not know if that explosion would be a good idea nonexpl = filter (\pos -> length (neighbors (size b) pos) < getCell pos b) lpegp lpegp = stLowsPEG p b --choose positions with the lowest possible conversions of our enemy stLowsPEG :: Player -> Board -> [Pos] stLowsPEG p b = map fst $ filter (\(_, x) -> x == mi) pmegs where (_, mi) = minimumBy (\(_, x) (_, y) -> compare x y) pmegs pmegs = filter (\(_, x) -> x >= 0) $ map ( \pos -> (pos, bposVal p b (- 1) (maximum . calcPotEnemyGain p) pos) ) (boardPoss b) --Calculate all Conversions our enemey could make calcPotEnemyGain :: Player -> Board -> [Int] calcPotEnemyGain p b = map (bposVal ep b 0 (calcGain ep b)) (boardPoss b) where ep = - p --Calculate Value of Placing Orb based on Function f bposVal :: Player -> Board -> Int -> (Board -> Int) -> Pos -> Int bposVal p b cnpp f po = if canPlaceOrb p po b then f (putOrb p po b) else cnpp --calc Conversions from Player between boards calcGain :: Player -> Board -> Board -> Int calcGain p b nb | hasWon p nb = 9999 | otherwise = abs (boardSum nb - p - boardSum b) `div` 2 + 1 --The sum of the board boardSum :: Board -> Int boardSum b = sum $ concat b --all possible Board positions boardPoss :: Board -> [(Int, Int)] boardPoss b = [(y, x) | y <- [0 .. ym -1], x <- [0 .. xm -1]] where (ym, xm) = size b --Optimizes to put tokens near eachother neartok :: Field -> Board -> [(Int, Int)] -> (Int, Int) neartok p b xs = fst (maximumBy (\(_, x) (_, y) -> compare x y) (map (\pos -> (pos, p * sum (map (`getCell` b) (neighbors (size b) pos)))) xs)) -- adds state to a strategy that doesn't use it wrapStrategy :: Strategy -> StatefulStrategy Int wrapStrategy strat = (0, \s r p b -> (strat r p b, succ s)) -- the actual strategy submissions -- if you want to use state modify this instead of strategy -- additionally you may change the Int in this type declaration to any type that is usefully for your strategy strategyState :: StatefulStrategy Int strategyState = wrapStrategy strategy {-TTEW-} -- Simulate a game between two strategies on a board of the given size and -- returns the state of the board before each move together with the player that won the game play :: [Int] -> Size -> StatefulStrategy a -> StatefulStrategy b -> [(Board, Pos)] play rss (r, c) (isa, sa) (isb, sb) = go rss isa sa isb sb 1 0 (replicate r (replicate c 0)) where -- type signature is necessary, inferred type is wrong! go :: [Int] -> a -> StatefulStrategyFunc a -> b -> StatefulStrategyFunc b -> Player -> Int -> Board -> [(Board, Pos)] go (rs : rss) stc sc stn sn p n b | won = [] | valid = (b, m) : go rss stn sn st' sc (- p) (succ n) (putOrb p m b) | otherwise = [] where won = n > 1 && hasWon (- p) b (m, st') = sc stc (mkRandoms rs) p b valid = isValidPos (size b) m && canPlaceOrb p m b -- Play a game and print it to the console playAndPrint :: Size -> StatefulStrategy a -> StatefulStrategy b -> IO () playAndPrint size sa sb = do seed <- randomIO -- let seed = 42 let moves = play (mkRandoms seed) size sa sb putStr $ unlines (zipWith showState moves $ cycle ['+', '-']) ++ "\n" ++ (case length moves `mod` 2 of 1 -> "Winner: +"; 0 -> "Winner: -") ++ "\n" ++ "View at https://vmnipkow16.in.tum.de/christmas2020/embed.html#i" ++ base64 (1 : t size ++ concatMap (t . snd) moves) ++ "\n" where showState (b, pos) p = showBoard b ++ p : " places at " ++ show pos ++ "\n" t (a, b) = [a, b] mkRandoms :: Random a => Int -> [a] mkRandoms = randoms . mkStdGen base64 :: [Int] -> String base64 xs = case xs of [] -> "" [a] -> f1 a : f2 a 0 : "==" [a, b] -> f1 a : f2 a b : f3 b 0 : "=" a : b : c : d -> f1 a : f2 a b : f3 b c : f4 c : base64 d where alphabet = (!!) "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/" f1 a = alphabet $ shiftR a 2 f2 a b = alphabet $ shiftL (a .&. 3) 4 .|. shiftR b 4 f3 b c = alphabet $ shiftL (b .&. 15) 2 .|. shiftR c 6 f4 c = alphabet $ c .&. 63