bishbosh-0.1.1.0: Plays chess.
Safe HaskellNone
LanguageHaskell2010

BishBosh.Component.Zobrist

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
Synopsis

Type-classes

class Hashable1D hashable x where Source #

An interface to which 1-D hashable data can conform.

Methods

listRandoms1D :: hashable x -> Zobrist x y positionHash -> [positionHash] Source #

Instances

Instances details
Ix x => Hashable1D EnPassantAbscissa x Source # 
Instance details

Defined in BishBosh.State.EnPassantAbscissa

Methods

listRandoms1D :: EnPassantAbscissa x -> Zobrist x y positionHash -> [positionHash] Source #

Eq x => Hashable1D CastleableRooksByLogicalColour x Source #

Get the list of random numbers required to represent the current castling potential.

Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

Methods

listRandoms1D :: CastleableRooksByLogicalColour x -> Zobrist x y positionHash -> [positionHash] Source #

class Hashable2D hashable x y where Source #

An interface to which 2-D hashable data can conform.

Methods

listRandoms2D :: hashable x y -> Zobrist x y positionHash -> [positionHash] Source #

Instances

Instances details
(Enum x, Enum y, Ord x, Ord y) => Hashable2D MaybePieceByCoordinates x y Source # 
Instance details

Defined in BishBosh.State.MaybePieceByCoordinates

Methods

listRandoms2D :: MaybePieceByCoordinates x y -> Zobrist x y positionHash -> [positionHash] Source #

(Enum x, Enum y, Ord x, Ord y) => Hashable2D CoordinatesByRankByLogicalColour x y Source # 
Instance details

Defined in BishBosh.State.CoordinatesByRankByLogicalColour

Methods

listRandoms2D :: CoordinatesByRankByLogicalColour x y -> Zobrist x y positionHash -> [positionHash] Source #

(Enum x, Enum y, Ord x, Ord y) => Hashable2D Board x y Source # 
Instance details

Defined in BishBosh.State.Board

Methods

listRandoms2D :: Board x y -> Zobrist x y positionHash -> [positionHash] Source #

(Ix x, Enum x, Enum y, Ord y) => Hashable2D Position x y Source # 
Instance details

Defined in BishBosh.State.Position

Methods

listRandoms2D :: Position x y -> Zobrist x y positionHash -> [positionHash] Source #

(Ix x, Enum x, Enum y, Ord y) => Hashable2D Game x y Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

listRandoms2D :: Game x y -> Zobrist x y positionHash -> [positionHash] Source #

Types

Type-synonyms

Data-types

data Zobrist x y positionHash Source #

The random numbers used to generate a hash, which almost uniquely represent a position.

Instances

Instances details
Foldable (Zobrist x y) Source # 
Instance details

Defined in BishBosh.Component.Zobrist

Methods

fold :: Monoid m => Zobrist x y m -> m #

foldMap :: Monoid m => (a -> m) -> Zobrist x y a -> m #

foldMap' :: Monoid m => (a -> m) -> Zobrist x y a -> m #

foldr :: (a -> b -> b) -> b -> Zobrist x y a -> b #

foldr' :: (a -> b -> b) -> b -> Zobrist x y a -> b #

foldl :: (b -> a -> b) -> b -> Zobrist x y a -> b #

foldl' :: (b -> a -> b) -> b -> Zobrist x y a -> b #

foldr1 :: (a -> a -> a) -> Zobrist x y a -> a #

foldl1 :: (a -> a -> a) -> Zobrist x y a -> a #

toList :: Zobrist x y a -> [a] #

null :: Zobrist x y a -> Bool #

length :: Zobrist x y a -> Int #

elem :: Eq a => a -> Zobrist x y a -> Bool #

maximum :: Ord a => Zobrist x y a -> a #

minimum :: Ord a => Zobrist x y a -> a #

sum :: Num a => Zobrist x y a -> a #

product :: Num a => Zobrist x y a -> a #

(Enum x, Enum y, Ord y, Show positionHash, Show x, Show y, Ix x) => Show (Zobrist x y positionHash) Source # 
Instance details

Defined in BishBosh.Component.Zobrist

Methods

showsPrec :: Int -> Zobrist x y positionHash -> ShowS #

show :: Zobrist x y positionHash -> String #

showList :: [Zobrist x y positionHash] -> ShowS #

(Ix x, FiniteBits positionHash, Enum x, Enum y, Ord y, Random positionHash) => Default (Zobrist x y positionHash) Source # 
Instance details

Defined in BishBosh.Component.Zobrist

Methods

def :: Zobrist x y positionHash #

Constants

Functions

dereferenceRandomByCoordinatesByRankByLogicalColour :: (Enum x, Enum y, Ord x, Ord y) => Index x y -> Zobrist x y positionHash -> positionHash Source #

Dereferences getRandomByCoordinatesByRankByLogicalColour using the specified index.

dereferenceRandomByCastleableRooksXByLogicalColour Source #

Arguments

:: Eq x 
=> LogicalColour 
-> x 
-> Zobrist x y positionHash 
-> Maybe positionHash

The existence of a result depends on whether there remain any Rooks which can castle.

Dereferences getRandomByCastleableRooksXByLogicalColour using the specified abscissa.

dereferenceRandomByEnPassantAbscissa :: Ix x => x -> Zobrist x y positionHash -> positionHash Source #

Dereferences getRandomByEnPassantAbscissa using the specified abscissa.

hash2D :: (Bits positionHash, Hashable2D hashable x y) => hashable x y -> Zobrist x y positionHash -> positionHash Source #

Resolve a hashable into a hash.

combine :: Bits positionHash => positionHash -> [positionHash] -> positionHash Source #

Include a list of random numbers in the hash.

Constructors

mkZobrist Source #

Arguments

:: (Ix x, FiniteBits positionHash, Enum x, Enum y, Ord y, RandomGen randomGen, Random positionHash) 
=> Maybe Int

The optional minimum acceptable Hamming-distance between any two of the selected random numbers.

-> randomGen 
-> Zobrist x y positionHash 

Smart constructor.