{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-
	Copyright (C) 2018 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@]

	* A view of the /board/ from the perspective of its /piece/s.

	* cf. the square-centric model of the board defined in "BishBosh.State.MaybePieceByCoordinates".
-}

module BishBosh.State.CoordinatesByRankByLogicalColour(
-- * Types
-- ** Type-synonyms
	NPiecesByFileByLogicalColour,
--	CoordinatesByRank,
	CoordinatesByLogicalColour,
--	Transformation,
-- ** Data-types
	CoordinatesByRankByLogicalColour(
--		MkCoordinatesByRankByLogicalColour,
		deconstruct
	),
-- * Functions
	countPawnsByFileByLogicalColour,
	findPassedPawnCoordinatesByLogicalColour,
	findPieces,
	findPiecesOfColour,
	findProximateKnights,
	sumPieceSquareValueByLogicalColour,
--	deleteCoordinates,
	assocs,
-- ** Accessors
	getKingsCoordinates,
	dereference,
	elems,
-- ** Constructors,
	fromMaybePieceByCoordinates,
-- ** Mutators
	movePiece,
	sortCoordinates
) where

import			Control.Arrow((&&&))
import			Data.Array.IArray((!), (//))
import qualified	BishBosh.Attribute.Direction		as Attribute.Direction
import qualified	BishBosh.Attribute.LogicalColour	as Attribute.LogicalColour
import qualified	BishBosh.Attribute.Rank			as Attribute.Rank
import qualified	BishBosh.Cartesian.Abscissa		as Cartesian.Abscissa
import qualified	BishBosh.Cartesian.Coordinates		as Cartesian.Coordinates
import qualified	BishBosh.Cartesian.Vector		as Cartesian.Vector
import qualified	BishBosh.Component.Move			as Component.Move
import qualified	BishBosh.Component.Piece		as Component.Piece
import qualified	BishBosh.Component.PieceSquareArray	as Component.PieceSquareArray
import qualified	BishBosh.Component.Zobrist		as Component.Zobrist
import qualified	BishBosh.Property.Opposable		as Property.Opposable
import qualified	BishBosh.State.Censor			as State.Censor
import qualified	BishBosh.State.MaybePieceByCoordinates	as State.MaybePieceByCoordinates
import qualified	BishBosh.Types				as T
import qualified	Control.Arrow
import qualified	Control.DeepSeq
import qualified	Control.Exception
import qualified	Data.Array.IArray
import qualified	Data.Foldable
import qualified	Data.List
import qualified	Data.Map
import qualified	Data.Map.Strict
import qualified	Data.Maybe

-- | The /coordinate/s of all the pieces of one /rank/.
type CoordinatesByRank x y	= Attribute.Rank.ByRank [Cartesian.Coordinates.Coordinates x y]

{- |
	* This structure allows one to determine the set of /coordinates/ where a type of /piece/ is located.

	* CAVEAT: the list of /coordinates/ is unordered, so test for equality using @ deconstruct . sortCoordinates @.
-}
newtype CoordinatesByRankByLogicalColour x y	= MkCoordinatesByRankByLogicalColour {
	CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct	:: Attribute.LogicalColour.ByLogicalColour (CoordinatesByRank x y)
}

instance (
	Control.DeepSeq.NFData	x,
	Control.DeepSeq.NFData	y
 ) => Control.DeepSeq.NFData (CoordinatesByRankByLogicalColour x y) where
	rnf :: CoordinatesByRankByLogicalColour x y -> ()
rnf MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= ByLogicalColour (CoordinatesByRank x y) -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf ByLogicalColour (CoordinatesByRank x y)
byLogicalColour

instance (Enum x, Enum y) => State.Censor.Censor (CoordinatesByRankByLogicalColour x y) where
	countPiecesByLogicalColour :: CoordinatesByRankByLogicalColour x y -> (NPieces, NPieces)
countPiecesByLogicalColour MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= ((LogicalColour -> NPieces) -> LogicalColour -> NPieces
forall a b. (a -> b) -> a -> b
$ LogicalColour
Attribute.LogicalColour.Black) ((LogicalColour -> NPieces) -> NPieces)
-> ((LogicalColour -> NPieces) -> NPieces)
-> (LogicalColour -> NPieces)
-> (NPieces, NPieces)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& ((LogicalColour -> NPieces) -> LogicalColour -> NPieces
forall a b. (a -> b) -> a -> b
$ LogicalColour
Attribute.LogicalColour.White) ((LogicalColour -> NPieces) -> (NPieces, NPieces))
-> (LogicalColour -> NPieces) -> (NPieces, NPieces)
forall a b. (a -> b) -> a -> b
$ (NPieces -> [Coordinates x y] -> NPieces)
-> NPieces -> CoordinatesByRank x y -> NPieces
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.Foldable.foldl' (\NPieces
acc -> (NPieces -> NPieces -> NPieces
forall a. Num a => a -> a -> a
+ NPieces
acc) (NPieces -> NPieces)
-> ([Coordinates x y] -> NPieces) -> [Coordinates x y] -> NPieces
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Coordinates x y] -> NPieces
forall (t :: * -> *) a. Foldable t => t a -> NPieces
length) NPieces
0 (CoordinatesByRank x y -> NPieces)
-> (LogicalColour -> CoordinatesByRank x y)
-> LogicalColour
-> NPieces
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)

	countPieces :: CoordinatesByRankByLogicalColour x y -> NPieces
countPieces MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= (NPieces -> CoordinatesByRank x y -> NPieces)
-> NPieces -> ByLogicalColour (CoordinatesByRank x y) -> NPieces
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.Foldable.foldl' (
		(NPieces -> [Coordinates x y] -> NPieces)
-> NPieces -> CoordinatesByRank x y -> NPieces
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.Foldable.foldl' ((NPieces -> [Coordinates x y] -> NPieces)
 -> NPieces -> CoordinatesByRank x y -> NPieces)
