{-# 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@]

	* Models the /board/ as a sparse array, each element of which might contain a /piece/.

	* N.B.: while this could be represented as @Data.Map.Map Coordinates Piece@, replacing 'Data.Array.IArray.!' with 'Data.Map.lookup',
	it actually required more space (despite having at most half the elements) & runs slower (because of 'compare').

	* cf. the piece-centric model of the board defined in "BishBosh.State.CoordinatesByRankByLogicalColour".
-}

module BishBosh.State.MaybePieceByCoordinates(
-- * Types
-- ** Type-synonyms
--	Transformation,
-- ** Data-types
	MaybePieceByCoordinates(),
-- * Constants
--	rankSeparator,
-- * Functions
	inferMoveType,
	findBlockingPiece,
	findAttackerInDirection,
	sumPieceSquareValueByLogicalColour,
	listDestinationsFor,
--	listToRaster,
--	shows2D,
	show2D,
-- ** Accessors
	dereference,
--	getPieces,
-- ** Mutators
	movePiece,
-- ** Predicates
	isVacant,
	isOccupied,
	isClear,
	isObstructed,
	isEnPassantMove
) where

import			Control.Applicative((<|>))
import			Control.Arrow((&&&), (***))
import			Control.Category((>>>))
import			Data.Array.IArray((!), (//))
import qualified	BishBosh.Attribute.ColourScheme				as Attribute.ColourScheme
import qualified	BishBosh.Attribute.Direction				as Attribute.Direction
import qualified	BishBosh.Attribute.LogicalColour			as Attribute.LogicalColour
import qualified	BishBosh.Attribute.LogicalColourOfSquare		as Attribute.LogicalColourOfSquare
import qualified	BishBosh.Attribute.MoveType				as Attribute.MoveType
import qualified	BishBosh.Attribute.PhysicalColour			as Attribute.PhysicalColour
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.Ordinate				as Cartesian.Ordinate
import qualified	BishBosh.Component.CastlingMove				as Component.CastlingMove
import qualified	BishBosh.Component.Move					as Component.Move
import qualified	BishBosh.Component.Piece				as Component.Piece
import qualified	BishBosh.Component.PieceSquareByCoordinatesByRank	as Component.PieceSquareByCoordinatesByRank
import qualified	BishBosh.Component.Zobrist				as Component.Zobrist
import qualified	BishBosh.Data.Exception					as Data.Exception
import qualified	BishBosh.Property.Empty					as Property.Empty
import qualified	BishBosh.Property.ExtendedPositionDescription		as Property.ExtendedPositionDescription
import qualified	BishBosh.Property.FixedMembership			as Property.FixedMembership
import qualified	BishBosh.Property.ForsythEdwards			as Property.ForsythEdwards
import qualified	BishBosh.Property.Opposable				as Property.Opposable
import qualified	BishBosh.Property.Orientated				as Property.Orientated
import qualified	BishBosh.Property.Reflectable				as Property.Reflectable
import qualified	BishBosh.StateProperty.Censor				as StateProperty.Censor
import qualified	BishBosh.StateProperty.Mutator				as StateProperty.Mutator
import qualified	BishBosh.StateProperty.Seeker				as StateProperty.Seeker
import qualified	BishBosh.Text.ShowList					as Text.ShowList
import qualified	BishBosh.Type.Length					as Type.Length
import qualified	BishBosh.Type.Mass					as Type.Mass
import qualified	Control.Arrow
import qualified	Control.DeepSeq
import qualified	Control.Exception
import qualified	Data.Array.IArray
import qualified	Data.Char
import qualified	Data.Default
import qualified	Data.List
import qualified	Data.List.Extra
import qualified	Data.Maybe
import qualified	ToolShed.Data.List.Runlength

{- |
	* This structure allows one to determine what /piece/ (if any) is located at specific /coordinates/.

	* N.B.: this could be implemented using 'Data.Vector.Vector', which being indexed by 'Int' is no longer polymorphic & permits many unsafe operations; but the result is no faster.
-}
newtype MaybePieceByCoordinates x y	= MkMaybePieceByCoordinates {
	MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct	:: Cartesian.Coordinates.ArrayByCoordinates x y (
		Maybe Component.Piece.Piece	-- Each square optionally contains a piece.
	)
} deriving (MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
(MaybePieceByCoordinates x y
 -> MaybePieceByCoordinates x y -> Bool)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> Bool)
-> Eq (MaybePieceByCoordinates x y)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
/= :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
$c/= :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
== :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
$c== :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
Eq, Eq (MaybePieceByCoordinates x y)
Eq (MaybePieceByCoordinates x y)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> Ordering)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> Bool)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> Bool)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> Bool)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> Bool)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y)
-> (MaybePieceByCoordinates x y
    -> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y)
-> Ord (MaybePieceByCoordinates x y)
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> Ordering
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Eq (MaybePieceByCoordinates x y)
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> Ordering
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
min :: MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
$cmin :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
max :: MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
$cmax :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
>= :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
$c>= :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
> :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
$c> :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
<= :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
$c<= :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
< :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
$c< :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y -> Bool
compare :: MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> Ordering
$ccompare :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y -> Ordering
$cp1Ord :: forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Eq (MaybePieceByCoordinates x y)
Ord)

-- | Used to separate the /ranks/ of the /board/ as represented by the IO-format <https://en.wikipedia.org/wiki/Forsyth%E2%80%93Edwards_Notation>.
rankSeparator :: Char
rankSeparator :: Char
rankSeparator	= Char
'/'

-- | Chops a list into a 2-D list.
listToRaster :: [a] -> [[a]]
listToRaster :: [a] -> [[a]]
listToRaster	= Int -> [a] -> [[a]]
forall a. Partial => Int -> [a] -> [[a]]
Data.List.Extra.chunksOf (Int -> [a] -> [[a]]) -> Int -> [a] -> [[a]]
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Cartesian.Abscissa.xLength {-CAVEAT: this also depends on the raster-order-}

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Read (MaybePieceByCoordinates x y) where
	readsPrec :: Int -> ReadS (MaybePieceByCoordinates x y)
readsPrec Int
_	= ReadS (MaybePieceByCoordinates x y)
forall a. ReadsFEN a => ReadS a
Property.ForsythEdwards.readsFEN

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Show (MaybePieceByCoordinates x y) where
	showsPrec :: Int -> MaybePieceByCoordinates x y -> ShowS
showsPrec Int
_	= MaybePieceByCoordinates x y -> ShowS
forall a. ShowsFEN a => a -> ShowS
Property.ForsythEdwards.showsFEN

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.ExtendedPositionDescription.ReadsEPD (MaybePieceByCoordinates x y) where
	readsEPD :: ReadS (MaybePieceByCoordinates x y)
readsEPD String
s
		| [[Maybe Piece]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Maybe Piece]]
