boardgame-0.0.0.1: Modeling boardgames
Safe HaskellSafe-Inferred
LanguageHaskell2010

Boardgame

Description

The main framework module for boardgames. Contains the PositionalGame class implemented by all positional games, and a bunch of helper functions.

The helper functions range from just that, simple helper functions such as player1WinsWhen, to right out implementations of functions in the PositionalGames class, such as the takeEmptyMakeMove functions.

It also contains some functions for playing games. play is the implementation agnostic skeleton code that you can use in any context. And playIO uses play to play the games in the terminal.

TicTacToe as an example

-- TicTacToe is a
newtype TicTacToe = TicTacToe (Map (Integer, Integer) Position)

-- Creates an empty TicTacToe board with coordinates @(0..2, 0..2)@
emptyTicTacToe = TicTacToe $
  fromDistinctAscList $
    zip
      [(x, y) | x <- [0..2], y <- [0..2]]
      (repeat Empty)

instance Show TicTacToe where
  show (TicTacToe b) = intercalate "\n" [
      "╔═══╤═══╤═══╗"
    , "║ " ++ intercalate " │ " (row 0) ++ " ║"
    , "╟───┼───┼───╢"
    , "║ " ++ intercalate " │ " (row 1) ++ " ║"
    , "╟───┼───┼───╢"
    , "║ " ++ intercalate " │ " (row 2) ++ " ║"
    , "╚═══╧═══╧═══╝"
    ]
    where
      row y = map (\x -> showP $ b ! (x, y)) [0..2]
      showP (Occupied Player1) = "\ESC[34mo\ESC[0m"
      showP (Occupied Player2) = "\ESC[31mx\ESC[0m"
      showP Empty = " "

instance PositionalGame TicTacToe (Integer, Integer) where
  -- Just looks up the coordinate in the underlying Map
  getPosition (TicTacToe b) = flip lookup b
  -- Just returns the elements in the underlying Map
  positions (TicTacToe b) = elems b
  -- If the underlying Map has the given coordinate, update it with the given player
  setPosition (TicTacToe b) c p = if member c b then Just $ TicTacToe $ insert c p b else Nothing
  -- "Creates" a 'gameOver' function by supplying all the winning "patterns"
  gameOver = patternMatchingGameOver [
      [(0, 0), (0, 1), (0, 2)]
    , [(1, 0), (1, 1), (1, 2)]
    , [(2, 0), (2, 1), (2, 2)]
    , [(0, 0), (1, 0), (2, 0)]
    , [(0, 1), (1, 1), (2, 1)]
    , [(0, 2), (1, 2), (2, 2)]
    , [(0, 0), (1, 1), (2, 2)]
    , [(2, 0), (1, 1), (0, 2)]
    ]
  -- 'makeMove' is handled by the default implementation 'takeEmptyMakeMove'

-- Plays the game in the terminal, takes @(x, y)@ as input
main = playIO emptyTicTacToe
Synopsis

Documentation

data Player Source #

Represents one of the two players.

Constructors

Player1 
Player2 

Instances

Instances details
Eq Player Source # 
Instance details

Defined in Boardgame

Methods

(==) :: Player -> Player -> Bool #

(/=) :: Player -> Player -> Bool #

Show Player Source # 
Instance details

Defined in Boardgame

data Position Source #

A Position can either be Occupied by a Player or be Empty.

Constructors

Occupied Player 
Empty 

Instances

Instances details
Eq Position Source # 
Instance details

Defined in Boardgame

Show Position Source # 
Instance details

Defined in Boardgame

data Outcome Source #

The Outcome of a game. Either a Win for one of the players, or a Draw.

Constructors

Win Player 
Draw 

Instances

Instances details
Eq Outcome Source # 
Instance details

Defined in Boardgame

Methods

(==) :: Outcome -> Outcome -> Bool #

(/=) :: Outcome -> Outcome -> Bool #

Show Outcome Source # 
Instance details

Defined in Boardgame

class PositionalGame a c | a -> c where Source #

A type class for positional games where a is the game itself and c is its accompanying "coordinate" type.

Minimal complete definition

gameOver, positions, getPosition, setPosition

Methods

makeMove :: a -> Player -> c -> Maybe a Source #

Takes the "current" state, a player, and a coordinate. Returns the new state if the move is valid.

The default implementation is takeEmptyMakeMove.

gameOver :: a -> Maybe (Outcome, [c]) Source #

Takes the "current" state and checks if the game is over, in which case the victorious player is returned or Draw in case of a draw.

Nothing       -- Continue the game
Just (Just p, cs) -- Player p won
Just (Nothing, cs)  -- Draw

We also return cs, a list of coordinates to highlight.

positions :: a -> [Position] Source #

Returns a list of all positions. Not in any particular order.

getPosition :: a -> c -> Maybe Position Source #

Returns which player (or Empty) has taken the position at the given coordinate, or Nothing if the given coordinate is invalid.

Nothing         -- Invalid position
Occupied Player -- Player p owns this position
Empty           -- This position is empty

