{-
	Copyright (C) 2021 Dr. Alistair Ward

	This file is part of BishBosh.

	BishBosh is free software: you can redistribute it and/or modify
	it under the terms of the GNU General Public License as published by
	the Free Software Foundation, either version 3 of the License, or
	(at your option) any later version.

	BishBosh is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public License
	along with BishBosh.  If not, see <http://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]

	* Defines the random-numbers required to construct a hash of a chess-position.

	* Facilitates the construction of a hash from arbitrary data.
-}

module BishBosh.StateProperty.Hashable(
-- * Type-classes
	Hashable(listRandoms),
-- * Constants
--	combiningOp,
-- * Functions
	hash,
	combine
) where

import			Control.Arrow((***))
import qualified	BishBosh.Component.Zobrist	as Component.Zobrist
import qualified	Data.Bits
import qualified	Data.List
import qualified	Data.Maybe

-- | An interface to which hashable data can conform.
class Hashable hashable where
	listRandoms	:: Component.Zobrist.Zobrist positionHash -> hashable -> [positionHash]

instance (Hashable l, Hashable r) => Hashable (l, r) where
	listRandoms :: Zobrist positionHash -> (l, r) -> [positionHash]
listRandoms Zobrist positionHash
zobrist	= ([positionHash] -> [positionHash] -> [positionHash])
-> ([positionHash], [positionHash]) -> [positionHash]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [positionHash] -> [positionHash] -> [positionHash]
forall a. [a] -> [a] -> [a]
(++) (([positionHash], [positionHash]) -> [positionHash])
-> ((l, r) -> ([positionHash], [positionHash]))
-> (l, r)
-> [positionHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Zobrist positionHash -> l -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist (l -> [positionHash])
-> (r -> [positionHash])
-> (l, r)
-> ([positionHash], [positionHash])
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** Zobrist positionHash -> r -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist)

instance (Hashable f, Hashable s, Hashable t) => Hashable (f, s, t) where
	listRandoms :: Zobrist positionHash -> (f, s, t) -> [positionHash]
listRandoms Zobrist positionHash
zobrist (f
f, s
s, t
t)	= Zobrist positionHash -> f -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist f
f [positionHash] -> [positionHash] -> [positionHash]
forall a. [a] -> [a] -> [a]
++ Zobrist positionHash -> s -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist s
s [positionHash] -> [positionHash] -> [positionHash]
forall a. [a] -> [a] -> [a]
++ Zobrist positionHash -> t -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist t
t

instance Hashable a => Hashable [a] where
	listRandoms :: Zobrist positionHash -> [a] -> [positionHash]
listRandoms Zobrist positionHash
zobrist	= (a -> [positionHash]) -> [a] -> [positionHash]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((a -> [positionHash]) -> [a] -> [positionHash])
-> (a -> [positionHash]) -> [a] -> [positionHash]
forall a b. (a -> b) -> a -> b
$ Zobrist positionHash -> a -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist

instance Hashable a => Hashable (Maybe a) where
	listRandoms :: Zobrist positionHash -> Maybe a -> [positionHash]
listRandoms Zobrist positionHash
zobrist	= [positionHash]
-> (a -> [positionHash]) -> Maybe a -> [positionHash]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [] ((a -> [positionHash]) -> Maybe a -> [positionHash])
-> (a -> [positionHash]) -> Maybe a -> [positionHash]
forall a b. (a -> b) -> a -> b
$ Zobrist positionHash -> a -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist

-- | The operator used when combining random numbers to compose a hash.
combiningOp :: Data.Bits.Bits positionHash => positionHash -> positionHash -> positionHash
combiningOp :: positionHash -> positionHash -> positionHash
combiningOp	= positionHash -> positionHash -> positionHash
forall a. Bits a => a -> a -> a
Data.Bits.xor

-- | Resolve a hashable into a hash.
hash :: (
	Data.Bits.Bits	positionHash,
	Hashable	hashable
 )
	=> Component.Zobrist.Zobrist positionHash
	-> hashable
	-> positionHash
hash :: Zobrist positionHash -> hashable -> positionHash
hash Zobrist positionHash
zobrist	= (positionHash -> positionHash -> positionHash)
-> [positionHash] -> positionHash
forall a. (a -> a -> a) -> [a] -> a
Data.List.foldl1' positionHash -> positionHash -> positionHash
forall a. Bits a => a -> a -> a
combiningOp ([positionHash] -> positionHash)
-> (hashable -> [positionHash]) -> hashable -> positionHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Zobrist positionHash -> hashable -> [positionHash]
forall hashable positionHash.
Hashable hashable =>
Zobrist positionHash -> hashable -> [positionHash]
listRandoms Zobrist positionHash
zobrist

-- | Include a list of random numbers in the hash.
combine :: Data.Bits.Bits positionHash => positionHash -> [positionHash] -> positionHash
combine :: positionHash -> [positionHash] -> positionHash
combine	= (positionHash -> positionHash -> positionHash)
-> positionHash -> [positionHash] -> positionHash
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' positionHash -> positionHash -> positionHash
forall a. Bits a => a -> a -> a
combiningOp