rows Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Cartesian.Ordinate.yLength Bool -> Bool -> Bool
|| ([Maybe Piece] -> Bool) -> [[Maybe Piece]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (
			(Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Cartesian.Abscissa.xLength) (Int -> Bool) -> ([Maybe Piece] -> Int) -> [Maybe Piece] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length
		) [[Maybe Piece]]
rows		= []	-- No parse.
		| Bool
otherwise	= [(ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
forall x y.
ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
MkMaybePieceByCoordinates (ArrayByCoordinates x y (Maybe Piece)
 -> MaybePieceByCoordinates x y)
-> ([[Maybe Piece]] -> ArrayByCoordinates x y (Maybe Piece))
-> [[Maybe Piece]]
-> MaybePieceByCoordinates x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> ArrayByCoordinates x y (Maybe Piece)
forall (a :: * -> * -> *) e x y.
(IArray a e, Enum x, Enum y, Ord x, Ord y) =>
[e] -> a (Coordinates x y) e
Cartesian.Coordinates.listArrayByCoordinates ([Maybe Piece] -> ArrayByCoordinates x y (Maybe Piece))
-> ([[Maybe Piece]] -> [Maybe Piece])
-> [[Maybe Piece]]
-> ArrayByCoordinates x y (Maybe Piece)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Maybe Piece]] -> [Maybe Piece]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Maybe Piece]] -> MaybePieceByCoordinates x y)
-> [[Maybe Piece]] -> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ [[Maybe Piece]] -> [[Maybe Piece]]
forall a. [a] -> [a]
reverse [[Maybe Piece]]
rows, String
remainder)]
		where
			([[Maybe Piece]]
rows, String
remainder)	= (String -> [[Maybe Piece]])
-> (String, String) -> ([[Maybe Piece]], String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first (
				(String -> [Maybe Piece]) -> [String] -> [[Maybe Piece]]
forall a b. (a -> b) -> [a] -> [b]
map (
					(Char -> [Maybe Piece]) -> String -> [Maybe Piece]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (
						\Char
c -> case ReadS Int
forall a. Read a => ReadS a
reads [Char
c] of
							[(Int
i, String
"")]	-> Int -> Maybe Piece -> [Maybe Piece]
forall a. Int -> a -> [a]
replicate Int
i Maybe Piece
forall a. Maybe a
Nothing	-- Expand the runlength-code so that each row has the same length.
							[(Int, String)]
_		-> [Piece -> Maybe Piece
forall a. a -> Maybe a
Just Piece
piece | (Piece
piece, []) <- ReadS Piece
forall a. ReadsEPD a => ReadS a
Property.ExtendedPositionDescription.readsEPD [Char
c]] -- List-comprehension.
					)
				) ([String] -> [[Maybe Piece]])
-> (String -> [String]) -> String -> [[Maybe Piece]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> [String]
forall a. (a -> Bool) -> [a] -> [[a]]
Text.ShowList.splitOn (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
rankSeparator)
			 ) ((String, String) -> ([[Maybe Piece]], String))
-> (String -> (String, String))
-> String
-> ([[Maybe Piece]], String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (
				Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Char
rankSeparator Char -> ShowS
forall a. a -> [a] -> [a]
: (Piece -> String) -> [Piece] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Piece -> String
forall a. ShowsEPD a => a -> String
Property.ExtendedPositionDescription.showEPD [Piece]
Component.Piece.range String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Int -> String) -> [Int] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Int -> String
forall a. Show a => a -> String
show [Int
1 .. Int
Cartesian.Abscissa.xLength]
			 ) (String -> ([[Maybe Piece]], String))
-> String -> ([[Maybe Piece]], String)
forall a b. (a -> b) -> a -> b
$ ShowS
Data.List.Extra.trimStart String
s

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.ExtendedPositionDescription.ShowsEPD (MaybePieceByCoordinates x y) where
	showsEPD :: MaybePieceByCoordinates x y -> ShowS
showsEPD MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= (ShowS -> ShowS -> ShowS) -> [ShowS] -> ShowS
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 (
		>>>	-- Render the line with the highest y-coordinate first.
	 ) ([ShowS] -> ShowS)
-> ([Maybe Piece] -> [ShowS]) -> [Maybe Piece] -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS -> [ShowS] -> [ShowS]
forall a. a -> [a] -> [a]
Data.List.intersperse (
		Char -> ShowS
showChar Char
rankSeparator	-- Separate the lines.
	 ) ([ShowS] -> [ShowS])
-> ([Maybe Piece] -> [ShowS]) -> [Maybe Piece] -> [ShowS]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Maybe Piece] -> ShowS) -> [[Maybe Piece]] -> [ShowS]
forall a b. (a -> b) -> [a] -> [b]
map (
		(ShowS -> ShowS -> ShowS) -> [ShowS] -> ShowS
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ([ShowS] -> ShowS)
-> ([Maybe Piece] -> [ShowS]) -> [Maybe Piece] -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Maybe Piece) -> [ShowS]) -> [(Int, Maybe Piece)] -> [ShowS]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (
			\(Int
runLength, Maybe Piece
maybePiece) -> [ShowS] -> (Piece -> [ShowS]) -> Maybe Piece -> [ShowS]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [
				Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
runLength	-- Represent empty squares.
			] (
				Int -> ShowS -> [ShowS]
forall a. Int -> a -> [a]
replicate Int
runLength (ShowS -> [ShowS]) -> (Piece -> ShowS) -> Piece -> [ShowS]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> ShowS
forall a. ShowsEPD a => a -> ShowS
Property.ExtendedPositionDescription.showsEPD	-- Render each piece.
			) Maybe Piece
maybePiece
		) ([(Int, Maybe Piece)] -> [ShowS])
-> ([Maybe Piece] -> [(Int, Maybe Piece)])
-> [Maybe Piece]
-> [ShowS]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> [(Int, Maybe Piece)]
forall a. Eq a => [a] -> [Code a]
ToolShed.Data.List.Runlength.encode
	 ) ([[Maybe Piece]] -> [ShowS])
-> ([Maybe Piece] -> [[Maybe Piece]]) -> [Maybe Piece] -> [ShowS]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> [[Maybe Piece]]
forall a. [a] -> [[a]]
listToRaster ([Maybe Piece] -> ShowS) -> [Maybe Piece] -> ShowS
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece) -> [Maybe Piece]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
Data.Array.IArray.elems ArrayByCoordinates x y (Maybe Piece)
byCoordinates

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.ForsythEdwards.ReadsFEN (MaybePieceByCoordinates x y)

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.ForsythEdwards.ShowsFEN (MaybePieceByCoordinates x y)

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Data.Default.Default (MaybePieceByCoordinates x y) where
	def :: MaybePieceByCoordinates x y
def = String -> MaybePieceByCoordinates x y
forall a. ReadsFEN a => String -> a
Property.ForsythEdwards.readFEN (String -> MaybePieceByCoordinates x y)
-> ([String] -> String) -> [String] -> MaybePieceByCoordinates x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
Data.List.intercalate [Char
rankSeparator] ([String] -> MaybePieceByCoordinates x y)
-> [String] -> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ ((LogicalColour -> String) -> String)
-> [LogicalColour -> String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((LogicalColour -> String) -> LogicalColour -> String
forall a b. (a -> b) -> a -> b
$ LogicalColour
Attribute.LogicalColour.Black) [
		LogicalColour -> String
showNobility,
		LogicalColour -> String
showPawnRow
	 ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Int -> String -> [String]
forall a. Int -> a -> [a]
replicate Int
4 String
"8" [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ((LogicalColour -> String) -> String)
-> [LogicalColour -> String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((LogicalColour -> String) -> LogicalColour -> String
forall a b. (a -> b) -> a -> b
$ LogicalColour
Attribute.LogicalColour.White) [
		LogicalColour -> String
showPawnRow,
		LogicalColour -> String
showNobility
	 ] where
		showPieces :: [Component.Piece.Piece] -> String
		showPieces :: [Piece] -> String
showPieces	= (Piece -> String) -> [Piece] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Piece -> String
forall a. ShowsFEN a => a -> String
Property.ForsythEdwards.showFEN

		showPawnRow, showNobility :: Attribute.LogicalColour.LogicalColour -> String
		showPawnRow :: LogicalColour -> String
showPawnRow LogicalColour
logicalColour	= [Piece] -> String
showPieces ([Piece] -> String) -> (Piece -> [Piece]) -> Piece -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Piece -> [Piece]
forall a. Int -> a -> [a]
replicate (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Cartesian.Abscissa.xLength) (Piece -> String) -> Piece -> String
forall a b. (a -> b) -> a -> b
$ LogicalColour -> Piece
Component.Piece.mkPawn LogicalColour
logicalColour
		showNobility :: LogicalColour -> String
showNobility LogicalColour
logicalColour	= [Piece] -> String
showPieces ([Piece] -> String) -> [Piece] -> String
forall a b. (a -> b) -> a -> b
$ (Rank -> Piece) -> [Rank] -> [Piece]
forall a b. (a -> b) -> [a] -> [b]
map (LogicalColour -> Rank -> Piece
Component.Piece.mkPiece LogicalColour
logicalColour) [Rank]
Attribute.Rank.nobility

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.Reflectable.ReflectableOnX (MaybePieceByCoordinates x y) where
	reflectOnX :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
reflectOnX MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
forall x y.
ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
MkMaybePieceByCoordinates (ArrayByCoordinates x y (Maybe Piece)
 -> MaybePieceByCoordinates x y)
-> ([(Coordinates x y, Maybe Piece)]
    -> ArrayByCoordinates x y (Maybe Piece))
-> [(Coordinates x y, Maybe Piece)]
-> MaybePieceByCoordinates x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Coordinates x y, Maybe Piece)]
-> ArrayByCoordinates x y (Maybe Piece)
forall (a :: * -> * -> *) e x y.
(IArray a e, Enum x, Enum y, Ord x, Ord y) =>
[(Coordinates x y, e)] -> a (Coordinates x y) e
Cartesian.Coordinates.arrayByCoordinates ([(Coordinates x y, Maybe Piece)]
 -> ArrayByCoordinates x y (Maybe Piece))
-> ([(Coordinates x y, Maybe Piece)]
    -> [(Coordinates x y, Maybe Piece)])
-> [(Coordinates x y, Maybe Piece)]
-> ArrayByCoordinates x y (Maybe Piece)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Coordinates x y, Maybe Piece) -> (Coordinates x y, Maybe Piece))
-> [(Coordinates x y, Maybe Piece)]
-> [(Coordinates x y, Maybe Piece)]
forall a b. (a -> b) -> [a] -> [b]
map (
		Coordinates x y -> Coordinates x y
forall a. ReflectableOnX a => a -> a
Property.Reflectable.reflectOnX (Coordinates x y -> Coordinates x y)
-> (Maybe Piece -> Maybe Piece)
-> (Coordinates x y, Maybe Piece)
-> (Coordinates x y, Maybe Piece)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (Piece -> Piece) -> Maybe Piece -> Maybe Piece
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Piece -> Piece
forall a. Opposable a => a -> a
Property.Opposable.getOpposite
	 ) ([(Coordinates x y, Maybe Piece)] -> MaybePieceByCoordinates x y)
