{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE PartialTypeSignatures #-}
module Boardgame (
Player(..)
, Position(..)
, Outcome(..)
, PositionalGame(..)
, nextPlayer
, mapPosition
, isOccupied
, isEmpty
, mapOutcome
, isWin
, isDraw
, play
, playerToInt
, playIO
, takeEmptyMakeMove
, patternMatchingGameOver
, drawIf
, player1WinsIf
, player2WinsIf
, player1LosesIf
, player2LosesIf
, drawWhen
, player1WinsWhen
, player2WinsWhen
, player1LosesWhen
, player2LosesWhen
, criteria
, symmetric
, unless
, ifNotThen
, makerBreakerGameOver
) where
import Data.Functor ((<&>))
import Data.List (find, intercalate, minimumBy, intersect)
import Data.Maybe (isJust, fromJust)
import System.IO (hFlush, stdout)
import Text.Read (readMaybe)
import Control.Monad (join, foldM)
import Control.Applicative ((<|>))
import Data.Bifunctor (first, Bifunctor (second))
#ifdef WASM
import Data.Aeson (ToJSON(toJSON), Value(Number, Null))
import Data.Scientific (fromFloatDigits)
#endif
data Player = Player1 | Player2
deriving (Show, Eq)
nextPlayer :: Player -> Player
nextPlayer Player1 = Player2
nextPlayer Player2 = Player1
playerToInt :: Player -> Int
playerToInt Player1 = 1
playerToInt Player2 = 2
#ifdef WASM
instance ToJSON Player where
toJSON = Number . fromFloatDigits . fromIntegral . playerToInt
#endif
data Position = Occupied Player | Empty
deriving (Eq, Show)
#ifdef WASM
instance ToJSON Position where
toJSON (Occupied p) = toJSON p
toJSON Empty = Null
#endif
mapPosition :: (Player -> Player) -> Position -> Position
mapPosition f (Occupied p) = Occupied $ f p
mapPosition _ Empty = Empty
isOccupied :: Position -> Bool
isOccupied (Occupied _) = True
isOccupied Empty = False
isEmpty :: Position -> Bool
isEmpty (Occupied _) = False
isEmpty Empty = True
data Outcome = Win Player | Draw
deriving (Eq, Show)
#ifdef WASM
instance ToJSON Outcome where
toJSON (Win p) = toJSON p
toJSON Draw = Null
#endif
mapOutcome :: (Player -> Player) -> Outcome -> Outcome
mapOutcome f (Win p) = Win $ f p
mapOutcome _ Draw = Draw
isWin :: Outcome -> Bool
isWin (Win _) = True
isWin Draw = False
isDraw :: Outcome -> Bool
isDraw (Win _) = False
isDraw Draw = True
class PositionalGame a c | a -> c where
makeMove :: a -> Player -> c -> Maybe a
makeMove = takeEmptyMakeMove
gameOver :: a -> Maybe (Outcome, [c])
positions :: a -> [Position]
getPosition :: a -> c -> Maybe Position
setPosition :: a -> c -> Position -> Maybe a
takeEmptyMakeMove :: PositionalGame a c => a -> Player -> c -> Maybe a
takeEmptyMakeMove a p coord = case getPosition a coord of
Just Empty -> setPosition a coord (Occupied p)
_ -> Nothing
patternMatchingGameOver :: (Eq c, PositionalGame a c) => [[c]] -> a -> Maybe (Outcome, [c])
patternMatchingGameOver patterns a = case find (isOccupied . fst) $ (\pat -> (, pat) $ reduceHomogeneousList (fromJust . getPosition a <$> pat)) <$> patterns of
Nothing -> if all isOccupied (positions a) then Just (Draw, []) else Nothing
Just (Occupied winner, coords) -> Just (Win winner, coords)
Just (Empty, coords) -> Just (Draw, coords)
where
reduceHomogeneousList :: [Position] -> Position
reduceHomogeneousList [] = Empty
reduceHomogeneousList (x:xs) = if all (== x) xs then x else Empty
makerBreakerGameOver :: (Eq c, PositionalGame a c) => [[c]] -> a -> Maybe (Outcome, [c])
makerBreakerGameOver patterns a
| Just coords <- player1won = Just (Win Player1, coords)
| player2won = Just (Win Player2, player2Coords)
| otherwise = Nothing
where
player1won = find (all $ (== Occupied Player1) . fromJust . getPosition a) patterns
player2won = all (any $ (== Occupied Player2) . fromJust . getPosition a) patterns
player2Coords = minimumBy compareLength $ assignments $ filter ((== Occupied Player2) . fromJust . getPosition a) <$> patterns
compareLength :: [a] -> [b] -> Ordering
compareLength [] [] = EQ
compareLength (_:_) [] = GT
compareLength [] (_:_) = LT
compareLength (_:xs) (_:ys) = compareLength xs ys
assignments :: Eq c => [[c]] -> [[c]]
assignments = assignments' []
where
assignments' set [] = [set]
assignments' set (claus:clauses) = if not $ null $ intersect set claus
then assignments' set clauses
else concat $ (\c -> assignments' (c:set) clauses) <$> claus
avoiderEnforcerGameOver :: (Eq c, PositionalGame a c) => [[c]] -> a -> Maybe (Outcome, [c])
avoiderEnforcerGameOver patterns a = first (mapOutcome nextPlayer) <$> makerBreakerGameOver patterns a
play :: (Monad m, PositionalGame a c) =>
(a -> m ())
-> (Player -> m ())
-> m c
-> m ()
-> ((Outcome, [c]) -> m ())
-> a
-> m ()
play putState putTurn getMove putInvalidMove putGameOver startingState = putState startingState >> putTurn Player1 >> play' startingState Player1
where
play' s p = getMove <&> makeMove s p >>= \case
Just s' -> putState s' >> case gameOver s' of
Just v -> putGameOver v
Nothing -> (\p' -> putTurn p' >> play' s' p') $ nextPlayer p
Nothing -> putInvalidMove >> play' s p
playIO :: (Show a, Show c, Read c, PositionalGame a c) => a -> IO ()
playIO = play putState putTurn getMove putInvalidMove putGameOver
where
putState s = putStr "\ESC[s\ESC[0;0H" >> print s >> putStr "\ESC[u" >> hFlush stdout
putTurn p = putStr ("Move for " ++ (case p of
Player1 -> "player 1"
Player2 -> "player 2") ++ ": ") >> hFlush stdout
getMove = getLine <&> readMaybe >>= \case
Just c -> return c
Nothing -> putStr "Invalid input, try again: " >> hFlush stdout >> getMove
putInvalidMove = putStr "Invalid move, try again: " >> hFlush stdout
putGameOver = \case
(Win Player1, p) -> putStrLn "Player 1 won!" >> print p >> hFlush stdout
(Win Player2, p) -> putStrLn "Player 2 won!" >> print p >> hFlush stdout
(Draw, _) -> putStrLn "It's a draw!" >> hFlush stdout
data CombinedPositionalGames a b i j = CombinedPositionalGames a b
instance (PositionalGame a i, PositionalGame b j) => PositionalGame (CombinedPositionalGames a b i j) (Either i j) where
makeMove (CombinedPositionalGames x y) player index = case index of
Left i -> flip CombinedPositionalGames y <$> makeMove x player i
Right i -> CombinedPositionalGames x <$> makeMove y player i
gameOver (CombinedPositionalGames x y) = (second (fmap Left) <$> gameOver x)
<|> (second (fmap Right) <$> gameOver y)
positions (CombinedPositionalGames x y) = positions x ++ positions y
getPosition (CombinedPositionalGames x y) = either (getPosition x) (getPosition y)
setPosition (CombinedPositionalGames x y) ij p = case ij of
Left i -> flip CombinedPositionalGames y <$> setPosition x i p
Right j -> CombinedPositionalGames x <$> setPosition y j p
player1WinsIf :: (a -> Bool) -> a -> Maybe (Outcome, [c])
player1WinsIf pred x = if pred x
then Just (Win Player1, [])
else Nothing
player2LosesIf :: (a -> Bool) -> a -> Maybe (Outcome, [c])
player2LosesIf = player1WinsIf
player2WinsIf :: (a -> Bool) -> a -> Maybe (Outcome, [c])
player2WinsIf pred x = if pred x
then Just (Win Player2, [])
else Nothing
player1LosesIf :: (a -> Bool) -> a -> Maybe (Outcome, [c])
player1LosesIf = player2WinsIf
drawIf :: (a -> Bool) -> (a -> Maybe (Outcome, [c]))
drawIf pred x = if pred x
then Just (Draw, [])
else Nothing
player1WinsWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c])
player1WinsWhen pred x = (Win Player1, ) <$> pred x
player2LosesWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c])
player2LosesWhen = player1WinsWhen
player2WinsWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c])
player2WinsWhen pred x = (Win Player2, ) <$> pred x
player1LosesWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c])
player1LosesWhen = player2WinsWhen
drawWhen :: (a -> Maybe [c]) -> (a -> Maybe (Outcome, [c]))
drawWhen pred x = (Draw, ) <$> pred x
ifNotThen :: (a -> Maybe (Outcome, [c]))
-> (a -> Maybe (Outcome, [c]))
-> (a -> Maybe (Outcome, [c]))
ifNotThen crit1 crit2 x = crit1 x <|> crit2 x
infixl 8 `unless`
unless :: (a -> Maybe (Outcome, [c]))
-> (a -> Maybe (Outcome, [c]))
-> (a -> Maybe (Outcome, [c]))
unless = flip ifNotThen
criteria :: [a -> Maybe (Outcome, [c])] -> a -> Maybe (Outcome, [c])
criteria = foldl1 ifNotThen
symmetric :: (a -> a) -> (a -> Maybe (Outcome, [c])) -> a -> Maybe (Outcome, [c])
symmetric flipState criterion = criterion `ifNotThen` (fmap (first $ mapOutcome nextPlayer) . criterion . flipState)