-> (NPieces -> [Coordinates x y] -> NPieces)
-> NPieces
-> CoordinatesByRank x y
-> NPieces
forall a b. (a -> b) -> a -> b
$ \NPieces
acc -> (NPieces -> NPieces -> NPieces
forall a. Num a => a -> a -> a
+ NPieces
acc) (NPieces -> NPieces)
-> ([Coordinates x y] -> NPieces) -> [Coordinates x y] -> NPieces
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Coordinates x y] -> NPieces
forall (t :: * -> *) a. Foldable t => t a -> NPieces
length
	 ) NPieces
0 ByLogicalColour (CoordinatesByRank x y)
byLogicalColour

	countPieceDifferenceByRank :: CoordinatesByRankByLogicalColour x y -> NPiecesByRank
countPieceDifferenceByRank MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [NPieces] -> NPiecesByRank
forall (a :: * -> * -> *) e. IArray a e => [e] -> a Rank e
Attribute.Rank.listArrayByRank ([NPieces] -> NPiecesByRank)
-> ((LogicalColour -> [NPieces]) -> [NPieces])
-> (LogicalColour -> [NPieces])
-> NPiecesByRank
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([NPieces] -> [NPieces] -> [NPieces])
-> ([NPieces], [NPieces]) -> [NPieces]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (
		(NPieces -> NPieces -> NPieces)
-> [NPieces] -> [NPieces] -> [NPieces]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-)
	 ) (([NPieces], [NPieces]) -> [NPieces])
-> ((LogicalColour -> [NPieces]) -> ([NPieces], [NPieces]))
-> (LogicalColour -> [NPieces])
-> [NPieces]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (
		((LogicalColour -> [NPieces]) -> LogicalColour -> [NPieces]
forall a b. (a -> b) -> a -> b
$ LogicalColour
Attribute.LogicalColour.White) ((LogicalColour -> [NPieces]) -> [NPieces])
-> ((LogicalColour -> [NPieces]) -> [NPieces])
-> (LogicalColour -> [NPieces])
-> ([NPieces], [NPieces])
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& ((LogicalColour -> [NPieces]) -> LogicalColour -> [NPieces]
forall a b. (a -> b) -> a -> b
$ LogicalColour
Attribute.LogicalColour.Black)
	 ) ((LogicalColour -> [NPieces]) -> NPiecesByRank)
-> (LogicalColour -> [NPieces]) -> NPiecesByRank
forall a b. (a -> b) -> a -> b
$ ([Coordinates x y] -> NPieces) -> [[Coordinates x y]] -> [NPieces]
forall a b. (a -> b) -> [a] -> [b]
map [Coordinates x y] -> NPieces
forall (t :: * -> *) a. Foldable t => t a -> NPieces
length ([[Coordinates x y]] -> [NPieces])
-> (LogicalColour -> [[Coordinates x y]])
-> LogicalColour
-> [NPieces]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordinatesByRank x y -> [[Coordinates x y]]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
Data.Array.IArray.elems (CoordinatesByRank x y -> [[Coordinates x y]])
-> (LogicalColour -> CoordinatesByRank x y)
-> LogicalColour
-> [[Coordinates x y]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)

	hasInsufficientMaterial :: CoordinatesByRankByLogicalColour x y -> Bool
hasInsufficientMaterial MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= (CoordinatesByRank x y -> Bool)
-> ByLogicalColour (CoordinatesByRank x y) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
Data.Foldable.all (
		\CoordinatesByRank x y
byRank -> (Rank -> Bool) -> [Rank] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (
			[Coordinates x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Coordinates x y] -> Bool)
-> (Rank -> [Coordinates x y]) -> Rank -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CoordinatesByRank x y
byRank CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)
		) [Rank]
Attribute.Rank.individuallySufficientMaterial
	 ) ByLogicalColour (CoordinatesByRank x y)
byLogicalColour Bool -> Bool -> Bool
&& case [Coordinates x y]
blackKnights [Coordinates x y] -> [Coordinates x y] -> [Coordinates x y]
forall a. [a] -> [a] -> [a]
++ [Coordinates x y]
whiteKnights of
		[]	-> [Coordinates x y] -> Bool
forall x y. (Enum x, Enum y) => [Coordinates x y] -> Bool
Cartesian.Coordinates.areSquaresIsochromatic [Coordinates x y]
bishops
		[Coordinates x y
_]	-> [Coordinates x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Coordinates x y]
bishops
		[Coordinates x y]
_	-> Bool
False
		where
			[[Coordinates x y]
blackKnights, [Coordinates x y]
blackBishops, [Coordinates x y]
whiteKnights, [Coordinates x y]
whiteBishops]	= [
				CoordinatesByRank x y
byRank CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
rank |
					CoordinatesByRank x y
byRank	<- ByLogicalColour (CoordinatesByRank x y) -> [CoordinatesByRank x y]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
Data.Array.IArray.elems ByLogicalColour (CoordinatesByRank x y)
byLogicalColour,
					Rank
rank	<- [Rank
Attribute.Rank.Knight, Rank
Attribute.Rank.Bishop]
			 ] -- List-comprehension.

			bishops :: [Coordinates x y]
bishops	= [Coordinates x y]
blackBishops [Coordinates x y] -> [Coordinates x y] -> [Coordinates x y]
forall a. [a] -> [a] -> [a]
++ [Coordinates x y]
whiteBishops

	hasBothKings :: CoordinatesByRankByLogicalColour x y -> Bool
hasBothKings MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (CoordinatesByRank x y -> Bool)
-> ByLogicalColour (CoordinatesByRank x y) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
Data.Foldable.any ([Coordinates x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Coordinates x y] -> Bool)
-> (CoordinatesByRank x y -> [Coordinates x y])
-> CoordinatesByRank x y
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
Attribute.Rank.King)) ByLogicalColour (CoordinatesByRank x y)
byLogicalColour	-- CAVEAT: true for more than one King per side also.