-> [(Coordinates x y, Maybe Piece)] -> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece)
-> [(Coordinates x y, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates x y (Maybe Piece)
byCoordinates

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.Reflectable.ReflectableOnY (MaybePieceByCoordinates x y) where
	reflectOnY :: MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
reflectOnY MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
forall x y.
ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
MkMaybePieceByCoordinates (ArrayByCoordinates x y (Maybe Piece)
 -> MaybePieceByCoordinates x y)
-> ArrayByCoordinates x y (Maybe Piece)
-> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ (Coordinates x y, Coordinates x y)
-> (Coordinates x y -> Coordinates x y)
-> ArrayByCoordinates x y (Maybe Piece)
-> ArrayByCoordinates x y (Maybe Piece)
forall (a :: * -> * -> *) e i j.
(IArray a e, Ix i, Ix j) =>
(i, i) -> (i -> j) -> a j e -> a i e
Data.Array.IArray.ixmap (Coordinates x y
forall a. Bounded a => a
minBound, Coordinates x y
forall a. Bounded a => a
maxBound) Coordinates x y -> Coordinates x y
forall a. ReflectableOnY a => a -> a
Property.Reflectable.reflectOnY ArrayByCoordinates x y (Maybe Piece)
byCoordinates

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Property.Empty.Empty (MaybePieceByCoordinates x y) where
	empty :: MaybePieceByCoordinates x y
empty	= ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
forall x y.
ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
MkMaybePieceByCoordinates (ArrayByCoordinates x y (Maybe Piece)
 -> MaybePieceByCoordinates x y)
-> ([Maybe Piece] -> ArrayByCoordinates x y (Maybe Piece))
-> [Maybe Piece]
-> MaybePieceByCoordinates x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> ArrayByCoordinates x y (Maybe Piece)
forall (a :: * -> * -> *) e x y.
(IArray a e, Enum x, Enum y, Ord x, Ord y) =>
[e] -> a (Coordinates x y) e
Cartesian.Coordinates.listArrayByCoordinates ([Maybe Piece] -> MaybePieceByCoordinates x y)
-> [Maybe Piece] -> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ Maybe Piece -> [Maybe Piece]
forall a. a -> [a]
repeat Maybe Piece
forall a. Empty a => a
Property.Empty.empty

instance (
	Control.DeepSeq.NFData	x,
	Control.DeepSeq.NFData	y
 ) => Control.DeepSeq.NFData (MaybePieceByCoordinates x y) where
	rnf :: MaybePieceByCoordinates x y -> ()
rnf MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= ArrayByCoordinates x y (Maybe Piece) -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf ArrayByCoordinates x y (Maybe Piece)
byCoordinates

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => StateProperty.Censor.Censor (MaybePieceByCoordinates x y) where
	countPiecesByLogicalColour :: MaybePieceByCoordinates x y -> (Int, Int)
countPiecesByLogicalColour	= ((Int, Int) -> Piece -> (Int, Int))
-> (Int, Int) -> [Piece] -> (Int, Int)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
		\(Int, Int)
acc Piece
piece -> let
			acc' :: (Int, Int)
acc'@(Int
nBlack, Int
nWhite)	= (
				if Piece -> Bool
Component.Piece.isBlack Piece
piece
					then (Int -> Int) -> (Int, Int) -> (Int, Int)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first
					else (Int -> Int) -> (Int, Int) -> (Int, Int)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
Control.Arrow.second
			 ) Int -> Int
forall a. Enum a => a -> a
succ (Int, Int)
acc
		in Int
nBlack Int -> (Int, Int) -> (Int, Int)
`seq` Int
nWhite Int -> (Int, Int) -> (Int, Int)
`seq` (Int, Int)
acc'
	 ) (Int
0, Int
0) ([Piece] -> (Int, Int))
-> (MaybePieceByCoordinates x y -> [Piece])
-> MaybePieceByCoordinates x y
-> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates x y -> [Piece]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> [Piece]
getPieces

	countPieces :: MaybePieceByCoordinates x y -> Int
countPieces	= Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int)
-> (MaybePieceByCoordinates x y -> Int)
-> MaybePieceByCoordinates x y
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Piece] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Piece] -> Int)
-> (MaybePieceByCoordinates x y -> [Piece])
-> MaybePieceByCoordinates x y
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates x y -> [Piece]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> [Piece]
getPieces

	countPieceDifferenceByRank :: MaybePieceByCoordinates x y -> NPiecesByRank
