halma-0.3.0.1: Library implementing Halma rules

Safe HaskellNone
LanguageHaskell2010

Game.Halma.Board

Synopsis

Documentation

data HalmaGrid Source #

Constructors

SmallGrid 
LargeGrid 
Instances
Eq HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

Ord HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

Show HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

ToJSON HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

FromJSON HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

Grid HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

Associated Types

type Index HalmaGrid :: Type #

type Direction HalmaGrid :: Type #

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 # 
Instance details

Defined in Game.Halma.Board

Associated Types

type Size HalmaGrid :: Type #

BoundedGrid HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

type Direction HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

type Index HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

type Size HalmaGrid Source # 
Instance details

Defined in Game.Halma.Board

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 # 
Instance details

Defined in Game.Halma.Board

Enum HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

Eq HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

Ord HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

Read HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

Show HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

Generic HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

Associated Types

type Rep HalmaDirection :: Type -> Type #

ToJSON HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

FromJSON HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

type Rep HalmaDirection Source # 
Instance details

Defined in Game.Halma.Board

type Rep HalmaDirection = D1 (MetaData "HalmaDirection" "Game.Halma.Board" "halma-0.3.0.1-BhzHnXmtMTpI3RqVPjb4X3" False) ((C1 (MetaCons "North" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Northeast" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Southeast" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "South" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Southwest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Northwest" PrefixI False) (U1 :: Type -> Type))))

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

Instances
Eq Piece Source # 
Instance details

Defined in Game.Halma.Board

Methods

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

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

Ord Piece Source # 
Instance details

Defined in Game.Halma.Board

Methods

compare :: Piece -> Piece -> Ordering #

(<) :: Piece -> Piece -> Bool #

(<=) :: Piece -> Piece -> Bool #

(>) :: Piece -> Piece -> Bool #

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

max :: Piece -> Piece -> Piece #

min :: Piece -> Piece -> Piece #

Show Piece Source # 
Instance details

Defined in Game.Halma.Board

Methods

showsPrec :: Int -> Piece -> ShowS #

show :: Piece -> String #

showList :: [Piece] -> ShowS #

ToJSON Piece Source # 
Instance details

Defined in Game.Halma.Board

FromJSON Piece Source # 
Instance details

Defined in Game.Halma.Board

data HalmaBoard Source #

Map from board positions to the team occupying that position.

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

Instances
Eq Move Source # 
Instance details

Defined in Game.Halma.Board

Methods

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

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

Show Move Source # 
Instance details

Defined in Game.Halma.Board

Methods

showsPrec :: Int -> Move -> ShowS #

show :: Move -> String #

showList :: [Move] -> ShowS #

ToJSON Move Source # 
Instance details

Defined in Game.Halma.Board

FromJSON Move Source # 
Instance details

Defined in Game.Halma.Board

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.