instance (Enum x, Enum y, Ord x, Ord y) => Component.Zobrist.Hashable2D CoordinatesByRankByLogicalColour x y {-CAVEAT: FlexibleInstances, MultiParamTypeClasses-} where
	listRandoms2D :: CoordinatesByRankByLogicalColour x y
-> Zobrist x y positionHash -> [positionHash]
listRandoms2D MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour } Zobrist x y positionHash
zobrist	= [
		LogicalColour
-> Rank
-> Coordinates x y
-> Zobrist x y positionHash
-> positionHash
forall x y positionHash.
(Enum x, Enum y, Ord x, Ord y) =>
LogicalColour
-> Rank
-> Coordinates x y
-> Zobrist x y positionHash
-> positionHash
Component.Zobrist.dereferenceRandomByCoordinatesByRankByLogicalColour LogicalColour
logicalColour Rank
rank Coordinates x y
coordinates Zobrist x y positionHash
zobrist |
			(LogicalColour
logicalColour, CoordinatesByRank x y
byRank)	<- ByLogicalColour (CoordinatesByRank x y)
-> [(LogicalColour, CoordinatesByRank x y)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ByLogicalColour (CoordinatesByRank x y)
byLogicalColour,
			(Rank
rank, [Coordinates x y]
coordinatesList)	<- CoordinatesByRank x y -> [(Rank, [Coordinates x y])]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs CoordinatesByRank x y
byRank,
			Coordinates x y
coordinates		<- [Coordinates x y]
coordinatesList
	 ] -- List-comprehension.

-- | Constructor.
fromMaybePieceByCoordinates :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => State.MaybePieceByCoordinates.MaybePieceByCoordinates x y -> CoordinatesByRankByLogicalColour x y
fromMaybePieceByCoordinates :: MaybePieceByCoordinates x y -> CoordinatesByRankByLogicalColour x y
fromMaybePieceByCoordinates MaybePieceByCoordinates x y
maybePieceByCoordinates	= ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
forall x y.
ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
MkCoordinatesByRankByLogicalColour (ByLogicalColour (CoordinatesByRank x y)
 -> CoordinatesByRankByLogicalColour x y)
-> (([(Piece, [Coordinates x y])], [(Piece, [Coordinates x y])])
    -> ByLogicalColour (CoordinatesByRank x y))
-> ([(Piece, [Coordinates x y])], [(Piece, [Coordinates x y])])
-> CoordinatesByRankByLogicalColour x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (
	\([(Piece, [Coordinates x y])]
b, [(Piece, [Coordinates x y])]
w) -> [CoordinatesByRank x y] -> ByLogicalColour (CoordinatesByRank x y)
forall (a :: * -> * -> *) e. IArray a e => [e] -> a LogicalColour e
Attribute.LogicalColour.listArrayByLogicalColour ([CoordinatesByRank x y]
 -> ByLogicalColour (CoordinatesByRank x y))
-> [CoordinatesByRank x y]
-> ByLogicalColour (CoordinatesByRank x y)
forall a b. (a -> b) -> a -> b
$ ([(Piece, [Coordinates x y])] -> CoordinatesByRank x y)
-> [[(Piece, [Coordinates x y])]] -> [CoordinatesByRank x y]
forall a b. (a -> b) -> [a] -> [b]
map (
		([Coordinates x y] -> [Coordinates x y] -> [Coordinates x y])
-> [Coordinates x y]
-> (Rank, Rank)
-> [(Rank, [Coordinates x y])]
-> CoordinatesByRank x y
forall (a :: * -> * -> *) e i e'.
(IArray a e, Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(i, e')] -> a i e
Data.Array.IArray.accumArray [Coordinates x y] -> [Coordinates x y] -> [Coordinates x y]
forall a. [a] -> [a] -> [a]
(++) [] (Rank
forall a. Bounded a => a
minBound, Rank
forall a. Bounded a => a
maxBound) ([(Rank, [Coordinates x y])] -> CoordinatesByRank x y)
-> ([(Piece, [Coordinates x y])] -> [(Rank, [Coordinates x y])])
-> [(Piece, [Coordinates x y])]
-> CoordinatesByRank x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Piece, [Coordinates x y]) -> (Rank, [Coordinates x y]))
-> [(Piece, [Coordinates x y])] -> [(Rank, [Coordinates x y])]
forall a b. (a -> b) -> [a] -> [b]
map ((Piece -> Rank)
-> (Piece, [Coordinates x y]) -> (Rank, [Coordinates x y])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first Piece -> Rank
Component.Piece.getRank)
	) [[(Piece, [Coordinates x y])]
b, [(Piece, [Coordinates x y])]
w]
 ) (([(Piece, [Coordinates x y])], [(Piece, [Coordinates x y])])
 -> CoordinatesByRankByLogicalColour x y)
-> ([(Piece, [Coordinates x y])], [(Piece, [Coordinates x y])])
-> CoordinatesByRankByLogicalColour x y
forall a b. (a -> b) -> a -> b
$ ((Piece, [Coordinates x y]) -> Bool)
-> [(Piece, [Coordinates x y])]
-> ([(Piece, [Coordinates x y])], [(Piece, [Coordinates x y])])
forall a. (a -> Bool) -> [a] -> ([a], [a])
Data.List.partition (
	Piece -> Bool
Component.Piece.isBlack (Piece -> Bool)
-> ((Piece, [Coordinates x y]) -> Piece)
-> (Piece, [Coordinates x y])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Piece, [Coordinates x y]) -> Piece
forall a b. (a, b) -> a
fst {-piece-}
 ) [
	(Piece
piece, [Coordinates x y
coordinates]) |
		(Coordinates x y
coordinates, Piece
piece)	<- MaybePieceByCoordinates x y -> [(Coordinates x y, Piece)]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> [LocatedPiece x y]
State.MaybePieceByCoordinates.findPieces MaybePieceByCoordinates x y
maybePieceByCoordinates
 ] -- List-comprehension.