countPieceDifferenceByRank	= (Int -> Int -> Int)
-> Int -> (Rank, Rank) -> [(Rank, Int)] -> NPiecesByRank
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 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Int
0 (Rank
forall a. Bounded a => a
minBound, Rank
forall a. Bounded a => a
maxBound) ([(Rank, Int)] -> NPiecesByRank)
-> (MaybePieceByCoordinates x y -> [(Rank, Int)])
-> MaybePieceByCoordinates x y
-> NPiecesByRank
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Piece -> (Rank, Int)) -> [Piece] -> [(Rank, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (
		Piece -> Rank
Component.Piece.getRank (Piece -> Rank) -> (Piece -> Int) -> Piece -> (Rank, Int)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& (
			\Piece
piece -> (
				if Piece -> Bool
Component.Piece.isBlack Piece
piece
					then Int -> Int
forall a. Num a => a -> a
negate
					else Int -> Int
forall a. a -> a
id
			) Int
1
		)
	 ) ([Piece] -> [(Rank, Int)])
-> (MaybePieceByCoordinates x y -> [Piece])
-> MaybePieceByCoordinates x y
-> [(Rank, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates x y -> [Piece]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> [Piece]
getPieces

	hasInsufficientMaterial :: MaybePieceByCoordinates x y -> Bool
hasInsufficientMaterial MaybePieceByCoordinates x y
maybePieceByCoordinates	= ((Coordinates x y, Piece) -> Bool)
-> [(Coordinates x y, Piece)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (
		(Rank -> [Rank] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Rank]
Attribute.Rank.individuallySufficientMaterial) (Rank -> Bool)
-> ((Coordinates x y, Piece) -> Rank)
-> (Coordinates x y, Piece)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> Rank
Component.Piece.getRank (Piece -> Rank)
-> ((Coordinates x y, Piece) -> Piece)
-> (Coordinates x y, Piece)
-> Rank
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates x y, Piece) -> Piece
forall a b. (a, b) -> b
snd {-piece-}
	 ) [(Coordinates x y, Piece)]
locatedPieces 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
			locatedPieces :: [(Coordinates x y, Piece)]
locatedPieces	= MaybePieceByCoordinates x y -> [(Coordinates x y, Piece)]
forall (seeker :: * -> * -> *) x y.
Seeker seeker x y =>
seeker x y -> [LocatedPiece x y]
StateProperty.Seeker.findAllPieces MaybePieceByCoordinates x y
maybePieceByCoordinates

			[[Coordinates x y]
blackKnights, [Coordinates x y]
blackBishops, [Coordinates x y]
whiteKnights, [Coordinates x y]
whiteBishops]	= [
				[
					Coordinates x y
coordinates |
						(Coordinates x y
coordinates, Piece
piece)	<- [(Coordinates x y, Piece)]
locatedPieces,
						Piece
piece Piece -> Piece -> Bool
forall a. Eq a => a -> a -> Bool
== LogicalColour -> Rank -> Piece
Component.Piece.mkPiece LogicalColour
logicalColour Rank
rank
				] |
					LogicalColour
logicalColour	<- [LogicalColour]
forall a. FixedMembership a => [a]
Property.FixedMembership.members,
					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 :: MaybePieceByCoordinates x y -> Bool
hasBothKings MaybePieceByCoordinates x y
maybePieceByCoordinates	= case (Piece -> Bool) -> [Piece] -> ([Piece], [Piece])
forall a. (a -> Bool) -> [a] -> ([a], [a])
Data.List.partition Piece -> Bool
Component.Piece.isBlack ([Piece] -> ([Piece], [Piece]))
-> ([Piece] -> [Piece]) -> [Piece] -> ([Piece], [Piece])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Piece -> Bool) -> [Piece] -> [Piece]
forall a. (a -> Bool) -> [a] -> [a]
filter Piece -> Bool
Component.Piece.isKing ([Piece] -> ([Piece], [Piece])) -> [Piece] -> ([Piece], [Piece])
forall a b. (a -> b) -> a -> b
$ MaybePieceByCoordinates x y -> [Piece]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
MaybePieceByCoordinates x y -> [Piece]
getPieces MaybePieceByCoordinates x y
maybePieceByCoordinates of
		([Piece
_], [Piece
_])	-> Bool
True
		([Piece], [Piece])
_		-> Bool
False

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Component.Zobrist.Hashable2D MaybePieceByCoordinates x y {-CAVEAT: FlexibleInstances, MultiParamTypeClasses-} where
	listRandoms2D :: MaybePieceByCoordinates x y
-> Zobrist x y positionHash -> [positionHash]
listRandoms2D MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates } Zobrist x y positionHash
zobrist	= [
		Index x y -> Zobrist x y positionHash -> positionHash
forall x y positionHash.
(Enum x, Enum y, Ord x, Ord y) =>
Index x y -> Zobrist x y positionHash -> positionHash
Component.Zobrist.dereferenceRandomByCoordinatesByRankByLogicalColour (Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece, Piece -> Rank
Component.Piece.getRank Piece
piece, Coordinates x y
coordinates) Zobrist x y positionHash
zobrist |
			(Coordinates x y
coordinates, Just Piece
piece)	<- ArrayByCoordinates x y (Maybe Piece)
-> [(Coordinates x y, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates x y (Maybe Piece)
byCoordinates
	 ] -- 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.

	* CAVEAT: less efficient than 'State.CoordinatesByRankByLogicalColour.findProximateKnights'.
-}
instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => StateProperty.Seeker.Seeker MaybePieceByCoordinates x y {-CAVEAT: MultiParamTypeClasses-} where
	{-# SPECIALISE instance StateProperty.Seeker.Seeker MaybePieceByCoordinates Type.Length.X Type.Length.Y #-}
	findProximateKnights :: LogicalColour
-> Coordinates x y
-> MaybePieceByCoordinates x y
-> [Coordinates x y]
findProximateKnights LogicalColour
logicalColour Coordinates x y
destination MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= (Coordinates x y -> Bool) -> [Coordinates x y] -> [Coordinates x y]
forall a. (a -> Bool) -> [a] -> [a]
filter (
		(Maybe Piece -> Maybe Piece -> Bool
forall a. Eq a => a -> a -> Bool
== Piece -> Maybe Piece
forall a. a -> Maybe a
Just Piece
knight) (Maybe Piece -> Bool)
-> (Coordinates x y -> Maybe Piece) -> Coordinates x y -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)
	 ) ([Coordinates x y] -> [Coordinates x y])
-> [Coordinates x y] -> [Coordinates x y]
forall a b. (a -> b) -> a -> b
$ Coordinates x y -> Piece -> [Coordinates x y]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> Piece -> [Coordinates x y]
Component.Piece.findAttackDestinations Coordinates x y
destination Piece
knight where
		knight :: Piece
knight	= LogicalColour -> Piece
Component.Piece.mkKnight LogicalColour
logicalColour

	findPieces :: (Piece -> Bool)
-> MaybePieceByCoordinates x y -> [LocatedPiece x y]
findPieces Piece -> Bool
predicate MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= [
		(Coordinates x y
coordinates, Piece
piece) |
			(Coordinates x y
coordinates, Just Piece
piece)	<- ArrayByCoordinates x y (Maybe Piece)
-> [(Coordinates x y, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates x y (Maybe Piece)
byCoordinates,
			Piece -> Bool
predicate Piece
piece
	 ] -- List-comprehension.

instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => StateProperty.Mutator.Mutator MaybePieceByCoordinates x y {-CAVEAT: MultiParamTypeClasses-} where
	{-# SPECIALISE instance StateProperty.Mutator.Mutator MaybePieceByCoordinates Type.Length.X Type.Length.Y #-}
	defineCoordinates :: Maybe Piece
-> Coordinates x y
-> MaybePieceByCoordinates x y
-> MaybePieceByCoordinates x y
defineCoordinates Maybe Piece
maybePiece Coordinates x y
coordinates MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= Bool -> MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y
forall a. Partial => Bool -> a -> a
Control.Exception.assert (
		Maybe Piece -> Bool
forall a. Maybe a -> Bool
Data.Maybe.isJust Maybe Piece
maybePiece Bool -> Bool -> Bool
|| Maybe Piece -> Bool
forall a. Maybe a -> Bool
Data.Maybe.isJust (ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
coordinates)
	 ) (MaybePieceByCoordinates x y -> MaybePieceByCoordinates x y)
-> (ArrayByCoordinates x y (Maybe Piece)
    -> MaybePieceByCoordinates x y)
-> ArrayByCoordinates x y (Maybe Piece)
-> MaybePieceByCoordinates x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
forall x y.
ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
MkMaybePieceByCoordinates (ArrayByCoordinates x y (Maybe Piece)
 -> MaybePieceByCoordinates x y)
-> ArrayByCoordinates x y (Maybe Piece)
-> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> [(Coordinates x y, Maybe Piece)]
-> ArrayByCoordinates x y (Maybe Piece)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// [(Coordinates x y
coordinates, Maybe Piece
maybePiece)]

-- | Dereference the array.
dereference :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Cartesian.Coordinates.Coordinates x y
	-> MaybePieceByCoordinates x y
	-> Maybe Component.Piece.Piece
{-# INLINE dereference #-}
dereference :: Coordinates x y -> MaybePieceByCoordinates x y -> Maybe Piece
dereference Coordinates x y
coordinates MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
coordinates

-- | Infer the type of the specified /move/.
inferMoveType :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y,
	Show	x,
	Show	y
 )
	=> Component.Move.Move x y
	-> Maybe Attribute.Rank.Rank	-- ^ The /rank/ to which a @Pawn@ should be promoted; defaulting to @Queen@.
	-> MaybePieceByCoordinates x y
	-> Attribute.MoveType.MoveType
{-# SPECIALISE inferMoveType :: Component.Move.Move Type.Length.X Type.Length.Y -> Maybe Attribute.Rank.Rank -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> Attribute.MoveType.MoveType #-}
inferMoveType :: Move x y -> Maybe Rank -> MaybePieceByCoordinates x y -> MoveType
inferMoveType Move x y
move Maybe Rank
maybePromotionRank maybePieceByCoordinates :: MaybePieceByCoordinates x y
maybePieceByCoordinates@MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }
	| Just Piece
sourcePiece <- ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getSource Move x y
move	= MoveType
-> (CastlingMove x y -> MoveType)
-> Maybe (CastlingMove x y)
-> MoveType
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe (
		if Move x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Move x y -> MaybePieceByCoordinates x y -> Bool
isEnPassantMove Move x y
move MaybePieceByCoordinates x y
maybePieceByCoordinates
			then MoveType
Attribute.MoveType.enPassant	-- N.B.: if this move is valid, then one's opponent must have just double advanced an adjacent Pawn.
			else let
				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
			in Maybe Rank -> Maybe Rank -> MoveType
Attribute.MoveType.mkNormalMoveType (
				(Piece -> Rank) -> Maybe Piece -> Maybe Rank
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Piece -> Rank
Component.Piece.getRank (Maybe Piece -> Maybe Rank) -> Maybe Piece -> Maybe Rank
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
destination	-- Record the rank of any piece which was taken; the logical colour is inferred to be the opposite of 'sourcePiece'.
			) (Maybe Rank -> MoveType) -> Maybe Rank -> MoveType
forall a b. (a -> b) -> a -> b
$ if Coordinates x y -> Piece -> Bool
forall y x. (Enum y, Eq y) => Coordinates x y -> Piece -> Bool
Component.Piece.isPawnPromotion Coordinates x y
destination Piece
sourcePiece
				then Maybe Rank
maybePromotionRank Maybe Rank -> Maybe Rank -> Maybe Rank
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Rank -> Maybe Rank
forall a. a -> Maybe a
Just Rank
Attribute.Rank.defaultPromotionRank
				else Maybe Rank
forall a. Maybe a
Nothing
	) CastlingMove x y -> MoveType
forall x y. CastlingMove x y -> MoveType
Component.CastlingMove.getMoveType (Maybe (CastlingMove x y) -> MoveType)
-> Maybe (CastlingMove x y) -> MoveType
forall a b. (a -> b) -> a -> b
$ if Piece -> Bool
Component.Piece.isKing Piece
sourcePiece
		then (CastlingMove x y -> Bool)
-> [CastlingMove x y] -> Maybe (CastlingMove x y)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
Data.List.find (
			(Move x y -> Move x y -> Bool
forall a. Eq a => a -> a -> Bool
== Move x y
move) (Move x y -> Bool)
-> (CastlingMove x y -> Move x y) -> CastlingMove x y -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CastlingMove x y -> Move x y
forall x y. CastlingMove x y -> Move x y
Component.CastlingMove.getKingsMove
		) ([CastlingMove x y] -> Maybe (CastlingMove x y))
-> (LogicalColour -> [CastlingMove x y])
-> LogicalColour
-> Maybe (CastlingMove x y)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogicalColour -> [CastlingMove x y]
forall x y.
(Enum x, Enum y, Eq y, Ord x) =>
LogicalColour -> [CastlingMove x y]
Component.CastlingMove.getCastlingMoves (LogicalColour -> Maybe (CastlingMove x y))
-> LogicalColour -> Maybe (CastlingMove x y)
forall a b. (a -> b) -> a -> b
$ Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
sourcePiece
		else Maybe (CastlingMove x y)
forall a. Maybe a
Nothing
	| Bool
otherwise	= Exception -> MoveType
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> MoveType)
-> (String -> Exception) -> String -> MoveType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkSearchFailure (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.State.MaybePieceByCoordinates.inferMoveType:\tno piece exists at " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> ShowS
forall a. Show a => a -> ShowS
shows (Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getSource Move x y
move) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"; " (String -> MoveType) -> String -> MoveType
forall a b. (a -> b) -> a -> b
$ MaybePieceByCoordinates x y -> ShowS
forall a. Show a => a -> ShowS
shows MaybePieceByCoordinates x y
maybePieceByCoordinates String
"."

{- |
	* Lists the destination-/coordinates/ to which the referenced /piece/ can move, & the /rank/ of any /piece/ taken.

	* N.B.: one can reference either player's /piece/, regardless of whose turn it is to move.

	* CAVEAT: doesn't include either /Castling/ or /En-passant/, because this function doesn't know the history of the game.

	* CAVEAT: doesn't check whether any proposed /move/ exposes one's @King@, because this function doesn't assume the existence of a @King@.

	* CAVEAT: the opponent's @King@ may be one of the destinations returned, but only if it was actually their move next.

	* CAVEAT: doesn't typically check whether anything (let alone the specified /piece/) exists at the specified source-/coordinates/.
-}
listDestinationsFor :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Cartesian.Coordinates.Coordinates x y				-- ^ The source for which destinations are required.
	-> Component.Piece.Piece						-- ^ The /piece/ at the specified source.
	-> MaybePieceByCoordinates x y
	-> [(Cartesian.Coordinates.Coordinates x y, Maybe Attribute.Rank.Rank)]	-- ^ The destination & the rank of any piece taken.
{-# SPECIALISE listDestinationsFor :: Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> Component.Piece.Piece -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> [(Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y, Maybe Attribute.Rank.Rank)] #-}
listDestinationsFor :: Coordinates x y
-> Piece
-> MaybePieceByCoordinates x y
-> [(Coordinates x y, Maybe Rank)]
listDestinationsFor Coordinates x y
source Piece
piece maybePieceByCoordinates :: MaybePieceByCoordinates x y
maybePieceByCoordinates@MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= Bool
-> [(Coordinates x y, Maybe Rank)]
-> [(Coordinates x y, Maybe Rank)]
forall a. Partial => Bool -> a -> a
Control.Exception.assert (
	ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
source Maybe Piece -> Maybe Piece -> Bool
forall a. Eq a => a -> a -> Bool
== Piece -> Maybe Piece
forall a. a -> Maybe a
Just Piece
piece
 ) ([(Coordinates x y, Maybe Rank)]
 -> [(Coordinates x y, Maybe Rank)])
-> [(Coordinates x y, Maybe Rank)]
-> [(Coordinates x y, Maybe Rank)]
forall a b. (a -> b) -> a -> b
$ if Piece -> Rank
Component.Piece.getRank Piece
piece Rank -> [Rank] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Rank]
Attribute.Rank.fixedAttackRange
	then {-P,N,K-} let
		findAttackDestinations :: (Maybe Piece -> Bool) -> [(Coordinates x y, Maybe Rank)]
findAttackDestinations Maybe Piece -> Bool
predicate	= [
			(Coordinates x y
destination, (Piece -> Rank) -> Maybe Piece -> Maybe Rank
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Piece -> Rank
Component.Piece.getRank Maybe Piece
maybeDestinationPiece) |
				Coordinates x y
destination	<- Coordinates x y -> Piece -> [Coordinates x y]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> Piece -> [Coordinates x y]
Component.Piece.findAttackDestinations Coordinates x y
source Piece
piece,
				let maybeDestinationPiece :: Maybe Piece
maybeDestinationPiece	= ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
destination,
				Maybe Piece -> Bool
predicate Maybe Piece
maybeDestinationPiece
		 ] -- List-comprehension.
	in if Piece -> Bool
Component.Piece.isPawn Piece
piece
		then (Maybe Piece -> Bool) -> [(Coordinates x y, Maybe Rank)]
findAttackDestinations (
			Bool -> (Piece -> Bool) -> Maybe Piece -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe Bool
False {-unoccupied-} ((Piece -> Bool) -> Maybe Piece -> Bool)
-> (Piece -> Bool) -> Maybe Piece -> Bool
forall a b. (a -> b) -> a -> b
$ (LogicalColour -> LogicalColour -> Bool
forall a. Eq a => a -> a -> Bool
/= LogicalColour
logicalColour) (LogicalColour -> Bool)
-> (Piece -> LogicalColour) -> Piece -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> LogicalColour
Component.Piece.getLogicalColour
		) [(Coordinates x y, Maybe Rank)]
-> [(Coordinates x y, Maybe Rank)]
-> [(Coordinates x y, Maybe Rank)]
forall a. [a] -> [a] -> [a]
++ let
			advance	:: (Enum y, Ord y) => Cartesian.Coordinates.Coordinates x y -> Cartesian.Coordinates.Coordinates x y
			advance :: Coordinates x y -> Coordinates x y
advance	= LogicalColour -> Coordinates x y -> Coordinates x y
forall y x. (Enum y, Ord y) => LogicalColour -> Transformation x y
Cartesian.Coordinates.advance LogicalColour
logicalColour

			advancedLocation :: Coordinates x y
advancedLocation	= Coordinates x y -> Coordinates x y
forall y x. (Enum y, Ord y) => Coordinates x y -> Coordinates x y
advance Coordinates x y
source
		in if Coordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isVacant Coordinates x y
advancedLocation MaybePieceByCoordinates x y
maybePieceByCoordinates
			then (Coordinates x y -> (Coordinates x y, Maybe Rank))
-> [Coordinates x y] -> [(Coordinates x y, Maybe Rank)]
forall a b. (a -> b) -> [a] -> [b]
map (
				(Coordinates x y -> Maybe Rank -> (Coordinates x y, Maybe Rank))
-> Maybe Rank -> Coordinates x y -> (Coordinates x y, Maybe Rank)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) Maybe Rank
forall a. Maybe a
Nothing	-- N.B.: a Pawn can only take diagonally.
			) ([Coordinates x y] -> [(Coordinates x y, Maybe Rank)])
-> [Coordinates x y] -> [(Coordinates x y, Maybe Rank)]
forall a b. (a -> b) -> a -> b
$ Coordinates x y
advancedLocation Coordinates x y -> [Coordinates x y] -> [Coordinates x y]
forall a. a -> [a] -> [a]
: [
				Coordinates x y
doubleAdvancedLocation |
					LogicalColour -> Coordinates x y -> Bool
forall y x.
(Enum y, Eq y) =>
LogicalColour -> Coordinates x y -> Bool
Cartesian.Coordinates.isPawnsFirstRank LogicalColour
logicalColour Coordinates x y
source,
					let doubleAdvancedLocation :: Coordinates x y
doubleAdvancedLocation	= Coordinates x y -> Coordinates x y
forall y x. (Enum y, Ord y) => Coordinates x y -> Coordinates x y
advance Coordinates x y
advancedLocation,
					Coordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isVacant Coordinates x y
doubleAdvancedLocation MaybePieceByCoordinates x y
maybePieceByCoordinates
			] -- List-comprehension.
			else []	-- The path immediately ahead is blocked.
		else {-N,K-} (Maybe Piece -> Bool) -> [(Coordinates x y, Maybe Rank)]
findAttackDestinations ((Maybe Piece -> Bool) -> [(Coordinates x y, Maybe Rank)])
-> ((Piece -> Bool) -> Maybe Piece -> Bool)
-> (Piece -> Bool)
-> [(Coordinates x y, Maybe Rank)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> (Piece -> Bool) -> Maybe Piece -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe Bool
True {-unoccupied-} ((Piece -> Bool) -> [(Coordinates x y, Maybe Rank)])
-> (Piece -> Bool) -> [(Coordinates x y, Maybe Rank)]
forall a b. (a -> b) -> a -> b
$ (LogicalColour -> LogicalColour -> Bool
forall a. Eq a => a -> a -> Bool
/= LogicalColour
logicalColour) (LogicalColour -> Bool)
-> (Piece -> LogicalColour) -> Piece -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> LogicalColour
Component.Piece.getLogicalColour
	else {-R,B,Q-} let
		takeUntil :: [Coordinates x y] -> [(Coordinates x y, Maybe Rank)]
takeUntil (Coordinates x y
destination : [Coordinates x y]
remainder)
			| Just Piece
blockingPiece <- ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
destination	= [
				(
					Coordinates x y
destination,
					Rank -> Maybe Rank
forall a. a -> Maybe a
Just (Rank -> Maybe Rank) -> Rank -> Maybe Rank
forall a b. (a -> b) -> a -> b
$ Piece -> Rank
Component.Piece.getRank Piece
blockingPiece
				) | Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
blockingPiece LogicalColour -> LogicalColour -> Bool
forall a. Eq a => a -> a -> Bool
/= LogicalColour
logicalColour
			] -- List-comprehension.
			| Bool
otherwise	= (Coordinates x y
destination, Maybe Rank
forall a. Maybe a
Nothing) (Coordinates x y, Maybe Rank)
-> [(Coordinates x y, Maybe Rank)]
-> [(Coordinates x y, Maybe Rank)]
forall a. a -> [a] -> [a]
: [Coordinates x y] -> [(Coordinates x y, Maybe Rank)]
takeUntil [Coordinates x y]
remainder	-- Recurse.
		takeUntil [Coordinates x y]
_	= []
	in [
		(Coordinates x y, Maybe Rank)
pairs |
			Direction
direction	<- Piece -> [Direction]
Component.Piece.getAttackDirections Piece
piece,
			(Coordinates x y, Maybe Rank)
pairs		<- [Coordinates x y] -> [(Coordinates x y, Maybe Rank)]
takeUntil ([Coordinates x y] -> [(Coordinates x y, Maybe Rank)])
-> [Coordinates x y] -> [(Coordinates x y, Maybe Rank)]
forall a b. (a -> b) -> a -> b
$ Direction -> Coordinates x y -> [Coordinates x y]
forall x y.
(Enum x, Enum y) =>
Direction -> Coordinates x y -> [Coordinates x y]
Cartesian.Coordinates.extrapolate Direction
direction Coordinates x y
source
	] -- List-comprehension.
	where
		logicalColour :: LogicalColour
logicalColour	= Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece

-- | Show the /board/ in two dimensions, with /x/ & /y/ indexes.
shows2D :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Type.Length.Column	-- ^ The column-magnification.
	-> Attribute.ColourScheme.ColourScheme
	-> (Int, Int)	-- ^ The origin from which axes are labelled.
	-> MaybePieceByCoordinates x y
	-> ShowS	-- ^ The output suitable for display on a terminal.
shows2D :: Int
-> ColourScheme
-> (Int, Int)
-> MaybePieceByCoordinates x y
-> ShowS
shows2D Int
boardColumnMagnification ColourScheme
colourScheme (Int
xOrigin, Int
yOrigin) MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= (
	((Char, [(Coordinates x y, Char)]) -> ShowS -> ShowS)
-> ShowS -> [(Char, [(Coordinates x y, Char)])] -> ShowS
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (
		\(Char
y, [(Coordinates x y, Char)]
pairs) ShowS
showsRow -> ShowS
showsRow ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (
			Bool -> Int -> String
Attribute.PhysicalColour.selectGraphicsRendition Bool
True (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ PhysicalColour -> Int
Attribute.PhysicalColour.mkFgColourCode PhysicalColour
Attribute.PhysicalColour.green
		) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
y ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Coordinates x y, Char) -> ShowS -> ShowS)
-> ShowS -> [(Coordinates x y, Char)] -> ShowS
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (
			\(Coordinates x y
coordinates, Char
c) ShowS
acc' -> String -> ShowS
showString (
				Bool -> Int -> String
Attribute.PhysicalColour.selectGraphicsRendition Bool
False (Int -> String)
-> (PhysicalColour -> Int) -> PhysicalColour -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhysicalColour -> Int
Attribute.PhysicalColour.mkBgColourCode (PhysicalColour -> String) -> PhysicalColour -> String
forall a b. (a -> b) -> a -> b
$ (
					if LogicalColourOfSquare -> Bool
Attribute.LogicalColourOfSquare.isBlack (LogicalColourOfSquare -> Bool) -> LogicalColourOfSquare -> Bool
forall a b. (a -> b) -> a -> b
$ Coordinates x y -> LogicalColourOfSquare
forall x y.
(Enum x, Enum y) =>
Coordinates x y -> LogicalColourOfSquare
Cartesian.Coordinates.getLogicalColourOfSquare Coordinates x y
coordinates
						then ColourScheme -> PhysicalColour
Attribute.ColourScheme.getDarkSquareColour
						else ColourScheme -> PhysicalColour
Attribute.ColourScheme.getLightSquareColour
				 ) ColourScheme
colourScheme
			) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (
				Bool -> Int -> String
Attribute.PhysicalColour.selectGraphicsRendition Bool
True (Int -> String)
-> (PhysicalColour -> Int) -> PhysicalColour -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhysicalColour -> Int
Attribute.PhysicalColour.mkFgColourCode (PhysicalColour -> String) -> PhysicalColour -> String
forall a b. (a -> b) -> a -> b
$ (
					if Char -> Bool
Data.Char.isLower Char
c {-Black-}
						then ColourScheme -> PhysicalColour
Attribute.ColourScheme.getDarkPieceColour
						else ColourScheme -> PhysicalColour
Attribute.ColourScheme.getLightPieceColour
				 ) ColourScheme
colourScheme
			) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. let
				showPadding :: ShowS
showPadding	= String -> ShowS
showString (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int
forall a. Enum a => a -> a
pred Int
boardColumnMagnification) Int -> Char -> String
forall a. Int -> a -> [a]
`replicate` Char
' ')
			in ShowS
showPadding ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
c ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
showPadding ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
acc'
		) ShowS
showsReset [(Coordinates x y, Char)]
pairs ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'\n'
	) ShowS
forall a. a -> a
id ([(Char, [(Coordinates x y, Char)])] -> ShowS)
-> ([(Coordinates x y, Maybe Piece)]
    -> [(Char, [(Coordinates x y, Char)])])
-> [(Coordinates x y, Maybe Piece)]
-> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> [[(Coordinates x y, Char)]]
-> [(Char, [(Coordinates x y, Char)])]
forall a b. [a] -> [b] -> [(a, b)]
zip (
		Int -> ShowS
forall a. Int -> [a] -> [a]
take (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Cartesian.Ordinate.yLength) ShowS -> (Char -> String) -> Char -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall a. Enum a => a -> [a]
enumFrom (Char -> String) -> Char -> String
forall a b. (a -> b) -> a -> b
$ Int -> Char
Data.Char.chr Int
yOrigin
	) ([[(Coordinates x y, Char)]]
 -> [(Char, [(Coordinates x y, Char)])])
-> ([(Coordinates x y, Maybe Piece)]
    -> [[(Coordinates x y, Char)]])
-> [(Coordinates x y, Maybe Piece)]
-> [(Char, [(Coordinates x y, Char)])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Coordinates x y, Char)] -> [[(Coordinates x y, Char)]]
forall a. [a] -> [[a]]
listToRaster ([(Coordinates x y, Char)] -> [[(Coordinates x y, Char)]])
-> ([(Coordinates x y, Maybe Piece)] -> [(Coordinates x y, Char)])
-> [(Coordinates x y, Maybe Piece)]
-> [[(Coordinates x y, Char)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Coordinates x y, Maybe Piece) -> (Coordinates x y, Char))
-> [(Coordinates x y, Maybe Piece)] -> [(Coordinates x y, Char)]
forall a b. (a -> b) -> [a] -> [b]
map (
		(Maybe Piece -> Char)
-> (Coordinates x y, Maybe Piece) -> (Coordinates x y, Char)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
Control.Arrow.second ((Maybe Piece -> Char)
 -> (Coordinates x y, Maybe Piece) -> (Coordinates x y, Char))
-> ((Piece -> Char) -> Maybe Piece -> Char)
-> (Piece -> Char)
-> (Coordinates x y, Maybe Piece)
-> (Coordinates x y, Char)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> (Piece -> Char) -> Maybe Piece -> Char
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe Char
' ' ((Piece -> Char)
 -> (Coordinates x y, Maybe Piece) -> (Coordinates x y, Char))
-> (Piece -> Char)
-> (Coordinates x y, Maybe Piece)
-> (Coordinates x y, Char)
forall a b. (a -> b) -> a -> b
$ String -> Char
forall a. [a] -> a
head (String -> Char) -> (Piece -> String) -> Piece -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> String
forall a. Show a => a -> String
show	-- Represent each piece as a single character.
	) ([(Coordinates x y, Maybe Piece)] -> ShowS)
-> [(Coordinates x y, Maybe Piece)] -> ShowS
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece)
-> [(Coordinates x y, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates x y (Maybe Piece)
byCoordinates
 ) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (
	Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
boardColumnMagnification) Char
' '	-- Shift the line of x-axis labels right.
 ) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (
	Bool -> Int -> String
Attribute.PhysicalColour.selectGraphicsRendition Bool
True (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ PhysicalColour -> Int
Attribute.PhysicalColour.mkFgColourCode PhysicalColour
Attribute.PhysicalColour.green
 ) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShowS -> ShowS -> ShowS) -> ShowS -> [ShowS] -> ShowS
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ShowS
showsReset (
	ShowS -> [ShowS] -> [ShowS]
forall a. a -> [a] -> [a]
Data.List.intersperse (
		String -> ShowS
showString (String -> ShowS) -> String -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int
forall a. Enum a => a -> a
pred Int
boardColumnMagnification)) Char
' '	-- Separate each of the x-axis labels.
	) ([ShowS] -> [ShowS]) -> (Char -> [ShowS]) -> Char -> [ShowS]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> ShowS) -> String -> [ShowS]