setPosition :: a -> c -> Position -> Maybe a Source #

Takes the position at the given coordinate for the given player and returns the new state, or Nothing if the given coordinate is invalid.

nextPlayer :: Player -> Player Source #

Returns the "next" player in turn.

mapPosition :: (Player -> Player) -> Position -> Position Source #

Applies the given function to a occupying piece, or does nothing in the case of an Empty Position.

isOccupied :: Position -> Bool Source #

Checks if the position is occupied or not.

isEmpty :: Position -> Bool Source #

Checks if the position is empty or not.

mapOutcome :: (Player -> Player) -> Outcome -> Outcome Source #

Applies the given function to a winning player, or does nothing in the case of a draw.

isWin :: Outcome -> Bool Source #

Checks if the outcome is a victory or not.

isDraw :: Outcome -> Bool Source #

Checks if the outcome is a draw or not.

play Source #

Arguments

:: (Monad m, PositionalGame a c) 
=> (a -> m ())

Function for outputting the state of the game.

-> (Player -> m ())

Function for communicating which Players turn it is.

-> m c

Function for getting a move from a player.

-> m ()

Function for communicating an invalid move.

-> ((Outcome, [c]) -> m ())

Function for outputting the end result of the game.

-> a 
-> m () 

The skeleton code for "playing" any PositionalGame. When given a set of function for communicating the state of the game and moves, a starting state can be applied to play the game.

playerToInt :: Player -> Int Source #

Turns a Player into an int. 1 or 2 for the player respectively.

playIO :: (Show a, Show c, Read c, PositionalGame a c) => a -> IO () Source #

Plays a PositionalGame in the console by taking alternating input from the players. Requires that the game is an instance of Show and that its coordinates are instances of Read.

takeEmptyMakeMove :: PositionalGame a c => a -> Player -> c -> Maybe a Source #

A standard implementation of makeMove for a PositionalGame. Only allows move that "take" empty existing positions.

patternMatchingGameOver :: (Eq c, PositionalGame a c) => [[c]] -> a -> Maybe (Outcome, [c]) Source #

Returns an implementation of gameOver for a PositionalGame when given a set of winning sets. A player is victorious when they "own" one of the winning sets. The game ends in a draw when all positions on the board are taken.

drawIf :: (a -> Bool) -> a -> Maybe (Outcome, [c]) Source #

If the predicate holds, a draw state is returned. If not, a "game running" state is returned.

player1WinsIf :: (a -> Bool) -> a -> Maybe (Outcome, [c]) Source #

If the predicate holds, a winning state for player 1 is returned. If not, a "game running" state is returned.

player2WinsIf :: (a -> Bool) -> a -> Maybe (Outcome, [c]) Source #

If the predicate holds, a winning state for player 2 is returned. If not, a "game running" state is returned.

player1LosesIf :: (a -> Bool) -> a -> Maybe (Outcome, [c]) Source #

A synonym for player2WinsIf. When player 1 loses, player 2 wins.

player2LosesIf :: (a -> Bool) -> a -> Maybe (Outcome, [c]) Source #

A synonym for player1WinsIf. When player 2 loses, player 1 wins.

drawWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c]) Source #

If the predicate holds, a draw state is returned. If not, a "game running" state is returned.

player1WinsWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c]) Source #

If the predicate holds, a winning state for player 1 is returned. If not, a "game running" state is returned.

player2WinsWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c]) Source #

If the predicate holds, a winning state for player 2 is returned. If not, a "game running" state is returned.

player1LosesWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c]) Source #

A synonym for player2WinsIf. When player 1 loses, player 2 wins.

player2LosesWhen :: (a -> Maybe [c]) -> a -> Maybe (Outcome, [c]) Source #

A synonym for player1WinsIf. When player 2 loses, player 1 wins.

criteria :: [a -> Maybe (Outcome, [c])] -> a -> Maybe (Outcome, [c]) Source #

Combines several criteria into one. If two or more of the criteria returns different game over states, an error is raised.

symmetric :: (a -> a) -> (a -> Maybe (Outcome, [c])) -> a -> Maybe (Outcome, [c]) Source #

Create a symmetric game from a game defined for only one player.

unless :: (a -> Maybe (Outcome, [c])) -> (a -> Maybe (Outcome, [c])) -> a -> Maybe (Outcome, [c]) infixl 8 Source #

Combines two criteria into one where the first criterions result is returned, unless the second criterion returns a game over state.

ifNotThen :: (a -> Maybe (Outcome, [c])) -> (a -> Maybe (Outcome, [c])) -> a -> Maybe (Outcome, [c]) Source #

Combines two criteria into one where if the first criterion does not return a game over state, the result of the second criterion is used.

makerBreakerGameOver :: (Eq c, PositionalGame a c) => [[c]] -> a -> Maybe (Outcome, [c]) Source #

Returns an implementation of gameOver for a PositionalGame when given a set of winning sets. Player1 wins when they "own" one of the winning sets. Player2 wins if Player1 cannot win.