-- | Dereference the array.
dereference
	:: Attribute.LogicalColour.LogicalColour
	-> Attribute.Rank.Rank
	-> CoordinatesByRankByLogicalColour x y
	-> [Cartesian.Coordinates.Coordinates x y]
{-# INLINE dereference #-}
dereference :: LogicalColour
-> Rank
-> CoordinatesByRankByLogicalColour x y
-> [Coordinates x y]
dereference LogicalColour
logicalColour Rank
rank MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! LogicalColour
logicalColour CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
rank

-- | Build an association-list.
assocs :: CoordinatesByRankByLogicalColour x y -> [(Component.Piece.Piece, [Cartesian.Coordinates.Coordinates x y])]
assocs :: CoordinatesByRankByLogicalColour x y
-> [(Piece, [Coordinates x y])]
assocs MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [
	(LogicalColour -> Rank -> Piece
Component.Piece.mkPiece LogicalColour
logicalColour Rank
rank, [Coordinates x y]
coordinatesList) |
		(LogicalColour
logicalColour, CoordinatesByRank x y
byRank)	<- ByLogicalColour (CoordinatesByRank x y)
-> [(LogicalColour, CoordinatesByRank x y)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ByLogicalColour (CoordinatesByRank x y)
byLogicalColour,
		(Rank
rank, [Coordinates x y]
coordinatesList)	<- CoordinatesByRank x y -> [(Rank, [Coordinates x y])]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs CoordinatesByRank x y
byRank
 ] -- List-comprehension.

-- | Access the coordinate-lists.
elems :: CoordinatesByRankByLogicalColour x y -> [Cartesian.Coordinates.Coordinates x y]
elems :: CoordinatesByRankByLogicalColour x y -> [Coordinates x y]
elems MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [
	Coordinates x y
coordinates |
		CoordinatesByRank x y
byRank		<- ByLogicalColour (CoordinatesByRank x y) -> [CoordinatesByRank x y]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
Data.Array.IArray.elems ByLogicalColour (CoordinatesByRank x y)
byLogicalColour,
		[Coordinates x y]
coordinatesList	<- CoordinatesByRank x y -> [[Coordinates x y]]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
Data.Array.IArray.elems CoordinatesByRank x y
byRank,
		Coordinates x y
coordinates	<- [Coordinates x y]
coordinatesList
 ] -- List-comprehension.

-- | Get the /coordinates/ of the @King@ of the specified /logical colour/.
getKingsCoordinates
	:: Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the @King@ to find.
	-> CoordinatesByRankByLogicalColour x y
	-> Cartesian.Coordinates.Coordinates x y
{-# INLINE getKingsCoordinates #-}
getKingsCoordinates :: LogicalColour
-> CoordinatesByRankByLogicalColour x y -> Coordinates x y
getKingsCoordinates LogicalColour
logicalColour MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= Bool -> Coordinates x y -> Coordinates x y
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Coordinates x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Coordinates x y]
coordinates) (Coordinates x y -> Coordinates x y)
-> Coordinates x y -> Coordinates x y
forall a b. (a -> b) -> a -> b
$ [Coordinates x y] -> Coordinates x y
forall a. [a] -> a
head [Coordinates x y]
coordinates {-there should be exactly one-} where
	coordinates :: [Coordinates x y]
coordinates	= ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! LogicalColour
logicalColour CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
Attribute.Rank.King

-- | The number of /piece/s in each file, for each /logical colour/.
type NPiecesByFileByLogicalColour x	= Attribute.LogicalColour.ByLogicalColour (Data.Map.Map x Component.Piece.NPieces)

{- |
	* Counts the number of @Pawn@s of each /logical colour/ with similar /x/-coordinates; their /y/-coordinate is irrelevant.

	* N.B.: files lacking any @Pawn@, don't feature in the results.
-}
countPawnsByFileByLogicalColour :: Ord x => CoordinatesByRankByLogicalColour x y -> NPiecesByFileByLogicalColour x
countPawnsByFileByLogicalColour :: CoordinatesByRankByLogicalColour x y
-> NPiecesByFileByLogicalColour x
countPawnsByFileByLogicalColour MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= (CoordinatesByRank x y -> Map x NPieces)
-> ByLogicalColour (CoordinatesByRank x y)
-> NPiecesByFileByLogicalColour x
forall (a :: * -> * -> *) e' e i.
(IArray a e', IArray a e, Ix i) =>
(e' -> e) -> a i e' -> a i e
Data.Array.IArray.amap (
	(Map x NPieces -> Coordinates x y -> Map x NPieces)
-> Map x NPieces -> [Coordinates x y] -> Map x NPieces
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
		\Map x NPieces
m Coordinates x y
coordinates -> (NPieces -> NPieces -> NPieces)
-> x -> NPieces -> Map x NPieces -> Map x NPieces
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Data.Map.Strict.insertWith ((NPieces -> NPieces) -> NPieces -> NPieces -> NPieces
forall a b. a -> b -> a
const NPieces -> NPieces
forall a. Enum a => a -> a
succ) (Coordinates x y -> x
forall x y. Coordinates x y -> x
Cartesian.Coordinates.getX Coordinates x y
coordinates) NPieces
1 Map x NPieces
m
	) Map x NPieces
forall k a. Map k a
Data.Map.empty ([Coordinates x y] -> Map x NPieces)
-> (CoordinatesByRank x y -> [Coordinates x y])
-> CoordinatesByRank x y
-> Map x NPieces
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
Attribute.Rank.Pawn)
 ) ByLogicalColour (CoordinatesByRank x y)
byLogicalColour

-- | Locates those /piece/s which satisfy the specified predicate.
findPieces
	:: (Component.Piece.Piece -> Bool)	-- ^ Predicate.
	-> CoordinatesByRankByLogicalColour x y
	-> [Component.Piece.LocatedPiece x y]
findPieces :: (Piece -> Bool)
-> CoordinatesByRankByLogicalColour x y -> [LocatedPiece x y]
findPieces Piece -> Bool
predicate MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [
	(Coordinates x y
coordinates, Piece
piece) |
		(LogicalColour
logicalColour, CoordinatesByRank x y
byRank)	<- ByLogicalColour (CoordinatesByRank x y)
-> [(LogicalColour, CoordinatesByRank x y)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ByLogicalColour (CoordinatesByRank x y)
byLogicalColour,
		(Rank
rank, [Coordinates x y]
coordinatesList)	<- CoordinatesByRank x y -> [(Rank, [Coordinates x y])]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs CoordinatesByRank x y
byRank,
		let piece :: Piece
piece	= LogicalColour -> Rank -> Piece
Component.Piece.mkPiece LogicalColour
logicalColour Rank
rank,
		Piece -> Bool
predicate Piece
piece,
		Coordinates x y
coordinates		<- [Coordinates x y]
coordinatesList
 ] -- List-comprehension.

-- | Locate all /piece/s of the specified /logical colour/.
findPiecesOfColour
	:: Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the /piece/s to find.
	-> CoordinatesByRankByLogicalColour x y
	-> [Component.Piece.LocatedPiece x y]
findPiecesOfColour :: LogicalColour
-> CoordinatesByRankByLogicalColour x y -> [LocatedPiece x y]
findPiecesOfColour LogicalColour
logicalColour MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [
	(Coordinates x y
coordinates, LogicalColour -> Rank -> Piece
Component.Piece.mkPiece LogicalColour
logicalColour Rank
rank) |
		(Rank
rank, [Coordinates x y]
coordinatesList)	<- CoordinatesByRank x y -> [(Rank, [Coordinates x y])]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs (CoordinatesByRank x y -> [(Rank, [Coordinates x y])])
-> CoordinatesByRank x y -> [(Rank, [Coordinates x y])]
forall a b. (a -> b) -> a -> b
$ ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! LogicalColour
logicalColour,
		Coordinates x y
coordinates		<- [Coordinates x y]
coordinatesList
 ] -- List-comprehension.

{- |
	* Find any @Knight@s of the specified /logical colour/, in attack-range around the specified /coordinates/.

	* CAVEAT: nothing is said about whether any /piece/ at the specified /coordinates/ belongs to the opponent, as one might expect.
-}
findProximateKnights :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the @Knight@ for which to search.
	-> Cartesian.Coordinates.Coordinates x y	-- ^ The destination to which the @Knight@ is required to be capable of jumping.
	-> CoordinatesByRankByLogicalColour x y
	-> [Cartesian.Coordinates.Coordinates x y]
{-# INLINABLE findProximateKnights #-}
findProximateKnights :: LogicalColour
-> Coordinates x y
-> CoordinatesByRankByLogicalColour x y
-> [Coordinates x y]
findProximateKnights LogicalColour
logicalColour Coordinates x y
destination MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= (Coordinates x y -> Bool) -> [Coordinates x y] -> [Coordinates x y]
forall a. (a -> Bool) -> [a] -> [a]
filter (
	\Coordinates x y
source -> Coordinates x y
source Coordinates x y -> Coordinates x y -> Bool
forall a. Eq a => a -> a -> Bool
/= Coordinates x y
destination {-guard against attempting to constructing a null vector-} Bool -> Bool -> Bool
&& Vector NPieces -> Bool
forall distance.
(Eq distance, Num distance) =>
Vector distance -> Bool
Cartesian.Vector.isKnightsMove (
		Coordinates x y -> Coordinates x y -> Vector NPieces
forall x y distance.
(Enum x, Enum y, Num distance, Ord distance) =>
Coordinates x y -> Coordinates x y -> Vector distance
Cartesian.Vector.measureDistance Coordinates x y
source Coordinates x y
destination	:: Cartesian.Vector.VectorInt
	)
 ) ([Coordinates x y] -> [Coordinates x y])
-> [Coordinates x y] -> [Coordinates x y]
forall a b. (a -> b) -> a -> b
$ ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! LogicalColour
logicalColour CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
Attribute.Rank.Knight

-- | A list of /coordinates/ for each /logical colour/.
type CoordinatesByLogicalColour x y	= Attribute.LogicalColour.ByLogicalColour [Cartesian.Coordinates.Coordinates x y]

-- | For each /logical colour/, find the /coordinates/ of any passed @Pawn@s (<https://en.wikipedia.org/wiki/Passed_pawn>).
findPassedPawnCoordinatesByLogicalColour :: (Enum x, Ord x, Ord y) => CoordinatesByRankByLogicalColour x y -> CoordinatesByLogicalColour x y
findPassedPawnCoordinatesByLogicalColour :: CoordinatesByRankByLogicalColour x y
-> CoordinatesByLogicalColour x y
findPassedPawnCoordinatesByLogicalColour MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [[Coordinates x y]] -> CoordinatesByLogicalColour x y
forall (a :: * -> * -> *) e. IArray a e => [e] -> a LogicalColour e
Attribute.LogicalColour.listArrayByLogicalColour [
	(Coordinates x y -> Bool) -> [Coordinates x y] -> [Coordinates x y]
forall a. (a -> Bool) -> [a] -> [a]
filter (
		\Coordinates x y
coordinates -> (x -> Bool) -> [x] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (
			Bool -> (y -> Bool) -> Maybe y -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe Bool
True {-the absence of an opposing Pawn doesn't impede advancement-} (
				(
					Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= LogicalColour -> Ordering
Attribute.Direction.advanceDirection LogicalColour
logicalColour	-- Either equal or backwards is OK.
				) (Ordering -> Bool) -> (y -> Ordering) -> y -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (
					{-opponent-} y -> y -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Coordinates x y -> y
forall x y. Coordinates x y -> y
Cartesian.Coordinates.getY Coordinates x y
coordinates
				) -- As a Pawn advances, it becomes "Passed" when the y-distance to the least advanced adjacent opposing Pawn, is either equal or backwards.
			 ) (Maybe y -> Bool) -> (x -> Maybe y) -> x -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (x -> Map x y -> Maybe y
forall k a. Ord k => k -> Map k a -> Maybe a
`Data.Map.lookup` Map x y
opposingPawnYByX)
		) ([x] -> Bool) -> (x -> [x]) -> x -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (x -> [x] -> [x]) -> (x, [x]) -> [x]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (:) ((x, [x]) -> [x]) -> (x -> (x, [x])) -> x -> [x]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (
			x -> x
forall a. a -> a
id (x -> x) -> (x -> [x]) -> x -> (x, [x])
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& x -> [x]
forall x. (Enum x, Eq x) => x -> [x]
Cartesian.Abscissa.getAdjacents
		) (x -> Bool) -> x -> Bool
forall a b. (a -> b) -> a -> b
$ Coordinates x y -> x
forall x y. Coordinates x y -> x
Cartesian.Coordinates.getX Coordinates x y
coordinates
	) ([Coordinates x y] -> [Coordinates x y])
-> [Coordinates x y] -> [Coordinates x y]
forall a b. (a -> b) -> a -> b
$ LogicalColour -> [Coordinates x y]
findPawns LogicalColour
logicalColour |
		LogicalColour
logicalColour	<- [LogicalColour]
Attribute.LogicalColour.range,
		let
			opponentsLogicalColour :: LogicalColour
opponentsLogicalColour	= LogicalColour -> LogicalColour
forall a. Opposable a => a -> a
Property.Opposable.getOpposite LogicalColour
logicalColour
			opposingPawnYByX :: Map x y
opposingPawnYByX	= (Map x y -> Coordinates x y -> Map x y)
-> Map x y -> [Coordinates x y] -> Map x y
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
				\Map x y
m Coordinates x y
coordinates -> (x -> y -> Map x y -> Map x y) -> (x, y) -> Map x y -> Map x y
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (
					(y -> y -> y) -> x -> y -> Map x y -> Map x y
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Data.Map.Strict.insertWith ((y -> y -> y) -> x -> y -> Map x y -> Map x y)
-> (y -> y -> y) -> x -> y -> Map x y -> Map x y
forall a b. (a -> b) -> a -> b
$ if LogicalColour -> Bool
Attribute.LogicalColour.isBlack LogicalColour
opponentsLogicalColour
						then y -> y -> y
forall a. Ord a => a -> a -> a
max
						else y -> y -> y
forall a. Ord a => a -> a -> a
min
				) {-only compare with the least advanced opposing Pawn in each file-} (
					Coordinates x y -> x
forall x y. Coordinates x y -> x
Cartesian.Coordinates.getX (Coordinates x y -> x)
-> (Coordinates x y -> y) -> Coordinates x y -> (x, y)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Coordinates x y -> y
forall x y. Coordinates x y -> y
Cartesian.Coordinates.getY (Coordinates x y -> (x, y)) -> Coordinates x y -> (x, y)
forall a b. (a -> b) -> a -> b
$ Coordinates x y
coordinates
				) Map x y
m
			 ) Map x y
forall k a. Map k a
Data.Map.empty ([Coordinates x y] -> Map x y) -> [Coordinates x y] -> Map x y
forall a b. (a -> b) -> a -> b
$ LogicalColour -> [Coordinates x y]
findPawns LogicalColour
opponentsLogicalColour
 ] {-list-comprehension-} where
	findPawns :: LogicalColour -> [Coordinates x y]
findPawns	= (CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
Attribute.Rank.Pawn) (CoordinatesByRank x y -> [Coordinates x y])
-> (LogicalColour -> CoordinatesByRank x y)
-> LogicalColour
-> [Coordinates x y]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)

-- | Calculate the total value of the /coordinates/ occupied by the /piece/s of either side.
sumPieceSquareValueByLogicalColour
	:: Num pieceSquareValue
	=> Component.PieceSquareArray.FindPieceSquareValue x y pieceSquareValue
	-> CoordinatesByRankByLogicalColour x y
	-> [pieceSquareValue]
{-# SPECIALISE sumPieceSquareValueByLogicalColour :: Component.PieceSquareArray.FindPieceSquareValue T.X T.Y T.PieceSquareValue -> CoordinatesByRankByLogicalColour T.X T.Y -> [T.PieceSquareValue] #-}
sumPieceSquareValueByLogicalColour :: FindPieceSquareValue x y pieceSquareValue
-> CoordinatesByRankByLogicalColour x y -> [pieceSquareValue]
sumPieceSquareValueByLogicalColour FindPieceSquareValue x y pieceSquareValue
findPieceSquareValue MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= [
	(pieceSquareValue -> (Rank, [Coordinates x y]) -> pieceSquareValue)
-> pieceSquareValue
-> [(Rank, [Coordinates x y])]
-> pieceSquareValue
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
		\pieceSquareValue
acc (Rank
rank, [Coordinates x y]
coordinatesList) -> (pieceSquareValue -> Coordinates x y -> pieceSquareValue)
-> pieceSquareValue -> [Coordinates x y] -> pieceSquareValue
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
			\pieceSquareValue
acc' Coordinates x y
coordinates -> pieceSquareValue
acc' pieceSquareValue -> pieceSquareValue -> pieceSquareValue
forall a. Num a => a -> a -> a
+ FindPieceSquareValue x y pieceSquareValue
findPieceSquareValue LogicalColour
logicalColour Rank
rank Coordinates x y
coordinates
		) pieceSquareValue
acc [Coordinates x y]
coordinatesList
	 ) pieceSquareValue
0 ([(Rank, [Coordinates x y])] -> pieceSquareValue)
-> [(Rank, [Coordinates x y])] -> pieceSquareValue
forall a b. (a -> b) -> a -> b
$ CoordinatesByRank x y -> [(Rank, [Coordinates x y])]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs CoordinatesByRank x y
byRank | (LogicalColour
logicalColour, CoordinatesByRank x y
byRank) <- ByLogicalColour (CoordinatesByRank x y)
-> [(LogicalColour, CoordinatesByRank x y)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ByLogicalColour (CoordinatesByRank x y)
byLogicalColour
 ] -- List-comprehension.

-- | Self-documentation.
type Transformation x y	= CoordinatesByRankByLogicalColour x y -> CoordinatesByRankByLogicalColour x y

-- | Remove the specified /coordinates/ from those recorded for the specified /rank/.
deleteCoordinates
	:: (Eq x, Eq y)
	=> Cartesian.Coordinates.Coordinates x y
	-> Attribute.Rank.Rank
	-> CoordinatesByRank x y
	-> CoordinatesByRank x y
deleteCoordinates :: Coordinates x y
-> Rank -> CoordinatesByRank x y -> CoordinatesByRank x y
deleteCoordinates Coordinates x y
coordinates Rank
rank CoordinatesByRank x y
byRank	= CoordinatesByRank x y
byRank CoordinatesByRank x y
-> [(Rank, [Coordinates x y])] -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// [(Rank
rank, Coordinates x y -> [Coordinates x y] -> [Coordinates x y]
forall a. Eq a => a -> [a] -> [a]
Data.List.delete Coordinates x y
coordinates ([Coordinates x y] -> [Coordinates x y])
-> [Coordinates x y] -> [Coordinates x y]
forall a b. (a -> b) -> a -> b
$ CoordinatesByRank x y
byRank CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
rank)]