forall a b. (a -> b) -> [a] -> [b]
map Char -> ShowS
showChar (String -> [ShowS]) -> (Char -> String) -> Char -> [ShowS]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
take (
		Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Cartesian.Abscissa.xLength
	) ShowS -> (Char -> String) -> Char -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall a. Enum a => a -> [a]
enumFrom (Char -> [ShowS]) -> Char -> [ShowS]
forall a b. (a -> b) -> a -> b
$ Int -> Char
Data.Char.chr Int
xOrigin
 ) where
	showsReset :: ShowS
	showsReset :: ShowS
showsReset	= String -> ShowS
showString (String -> ShowS) -> String -> ShowS
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> String
Attribute.PhysicalColour.selectGraphicsRendition Bool
False Int
0

-- | Show the board using a two-dimensional representation.
show2D :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Type.Length.Column	-- ^ The column-magnification.
	-> Attribute.ColourScheme.ColourScheme
	-> (Int, Int)	-- ^ The origin from which axes are labelled.
	-> MaybePieceByCoordinates x y
	-> String	-- ^ The output suitable for display on a terminal.
show2D :: Int
-> ColourScheme
-> (Int, Int)
-> MaybePieceByCoordinates x y
-> String
show2D Int
boardColumnMagnification ColourScheme
colourScheme (Int
xOrigin, Int
yOrigin) MaybePieceByCoordinates x y
maybePieceByCoordinates	= Int
-> ColourScheme
-> (Int, Int)
-> MaybePieceByCoordinates x y
-> ShowS
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Int
-> ColourScheme
-> (Int, Int)
-> MaybePieceByCoordinates x y
-> ShowS
shows2D Int
boardColumnMagnification ColourScheme
colourScheme (Int
xOrigin, Int
yOrigin) MaybePieceByCoordinates x y
maybePieceByCoordinates String
""

