| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Quoridor
- type Cell = (Int, Int)
- type HalfGate = (Cell, Cell)
- type Gate = (HalfGate, HalfGate)
- type HalfGates = Set HalfGate
- type BoardSize = Int
- type ValidMoves = [Cell]
- newtype Game m a = Game (ReaderT GameConfig (StateT GameState m) a)
- runGame :: Functor m => Game m a -> GameConfig -> m ()
- runGameWithGameState :: Game m a -> GameState -> GameConfig -> m (a, GameState)
- data Player = Player {}
- data Turn
- data Color
- data Direction
- data GameState = GameState {}
- data GameConfig = GameConfig {
- gatesPerPlayer :: Int
- boardSize :: Int
- numOfPlayers :: Int
- initialGameState :: GameConfig -> GameState
- defaultGameConfig :: GameConfig
- startPos :: Int -> Map Color Cell
- modifyCurrP :: (Player -> Player) -> GameState -> GameState
- currP :: GameState -> Player
- distance :: Cell -> Cell -> Int
- isAdj :: Cell -> Cell -> Bool
- getAdj :: Int -> Cell -> [Cell]
- isWithinRange :: Int -> Cell -> Bool
- align :: HalfGate -> HalfGate
- isHalfGateSpaceClear :: HalfGate -> HalfGates -> Bool
- isGateSpaceClear :: Gate -> HalfGates -> Bool
- gateToCells :: Gate -> [Cell]
- gateUpperLeft :: Cell -> Direction -> Gate
- insertGate :: Gate -> HalfGates -> HalfGates
- isVacant :: Cell -> GameState -> Bool
- isWinningCell :: Int -> Player -> Cell -> Bool
- coerceTurn :: (Monad m, Functor m) => Turn -> Game m Turn
- getValidMoves :: Cell -> Int -> GameState -> [Cell]
- dfs :: Cell -> (Cell -> Bool) -> Int -> GameState -> Bool
- changeCurrPlayer :: Monad m => Game m ()
- isValidTurn :: (Monad m, Functor m) => Turn -> Game m Bool
- actTurn :: Monad m => Turn -> Game m ()
- checkAndSetWinner :: Monad m => Game m (Maybe Color)
- makeTurn :: (Monad m, Functor m) => Turn -> Game m (Maybe Turn)
- getCurrentValidMoves :: Monad m => Game m [Cell]
Documentation
A tile on the board. Direction of X and Y axis are right and down respectively.
type ValidMoves = [Cell] Source
List of valid moves for a player
The monad used for running the game. Basically adds layers of ReaderT for configuration, StateT for state, and some monad for the rest (currently just IO monad).
Constructors
| Game (ReaderT GameConfig (StateT GameState m) a) |
Instances
| MonadTrans Game | |
| Monad m => MonadReader GameConfig (Game m) | |
| Monad m => MonadState GameState (Game m) | |
| Monad m => Monad (Game m) | |
| Functor m => Functor (Game m) | |
| (Monad m, Functor m) => Applicative (Game m) | |
| MonadThrow m => MonadThrow (Game m) | |
| MonadCatch m => MonadCatch (Game m) | |
| MonadMask m => MonadMask (Game m) | |
| MonadIO m => MonadIO (Game m) |
runGame :: Functor m => Game m a -> GameConfig -> m () Source
To run the Game monad
runGameWithGameState :: Game m a -> GameState -> GameConfig -> m (a, GameState) Source
Same as runGame, but allows to start from a given GameState, instead of from the beginning
Represents a turn,
can be either a Gate put,
a Player move
or a ShortCutMove which is specified by an index
from the given valid moves for a player at
the current turn
Colors to distinguish between Players
The orientation (perhaps a better name?)
of the Gate, it can be either vertical or horizontal
data GameConfig Source
Constructors
| GameConfig | |
Fields
| |
Instances
| Read GameConfig | |
| Show GameConfig | |
| Monad m => MonadReader GameConfig (Game m) |
initialGameState :: GameConfig -> GameState Source
An initial state. All players begin at the firstlast rowcolumn
getAdj :: Int -> Cell -> [Cell] Source
Returns adjacent cells that are within the ranger of the board
isWithinRange :: Int -> Cell -> Bool Source
Is cell within board range
align :: HalfGate -> HalfGate Source
Coerces HalfGates so that left item is
less than or equal to the right item.
isHalfGateSpaceClear :: HalfGate -> HalfGates -> Bool Source
Equivalent to, given cells a and b (a,b) is the space between them open for movement?
isGateSpaceClear :: Gate -> HalfGates -> Bool Source
gateToCells :: Gate -> [Cell] Source
Breaks a gate into it's cell components. Used, for example, to make sure a gate is placed within bounds of the board.
gateUpperLeft :: Cell -> Direction -> Gate Source
Given a cell, returns a gate. That gate, the upper left corner of it's encompassing 2x2 square is at the given cell.
insertGate :: Gate -> HalfGates -> HalfGates Source
isWinningCell :: Int -> Player -> Cell -> Bool Source
Given a cell and a player, is that a cell that if the player reaches it, the game ends. Used with dfs, to make sure placing a gate still leaves at least one cell which is a winning cell, for every player.
coerceTurn :: (Monad m, Functor m) => Turn -> Game m Turn Source
Basically, translates a ShortCutMove into the Move
that it is a shortcut of, using the integral index that
is the index of the shortcut character in the list of
validMovesChars
getValidMoves :: Cell -> Int -> GameState -> [Cell] Source
Gets a list of possible cells which the current player can move to.
dfs :: Cell -> (Cell -> Bool) -> Int -> GameState -> Bool Source
Checks if from a given cell, another cell, which satisfies the given predicate, can be reached. Used in gate placement, to make sure a cell which is a winning cell for a player can still be reached.
changeCurrPlayer :: Monad m => Game m () Source
Rotates the Player list to change the current player.
The player at the had of the player list is the current player.
isValidTurn :: (Monad m, Functor m) => Turn -> Game m Bool Source
Checks if a given Turn is valid, rule-wise.
It does it by perusing getCurrentValidMovess returned
list of all possible valid moves.
actTurn :: Monad m => Turn -> Game m () Source
Acts upon a single Turn.
The difference with MakeTurn, is that MakeTurn calls this
function and does more, like changing currentPlayer and
checking for a winner.
checkAndSetWinner :: Monad m => Game m (Maybe Color) Source
Checks if there's a winner, returning it if there is
and sets the winner in the GameState.
getCurrentValidMoves :: Monad m => Game m [Cell] Source
A Game monad wrapper for the unmonadic getValidMoves