-- | Adjust the array to reflect a new /move/.
movePiece
	:: (Eq x, Eq y)
	=> Component.Move.Move x y
	-> Component.Piece.Piece							-- ^ The piece which moved.
	-> Maybe Attribute.Rank.Rank							-- ^ The (possibly promoted) rank to place at the destination.
	-> Either (Cartesian.Coordinates.Coordinates x y) (Maybe Attribute.Rank.Rank)	-- ^ Either the destination of any passed @Pawn@, or the /rank/ of any /piece/ taken.
	-> Transformation x y
movePiece :: Move x y
-> Piece
-> Maybe Rank
-> Either (Coordinates x y) (Maybe Rank)
-> Transformation x y
movePiece Move x y
move Piece
sourcePiece Maybe Rank
maybePromotionRank Either (Coordinates x y) (Maybe Rank)
eitherPassingPawnsDestinationOrMaybeTakenRank MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
forall x y.
ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
MkCoordinatesByRankByLogicalColour (ByLogicalColour (CoordinatesByRank x y)
 -> CoordinatesByRankByLogicalColour x y)
-> ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
forall a b. (a -> b) -> a -> b
$ ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> [(LogicalColour, CoordinatesByRank x y)]
-> ByLogicalColour (CoordinatesByRank x y)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// (Coordinates x y
 -> [(LogicalColour, CoordinatesByRank x y)]
 -> [(LogicalColour, CoordinatesByRank x y)])