-- | Extract the pieces from the board, discarding their coordinates.
getPieces :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => MaybePieceByCoordinates x y -> [Component.Piece.Piece]
getPieces :: MaybePieceByCoordinates x y -> [Piece]
getPieces MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= [Maybe Piece] -> [Piece]
forall a. [Maybe a] -> [a]
Data.Maybe.catMaybes ([Maybe Piece] -> [Piece]) -> [Maybe Piece] -> [Piece]
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece) -> [Maybe Piece]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
Data.Array.IArray.elems ArrayByCoordinates x y (Maybe Piece)
byCoordinates

{- |
	* Find the first /piece/ of either /logical colour/, encountered along a straight line in the specified /direction/, from just after the specified /coordinates/.

	* CAVEAT: this is a performance-hotspot.
-}
findBlockingPiece :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Attribute.Direction.Direction		-- ^ The direction in which to search.
	-> Cartesian.Coordinates.Coordinates x y	-- ^ The starting point.
	-> MaybePieceByCoordinates x y
	-> Maybe (Component.Piece.LocatedPiece x y)
{-# SPECIALISE findBlockingPiece :: Attribute.Direction.Direction -> Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> Maybe (Component.Piece.LocatedPiece Type.Length.X Type.Length.Y) #-}
{- CAVEAT: too slow.
findBlockingPiece direction source MkMaybePieceByCoordinates { deconstruct = byCoordinates }	= Data.Maybe.listToMaybe . Data.Maybe.mapMaybe (
	uncurry fmap . ((,) &&& (byCoordinates !))
 ) $ Cartesian.Coordinates.extrapolate direction source
findBlockingPiece direction source maybePieceByCoordinates	= fmap (
	id &&& Data.Maybe.fromJust . (deconstruct maybePieceByCoordinates !)
 ) . Data.List.find (`isOccupied` maybePieceByCoordinates) $ Cartesian.Coordinates.extrapolate direction source
findBlockingPiece direction source MkMaybePieceByCoordinates { deconstruct = byCoordinates }	= slave $ Cartesian.Coordinates.extrapolate direction source where
	slave (coordinates : remainder)	= case byCoordinates ! coordinates of
		Nothing		-> slave remainder	-- Recurse.
		Just piece	-> Just (coordinates, piece)
	slave _				= Nothing
findBlockingPiece direction source MkMaybePieceByCoordinates { deconstruct = byCoordinates }	= Data.Maybe.listToMaybe [
	(coordinates, piece) |
		coordinates	<- Cartesian.Coordinates.extrapolate direction source,
		piece		<- Data.Maybe.maybeToList $ byCoordinates ! coordinates
 ] -- List-comprehension.
-}
findBlockingPiece :: Direction
-> Coordinates x y
-> MaybePieceByCoordinates x y
-> Maybe (LocatedPiece x y)
findBlockingPiece Direction
direction Coordinates x y
source MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= [LocatedPiece x y] -> Maybe (LocatedPiece x y)
forall a. [a] -> Maybe a
Data.Maybe.listToMaybe [
	(Coordinates x y
coordinates, Piece
piece) |
		(Coordinates x y
coordinates, Just Piece
piece)	<- (Coordinates x y -> (Coordinates x y, Maybe Piece))
-> [Coordinates x y] -> [(Coordinates x y, Maybe Piece)]
forall a b. (a -> b) -> [a] -> [b]
map (Coordinates x y -> Coordinates x y
forall a. a -> a
id (Coordinates x y -> Coordinates x y)
-> (Coordinates x y -> Maybe Piece)
-> Coordinates x y
-> (Coordinates x y, Maybe Piece)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& (ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)) ([Coordinates x y] -> [(Coordinates x y, Maybe Piece)])
-> [Coordinates x y] -> [(Coordinates x y, Maybe Piece)]
forall a b. (a -> b) -> a -> b
$ Direction -> Coordinates x y -> [Coordinates x y]
forall x y.
(Enum x, Enum y) =>
Direction -> Coordinates x y -> [Coordinates x y]
Cartesian.Coordinates.extrapolate Direction
direction Coordinates x y
source
 ] -- List-comprehension.

{- |
	* Find the /coordinates/ of any attacker who can strike the specified /coordinates/, in a straight line along the specified /direction/ (as seen by the target).

	* N.B.: there no requirement for there to actually be a /piece/ to attack at the specified target.
-}
findAttackerInDirection :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Attribute.LogicalColour.LogicalColour				-- ^ The defender's /logical colour/.
	-> Attribute.Direction.Direction					-- ^ The /direction/ from the /coordinates/ of concern; the opposite /direction/ from which an attacker might strike.
	-> Cartesian.Coordinates.Coordinates x y				-- ^ The defender's square.
	-> MaybePieceByCoordinates x y
	-> Maybe (Cartesian.Coordinates.Coordinates x y, Attribute.Rank.Rank)	-- ^ Any opposing /piece/ which can attack the specified square from the specified /direction/.
{-# SPECIALISE findAttackerInDirection :: Attribute.LogicalColour.LogicalColour -> Attribute.Direction.Direction -> Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> Maybe (Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y, Attribute.Rank.Rank) #-}
findAttackerInDirection :: LogicalColour
-> Direction
-> Coordinates x y
-> MaybePieceByCoordinates x y
-> Maybe (Coordinates x y, Rank)
findAttackerInDirection LogicalColour
destinationLogicalColour Direction
direction Coordinates x y
destination	= ((Coordinates x y, Piece) -> Maybe (Coordinates x y, Rank))
-> Maybe (Coordinates x y, Piece) -> Maybe (Coordinates x y, Rank)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
(=<<) (
	\(Coordinates x y
source, Piece
sourcePiece) -> if Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
sourcePiece LogicalColour -> LogicalColour -> Bool
forall a. Eq a => a -> a -> Bool
/= LogicalColour
destinationLogicalColour Bool -> Bool -> Bool
&& Coordinates x y -> Coordinates x y -> Piece -> Bool
forall x y.
(Enum x, Enum y) =>
Coordinates x y -> Coordinates x y -> Piece -> Bool
Component.Piece.canAttackAlong Coordinates x y
source Coordinates x y
destination Piece
sourcePiece
		then (Coordinates x y, Rank) -> Maybe (Coordinates x y, Rank)
forall a. a -> Maybe a
Just (Coordinates x y
source, Piece -> Rank
Component.Piece.getRank Piece
sourcePiece)
		else Maybe (Coordinates x y, Rank)
forall a. Maybe a
Nothing
 ) (Maybe (Coordinates x y, Piece) -> Maybe (Coordinates x y, Rank))
-> (MaybePieceByCoordinates x y -> Maybe (Coordinates x y, Piece))
-> MaybePieceByCoordinates x y
-> Maybe (Coordinates x y, Rank)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Direction
-> Coordinates x y
-> MaybePieceByCoordinates x y
-> Maybe (Coordinates x y, Piece)
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Direction
-> Coordinates x y
-> MaybePieceByCoordinates x y
-> Maybe (LocatedPiece x y)
findBlockingPiece Direction
direction Coordinates x y
destination

-- | Whether the specified /coordinates/ are unoccupied.
isVacant :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Cartesian.Coordinates.Coordinates x y
	-> MaybePieceByCoordinates x y
	-> Bool
{-# INLINE isVacant #-}
isVacant :: Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isVacant Coordinates x y
coordinates MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= Maybe Piece -> Bool
forall a. Maybe a -> Bool
Data.Maybe.isNothing (Maybe Piece -> Bool) -> Maybe Piece -> Bool
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
coordinates

-- | Whether the specified /coordinates/ are occupied.
isOccupied :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Cartesian.Coordinates.Coordinates x y
	-> MaybePieceByCoordinates x y
	-> Bool
{-# INLINE isOccupied #-}
isOccupied :: Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isOccupied Coordinates x y
coordinates	= Bool -> Bool
not (Bool -> Bool)
-> (MaybePieceByCoordinates x y -> Bool)
-> MaybePieceByCoordinates x y
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isVacant Coordinates x y
coordinates

{- |
	* Whether the open interval (source, destination) is unobstructed.

	* CAVEAT: the move must be straight, so that all intermediate points lie on squares of the board.

	* N.B.: the specified end-points are uninspected.
-}
isClear :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Cartesian.Coordinates.Coordinates x y	-- ^ Source.
	-> Cartesian.Coordinates.Coordinates x y	-- ^ Destination.
	-> MaybePieceByCoordinates x y
	-> Bool
{-# INLINABLE isClear #-}	-- N.B.: required to ensure specialisation of 'Cartesian.Coordinates.interpolate'.
{-# SPECIALISE isClear :: Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> Bool #-}
isClear :: Coordinates x y
-> Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isClear Coordinates x y
source Coordinates x y
destination MaybePieceByCoordinates x y
maybePieceByCoordinates	= Bool -> Bool -> Bool
forall a. Partial => Bool -> a -> a
Control.Exception.assert (
	Coordinates x y
source Coordinates x y -> Coordinates x y -> Bool
forall a. Eq a => a -> a -> Bool
/= Coordinates x y
destination Bool -> Bool -> Bool
&& Move x y -> Bool
forall a. Orientated a => a -> Bool
Property.Orientated.isStraight (Coordinates x y -> Coordinates x y -> Move x y
forall x y.
(Eq x, Eq y) =>
Coordinates x y -> Coordinates x y -> Move x y
Component.Move.mkMove Coordinates x y
source Coordinates x y
destination)
 ) (Bool -> Bool)
-> ([Coordinates x y] -> Bool) -> [Coordinates x y] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates x y -> Bool) -> [Coordinates x y] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Coordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> MaybePieceByCoordinates x y -> Bool
`isVacant` MaybePieceByCoordinates x y
maybePieceByCoordinates) ([Coordinates x y] -> Bool)
-> ([Coordinates x y] -> [Coordinates x y])
-> [Coordinates x y]
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Coordinates x y] -> [Coordinates x y]
forall a. [a] -> [a]
init {-discard the destination-} ([Coordinates x y] -> Bool) -> [Coordinates x y] -> Bool
forall a b. (a -> b) -> a -> b
$ Coordinates x y -> Coordinates x y -> [Coordinates x y]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> Coordinates x y -> [Coordinates x y]
Cartesian.Coordinates.interpolate Coordinates x y
source Coordinates x y
destination

-- | Whether there's a blockage between a /piece/ presumed to exist at the specified source, & a /piece/ presumed to exist @ the specified destination.
isObstructed :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Cartesian.Coordinates.Coordinates x y	-- ^ Source.
	-> Cartesian.Coordinates.Coordinates x y	-- ^ Destination.
	-> MaybePieceByCoordinates x y
	-> Bool
{-# SPECIALISE isObstructed :: Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> Bool #-}
isObstructed :: Coordinates x y
-> Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isObstructed Coordinates x y
source Coordinates x y
destination	= Bool -> Bool
not (Bool -> Bool)
-> (MaybePieceByCoordinates x y -> Bool)
-> MaybePieceByCoordinates x y
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y
-> Coordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y
-> Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isClear Coordinates x y
source Coordinates x y
destination

{- |
	* Whether the specified /move/ matches the rules for /en-passant/.

	* CAVEAT: assumes that the /move/ is valid;
	otherwise one would also need to confirm that the opponent's @Pawn@ had just double-advanced into the appropriate position.
-}
isEnPassantMove :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Component.Move.Move x y
	-> MaybePieceByCoordinates x y
	-> Bool
{-# SPECIALISE isEnPassantMove :: Component.Move.Move Type.Length.X Type.Length.Y -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> Bool #-}
isEnPassantMove :: Move x y -> MaybePieceByCoordinates x y -> Bool
isEnPassantMove Move x y
move maybePieceByCoordinates :: MaybePieceByCoordinates x y
maybePieceByCoordinates@MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }
	| Just Piece
piece	<- ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> Coordinates x y -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates x y
source
	, let logicalColour :: LogicalColour
logicalColour	= Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece
	= LogicalColour -> Coordinates x y -> Bool
forall y x.
(Enum y, Eq y) =>
LogicalColour -> Coordinates x y -> Bool
Cartesian.Coordinates.isEnPassantRank LogicalColour
logicalColour Coordinates x y
source Bool -> Bool -> Bool
&& Piece -> Bool
Component.Piece.isPawn Piece
piece Bool -> Bool -> Bool
&& Coordinates x y
destination Coordinates x y -> [Coordinates x y] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Coordinates x y -> Piece -> [Coordinates x y]
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> Piece -> [Coordinates x y]
Component.Piece.findAttackDestinations Coordinates x y
source Piece
piece Bool -> Bool -> Bool
&& Coordinates x y -> MaybePieceByCoordinates x y -> Bool
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Coordinates x y -> MaybePieceByCoordinates x y -> Bool
isVacant Coordinates x y
destination MaybePieceByCoordinates x y
maybePieceByCoordinates	-- The move is either En-passant or invalid.
	| Bool
otherwise	= Bool
False	-- No piece.
	where
		(Coordinates x y
source, Coordinates x y
destination)	= Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getSource (Move x y -> Coordinates x y)
-> (Move x y -> Coordinates x y)
-> Move x y
-> (Coordinates x y, Coordinates x y)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getDestination (Move x y -> (Coordinates x y, Coordinates x y))
-> Move x y -> (Coordinates x y, Coordinates x y)
forall a b. (a -> b) -> a -> b
$ Move x y
move

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

{- |
	* Adjust the array to reflect a move.

	* CAVEAT: regrettably this allocates an entire array.
-}
movePiece :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 )
	=> Component.Move.Move x y
	-> Component.Piece.Piece				-- ^ The (possibly promoted) piece to place at the destination.
	-> Maybe (Cartesian.Coordinates.Coordinates x y)	-- ^ Destination of any En-passant @Pawn@.
	-> Transformation x y
{-# SPECIALISE movePiece :: Component.Move.Move Type.Length.X Type.Length.Y -> Component.Piece.Piece -> Maybe (Cartesian.Coordinates.Coordinates Type.Length.X Type.Length.Y) -> Transformation Type.Length.X Type.Length.Y #-}
movePiece :: Move x y -> Piece -> Maybe (Coordinates x y) -> Transformation x y
movePiece Move x y
move Piece
destinationPiece Maybe (Coordinates x y)
maybeEnPassantDestination MkMaybePieceByCoordinates { deconstruct :: forall x y.
MaybePieceByCoordinates x y -> ArrayByCoordinates x y (Maybe Piece)
deconstruct = ArrayByCoordinates x y (Maybe Piece)
byCoordinates }	= ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
forall x y.
ArrayByCoordinates x y (Maybe Piece) -> MaybePieceByCoordinates x y
MkMaybePieceByCoordinates (ArrayByCoordinates x y (Maybe Piece)
 -> MaybePieceByCoordinates x y)
-> ArrayByCoordinates x y (Maybe Piece)
-> MaybePieceByCoordinates x y
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates x y (Maybe Piece)
byCoordinates ArrayByCoordinates x y (Maybe Piece)
-> [(Coordinates x y, Maybe Piece)]
-> ArrayByCoordinates x y (Maybe Piece)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// ([(Coordinates x y, Maybe Piece)]
 -> [(Coordinates x y, Maybe Piece)])
-> (Coordinates x y
    -> [(Coordinates x y, Maybe Piece)]
    -> [(Coordinates x y, Maybe Piece)])
-> Maybe (Coordinates x y)
-> [(Coordinates x y, Maybe Piece)]
-> [(Coordinates x y, Maybe Piece)]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [(Coordinates x y, Maybe Piece)]
-> [(Coordinates x y, Maybe Piece)]
forall a. a -> a
id (
	(:) ((Coordinates x y, Maybe Piece)
 -> [(Coordinates x y, Maybe Piece)]
 -> [(Coordinates x y, Maybe Piece)])
-> (Coordinates x y -> (Coordinates x y, Maybe Piece))
-> Coordinates x y
-> [(Coordinates x y, Maybe Piece)]
-> [(Coordinates x y, Maybe Piece)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates x y -> Maybe Piece -> (Coordinates x y, Maybe Piece))
-> Maybe Piece -> Coordinates x y -> (Coordinates x y, Maybe Piece)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) Maybe Piece
forall a. Maybe a
Nothing	-- Take the Pawn en-passant.
 ) Maybe (Coordinates x y)
maybeEnPassantDestination [
	(
		Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getSource Move x y
move,
		Maybe Piece
forall a. Maybe a
Nothing	-- Remove the piece from the source.
	), (
		Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getDestination Move x y
move,
		Piece -> Maybe Piece
forall a. a -> Maybe a
Just Piece
destinationPiece	-- Place the piece at the destination, removing any opposing incumbent as a side-effect.
	)
 ]

-- | Calculate the total value of the /coordinates/ occupied by the /piece/s of either side.
sumPieceSquareValueByLogicalColour :: (
	Enum	x,
	Enum	y,
	Num	pieceSquareValue,
	Ord	x,
	Ord	y
 )
	=> Component.PieceSquareByCoordinatesByRank.FindPieceSquareValue x y pieceSquareValue
	-> MaybePieceByCoordinates x y
	-> [pieceSquareValue]
{-# SPECIALISE sumPieceSquareValueByLogicalColour :: Component.PieceSquareByCoordinatesByRank.FindPieceSquareValue Type.Length.X Type.Length.Y Type.Mass.PieceSquareValue -> MaybePieceByCoordinates Type.Length.X Type.Length.Y -> [Type.Mass.PieceSquareValue] #-}
sumPieceSquareValueByLogicalColour :: FindPieceSquareValue x y pieceSquareValue
-> MaybePieceByCoordinates x y -> [pieceSquareValue]
sumPieceSquareValueByLogicalColour FindPieceSquareValue x y pieceSquareValue
findPieceSquareValue	= (
	\(pieceSquareValue
b, pieceSquareValue
w) -> [pieceSquareValue
b, pieceSquareValue
w]
 ) ((pieceSquareValue, pieceSquareValue) -> [pieceSquareValue])
-> (MaybePieceByCoordinates x y
    -> (pieceSquareValue, pieceSquareValue))
-> MaybePieceByCoordinates x y
-> [pieceSquareValue]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((pieceSquareValue, pieceSquareValue)
 -> (Coordinates x y, Piece)
 -> (pieceSquareValue, pieceSquareValue))
-> (pieceSquareValue, pieceSquareValue)
-> [(Coordinates x y, Piece)]
-> (pieceSquareValue, pieceSquareValue)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
	\(pieceSquareValue
b, pieceSquareValue
w) (Coordinates x y
coordinates, Piece
piece) -> let
		logicalColour :: LogicalColour
logicalColour		= Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece
		pieceSquareValue :: pieceSquareValue
pieceSquareValue	= FindPieceSquareValue x y pieceSquareValue
findPieceSquareValue LogicalColour
logicalColour (Piece -> Rank
Component.Piece.getRank Piece
piece) Coordinates x y
coordinates
	in if LogicalColour -> Bool
Attribute.LogicalColour.isBlack LogicalColour
logicalColour
		then let b' :: pieceSquareValue
b' = pieceSquareValue
b pieceSquareValue -> pieceSquareValue -> pieceSquareValue
forall a. Num a => a -> a -> a
+ pieceSquareValue
pieceSquareValue in pieceSquareValue
b' pieceSquareValue
-> (pieceSquareValue, pieceSquareValue)
-> (pieceSquareValue, pieceSquareValue)
`seq` (pieceSquareValue
b', pieceSquareValue
w)
		else let w' :: pieceSquareValue
w' = pieceSquareValue
w pieceSquareValue -> pieceSquareValue -> pieceSquareValue
forall a. Num a => a -> a -> a
+ pieceSquareValue
pieceSquareValue in pieceSquareValue
w' pieceSquareValue
-> (pieceSquareValue, pieceSquareValue)
-> (pieceSquareValue, pieceSquareValue)
`seq` (pieceSquareValue
b, pieceSquareValue
w')
 ) (pieceSquareValue
0, pieceSquareValue
0) ([(Coordinates x y, Piece)]
 -> (pieceSquareValue, pieceSquareValue))
-> (MaybePieceByCoordinates x y -> [(Coordinates x y, Piece)])
-> MaybePieceByCoordinates x y
-> (pieceSquareValue, pieceSquareValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates x y -> [(Coordinates x y, Piece)]
forall (seeker :: * -> * -> *) x y.
Seeker seeker x y =>
seeker x y -> [LocatedPiece x y]
StateProperty.Seeker.findAllPieces