halma-0.3.0.0: Library implementing Halma rules

Safe HaskellNone
LanguageHaskell2010

Game.Halma.Board

Synopsis

Documentation

data HalmaGrid Source #

Constructors

SmallGrid 
LargeGrid 

Instances

Eq HalmaGrid Source # 
Ord HalmaGrid Source # 
Show HalmaGrid Source # 
ToJSON HalmaGrid Source # 
FromJSON HalmaGrid Source # 
Grid HalmaGrid Source # 

Associated Types

type Index HalmaGrid :: * #

type Direction HalmaGrid :: * #

Methods

indices :: HalmaGrid -> [Index HalmaGrid] #

distance :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> Int #

minDistance :: HalmaGrid -> [Index HalmaGrid] -> Index HalmaGrid -> Int #

neighbours :: HalmaGrid -> Index HalmaGrid -> [Index HalmaGrid] #

neighboursOfSet :: HalmaGrid -> [Index HalmaGrid] -> [Index HalmaGrid] #

neighbour :: HalmaGrid -> Index HalmaGrid -> Direction HalmaGrid -> Maybe (Index HalmaGrid) #

numNeighbours :: HalmaGrid -> Index HalmaGrid -> Int #

contains :: HalmaGrid -> Index HalmaGrid -> Bool #

tileCount :: HalmaGrid -> Int #

null :: HalmaGrid -> Bool #

nonNull :: HalmaGrid -> Bool #

edges :: HalmaGrid -> [(Index HalmaGrid, Index HalmaGrid)] #

viewpoint :: HalmaGrid -> Index HalmaGrid -> [(Index HalmaGrid, Int)] #

isAdjacent :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> Bool #

adjacentTilesToward :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> [Index HalmaGrid] #

minimalPaths :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> [[Index HalmaGrid]] #

directionTo :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> [Direction HalmaGrid] #

defaultMinDistance :: HalmaGrid -> [Index HalmaGrid] -> Index HalmaGrid -> Int #

defaultNeighbours :: HalmaGrid -> Index HalmaGrid -> [Index HalmaGrid] #

defaultNeighboursOfSet :: HalmaGrid -> [Index HalmaGrid] -> [Index HalmaGrid] #

defaultNeighbour :: HalmaGrid -> Index HalmaGrid -> Direction HalmaGrid -> Maybe (Index HalmaGrid) #

defaultTileCount :: HalmaGrid -> Int #

defaultEdges :: HalmaGrid -> [(Index HalmaGrid, Index HalmaGrid)] #

defaultIsAdjacent :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> Bool #

defaultAdjacentTilesToward :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> [Index HalmaGrid] #

defaultMinimalPaths :: HalmaGrid -> Index HalmaGrid -> Index HalmaGrid -> [[Index HalmaGrid]] #

FiniteGrid HalmaGrid Source # 

Associated Types

type Size HalmaGrid :: * #

BoundedGrid HalmaGrid Source # 
type Direction HalmaGrid Source # 
type Index HalmaGrid Source # 
type Size HalmaGrid Source # 

sideLength :: HalmaGrid -> Int Source #

Numbers of fields on each straight edge of a star-shaped halma board of the given size.

numberOfFields :: HalmaGrid -> Int Source #

Total number of fields on a halma board of the given size.

data HalmaDirection Source #

The six corners of a star-shaped halma board.

Instances

Bounded HalmaDirection Source # 
Enum HalmaDirection Source # 
Eq HalmaDirection Source # 
Ord HalmaDirection Source # 
Read HalmaDirection Source # 
Show HalmaDirection Source # 
Generic HalmaDirection Source # 

Associated Types

type Rep HalmaDirection :: * -> * #

ToJSON HalmaDirection Source # 
FromJSON HalmaDirection Source # 
type Rep HalmaDirection Source # 
type Rep HalmaDirection = D1 (MetaData "HalmaDirection" "Game.Halma.Board" "halma-0.3.0.0-E77mvIbb0PoJib7Qr9ou7J" False) ((:+:) ((:+:) (C1 (MetaCons "North" PrefixI False) U1) ((:+:) (C1 (MetaCons "Northeast" PrefixI False) U1) (C1 (MetaCons "Southeast" PrefixI False) U1))) ((:+:) (C1 (MetaCons "South" PrefixI False) U1) ((:+:) (C1 (MetaCons "Southwest" PrefixI False) U1) (C1 (MetaCons "Northwest" PrefixI False) U1))))

rowsInDirection :: HalmaDirection -> (Int, Int) -> Int Source #

From the point of view of the given corner: On which row lies the given field? The row through the center is row zero, rows nearer to the corner have positive, rows nearer to the opposite corner negative numbers.

corner :: HalmaGrid -> HalmaDirection -> (Int, Int) Source #

 The corner corresponding to a direction on a star-shaped board of the given size.

type Team = HalmaDirection Source #

The corner where the team starts.

startCorner :: HalmaGrid -> Team -> (Int, Int) Source #

The position of the corner field where a team starts.

endCorner :: HalmaGrid -> Team -> (Int, Int) Source #

The position of the end zone corner of a team.

startFields :: HalmaGrid -> Team -> [(Int, Int)] Source #

The start positions of a team's pieces.

endFields :: HalmaGrid -> Team -> [(Int, Int)] Source #

The end zone of the given team.

data Piece Source #

Halma gaming piece

Constructors

Piece 

Fields

fromMap :: HalmaGrid -> Map (Index HalmaGrid) Piece -> Maybe HalmaBoard Source #

Construct halma boards. Satisfies fromMap (getGrid board) (toMap board) = Just board.

lookupHalmaBoard :: (Int, Int) -> HalmaBoard -> Maybe Piece Source #

Lookup whether a position on the board is occupied, and

data Move Source #

A move of piece on a (Halma) board.

Constructors

Move 

Fields

movePiece :: Move -> HalmaBoard -> Either String HalmaBoard Source #

Move a piece on the halma board. This function does not check whether the move is valid according to the Halma rules.