-> (Maybe Rank
    -> [(LogicalColour, CoordinatesByRank x y)]
    -> [(LogicalColour, CoordinatesByRank x y)])
-> Either (Coordinates x y) (Maybe Rank)
-> [(LogicalColour, CoordinatesByRank x y)]
-> [(LogicalColour, CoordinatesByRank x y)]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (
	(:) ((LogicalColour, CoordinatesByRank x y)
 -> [(LogicalColour, CoordinatesByRank x y)]
 -> [(LogicalColour, CoordinatesByRank x y)])
-> (Coordinates x y -> (LogicalColour, CoordinatesByRank x y))
-> Coordinates x y
-> [(LogicalColour, CoordinatesByRank x y)]
-> [(LogicalColour, CoordinatesByRank x y)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates x y -> Rank -> (LogicalColour, CoordinatesByRank x y)
`deleteOpponentsCoordinates` Rank
Attribute.Rank.Pawn)
 ) (
	([(LogicalColour, CoordinatesByRank x y)]
 -> [(LogicalColour, CoordinatesByRank x y)])
-> (Rank
    -> [(LogicalColour, CoordinatesByRank x y)]
    -> [(LogicalColour, CoordinatesByRank x y)])
-> Maybe Rank
-> [(LogicalColour, CoordinatesByRank x y)]
-> [(LogicalColour, CoordinatesByRank x y)]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [(LogicalColour, CoordinatesByRank x y)]
-> [(LogicalColour, CoordinatesByRank x y)]
forall a. a -> a
id {-quiet move-} ((Rank
  -> [(LogicalColour, CoordinatesByRank x y)]
  -> [(LogicalColour, CoordinatesByRank x y)])
 -> Maybe Rank
 -> [(LogicalColour, CoordinatesByRank x y)]
 -> [(LogicalColour, CoordinatesByRank x y)])
-> (Rank
    -> [(LogicalColour, CoordinatesByRank x y)]
    -> [(LogicalColour, CoordinatesByRank x y)])
-> Maybe Rank
-> [(LogicalColour, CoordinatesByRank x y)]
-> [(LogicalColour, CoordinatesByRank x y)]
forall a b. (a -> b) -> a -> b
$ (:) ((LogicalColour, CoordinatesByRank x y)
 -> [(LogicalColour, CoordinatesByRank x y)]
 -> [(LogicalColour, CoordinatesByRank x y)])
-> (Rank -> (LogicalColour, CoordinatesByRank x y))
-> Rank
-> [(LogicalColour, CoordinatesByRank x y)]
-> [(LogicalColour, CoordinatesByRank x y)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> Rank -> (LogicalColour, CoordinatesByRank x y)
deleteOpponentsCoordinates Coordinates x y
destination
 ) Either (Coordinates x y) (Maybe Rank)
eitherPassingPawnsDestinationOrMaybeTakenRank [
	let
		byRank :: CoordinatesByRank x y
byRank	= ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! LogicalColour
logicalColour
	in (
		LogicalColour
logicalColour,
		CoordinatesByRank x y
byRank CoordinatesByRank x y
-> [(Rank, [Coordinates x y])] -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// ((Rank, [Coordinates x y]) -> [(Rank, [Coordinates x y])])
-> (Rank
    -> (Rank, [Coordinates x y]) -> [(Rank, [Coordinates x y])])
-> Maybe Rank
-> (Rank, [Coordinates x y])
-> [(Rank, [Coordinates x y])]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe (
			(Rank, [Coordinates x y]) -> [(Rank, [Coordinates x y])]
forall (m :: * -> *) a. Monad m => a -> m a
return {-to List-monad-} ((Rank, [Coordinates x y]) -> [(Rank, [Coordinates x y])])
-> ((Rank, [Coordinates x y]) -> (Rank, [Coordinates x y]))
-> (Rank, [Coordinates x y])
-> [(Rank, [Coordinates x y])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Coordinates x y] -> [Coordinates x y])
-> (Rank, [Coordinates x y]) -> (Rank, [Coordinates x y])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
Control.Arrow.second (Coordinates x y
destination Coordinates x y -> [Coordinates x y] -> [Coordinates x y]
forall a. a -> [a] -> [a]
:)	-- Add the destination to the mover.
		) (
			\Rank
promotionRank -> (:) (
				Rank
promotionRank,
				Coordinates x y
destination Coordinates x y -> [Coordinates x y] -> [Coordinates x y]
forall a. a -> [a] -> [a]
: CoordinatesByRank x y
byRank CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Rank
promotionRank	-- Add the destination to the mover's promoted rank.
			) ([(Rank, [Coordinates x y])] -> [(Rank, [Coordinates x y])])
-> ((Rank, [Coordinates x y]) -> [(Rank, [Coordinates x y])])
-> (Rank, [Coordinates x y])
-> [(Rank, [Coordinates x y])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rank, [Coordinates x y]) -> [(Rank, [Coordinates x y])]
forall (m :: * -> *) a. Monad m => a -> m a
return {-to List-monad-}
		) Maybe Rank
maybePromotionRank (
			Rank -> Rank
forall a. a -> a
id (Rank -> Rank)
-> (Rank -> [Coordinates x y]) -> Rank -> (Rank, [Coordinates x y])
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Coordinates x y -> [Coordinates x y] -> [Coordinates x y]
forall a. Eq a => a -> [a] -> [a]
Data.List.delete (Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getSource Move x y
move) ([Coordinates x y] -> [Coordinates x y])
-> (Rank -> [Coordinates x y]) -> Rank -> [Coordinates x y]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CoordinatesByRank x y
byRank CoordinatesByRank x y -> Rank -> [Coordinates x y]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!) (Rank -> (Rank, [Coordinates x y]))
-> Rank -> (Rank, [Coordinates x y])
forall a b. (a -> b) -> a -> b
$ Piece -> Rank
Component.Piece.getRank Piece
sourcePiece
		)
	) -- Pair.
 ] where
	destination :: Coordinates x y
destination					= Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getDestination Move x y
move
	logicalColour :: LogicalColour
logicalColour					= Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
sourcePiece
	deleteOpponentsCoordinates :: Coordinates x y -> Rank -> (LogicalColour, CoordinatesByRank x y)
deleteOpponentsCoordinates Coordinates x y
coordinates Rank
rank	= LogicalColour -> LogicalColour
forall a. a -> a
id (LogicalColour -> LogicalColour)
-> (LogicalColour -> CoordinatesByRank x y)
-> LogicalColour
-> (LogicalColour, CoordinatesByRank x y)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Coordinates x y
-> Rank -> CoordinatesByRank x y -> CoordinatesByRank x y
forall x y.
(Eq x, Eq y) =>
Coordinates x y
-> Rank -> CoordinatesByRank x y -> CoordinatesByRank x y
deleteCoordinates Coordinates x y
coordinates Rank
rank (CoordinatesByRank x y -> CoordinatesByRank x y)
-> (LogicalColour -> CoordinatesByRank x y)
-> LogicalColour
-> CoordinatesByRank x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByLogicalColour (CoordinatesByRank x y)
byLogicalColour ByLogicalColour (CoordinatesByRank x y)
-> LogicalColour -> CoordinatesByRank x y
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!) (LogicalColour -> (LogicalColour, CoordinatesByRank x y))
-> LogicalColour -> (LogicalColour, CoordinatesByRank x y)
forall a b. (a -> b) -> a -> b
$ LogicalColour -> LogicalColour
forall a. Opposable a => a -> a
Property.Opposable.getOpposite LogicalColour
logicalColour

-- | Independently sort each list of /coordinates/.
sortCoordinates :: (Ord x, Ord y) => Transformation x y
sortCoordinates :: Transformation x y
sortCoordinates MkCoordinatesByRankByLogicalColour { deconstruct :: forall x y.
CoordinatesByRankByLogicalColour x y
-> ByLogicalColour (CoordinatesByRank x y)
deconstruct = ByLogicalColour (CoordinatesByRank x y)
byLogicalColour }	= ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
forall x y.
ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
MkCoordinatesByRankByLogicalColour (ByLogicalColour (CoordinatesByRank x y)
 -> CoordinatesByRankByLogicalColour x y)
-> ByLogicalColour (CoordinatesByRank x y)
-> CoordinatesByRankByLogicalColour x y
forall a b. (a -> b) -> a -> b
$ (CoordinatesByRank x y -> CoordinatesByRank x y)
-> ByLogicalColour (CoordinatesByRank x y)
-> ByLogicalColour (CoordinatesByRank x y)
forall (a :: * -> * -> *) e' e i.
(IArray a e', IArray a e, Ix i) =>
(e' -> e) -> a i e' -> a i e
Data.Array.IArray.amap (([Coordinates x y] -> [Coordinates x y])
-> CoordinatesByRank x y -> CoordinatesByRank x y
forall (a :: * -> * -> *) e' e i.
(IArray a e', IArray a e, Ix i) =>
(e' -> e) -> a i e' -> a i e
Data.Array.IArray.amap [Coordinates x y] -> [Coordinates x y]
forall a. Ord a => [a] -> [a]
Data.List.sort) ByLogicalColour (CoordinatesByRank x y)
byLogicalColour