{-
	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(),
-- * Functions
	inferMoveType,
	findBlockingPiece,
	findAttackerInDirection,
	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.ANSIColourCode			as Attribute.ANSIColourCode
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.Accountant				as Component.Accountant
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.Notation.Figurine				as Notation.Figurine
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.Hashable				as StateProperty.Hashable
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	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.Foldable
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	= MkMaybePieceByCoordinates {
	MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct	:: Cartesian.Coordinates.ArrayByCoordinates (
		Maybe Component.Piece.Piece	-- Each square optionally contains a piece.
	)
} deriving (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
(MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool)
-> (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool)
-> Eq MaybePieceByCoordinates
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
$c/= :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
== :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
$c== :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
Eq, Eq MaybePieceByCoordinates
Eq MaybePieceByCoordinates
-> (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Ordering)
-> (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool)
-> (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool)
-> (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool)
-> (MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool)
-> (MaybePieceByCoordinates
    -> MaybePieceByCoordinates -> MaybePieceByCoordinates)
-> (MaybePieceByCoordinates
    -> MaybePieceByCoordinates -> MaybePieceByCoordinates)
-> Ord MaybePieceByCoordinates
MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
MaybePieceByCoordinates -> MaybePieceByCoordinates -> Ordering
MaybePieceByCoordinates
-> MaybePieceByCoordinates -> MaybePieceByCoordinates
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
min :: MaybePieceByCoordinates
-> MaybePieceByCoordinates -> MaybePieceByCoordinates
$cmin :: MaybePieceByCoordinates
-> MaybePieceByCoordinates -> MaybePieceByCoordinates
max :: MaybePieceByCoordinates
-> MaybePieceByCoordinates -> MaybePieceByCoordinates
$cmax :: MaybePieceByCoordinates
-> MaybePieceByCoordinates -> MaybePieceByCoordinates
>= :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
$c>= :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
> :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
$c> :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
<= :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
$c<= :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
< :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
$c< :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Bool
compare :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Ordering
$ccompare :: MaybePieceByCoordinates -> MaybePieceByCoordinates -> Ordering
$cp1Ord :: Eq MaybePieceByCoordinates
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>.
-- | 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 Read MaybePieceByCoordinates where
	readsPrec :: Int -> ReadS MaybePieceByCoordinates
readsPrec Int
_	= ReadS MaybePieceByCoordinates
forall a. ReadsFEN a => ReadS a
Property.ForsythEdwards.readsFEN

instance Show MaybePieceByCoordinates where
	showsPrec :: Int -> MaybePieceByCoordinates -> ShowS
showsPrec Int
_	= MaybePieceByCoordinates -> ShowS
forall a. ShowsFEN a => a -> ShowS
Property.ForsythEdwards.showsFEN

instance Property.ExtendedPositionDescription.ReadsEPD MaybePieceByCoordinates where
	readsEPD :: ReadS MaybePieceByCoordinates
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 (Maybe Piece) -> MaybePieceByCoordinates
MkMaybePieceByCoordinates (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ([[Maybe Piece]] -> ArrayByCoordinates (Maybe Piece))
-> [[Maybe Piece]]
-> MaybePieceByCoordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> ArrayByCoordinates (Maybe Piece)
forall (a :: * -> * -> *) e. IArray a e => [e] -> a Coordinates e
Cartesian.Coordinates.listArrayByCoordinates ([Maybe Piece] -> ArrayByCoordinates (Maybe Piece))
-> ([[Maybe Piece]] -> [Maybe Piece])
-> [[Maybe Piece]]
-> ArrayByCoordinates (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)
-> [[Maybe Piece]] -> MaybePieceByCoordinates
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
Property.ExtendedPositionDescription.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
Property.ExtendedPositionDescription.rankSeparator Char -> ShowS
forall a. a -> [a] -> [a]
: String
Component.Piece.epdCharacterSet 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 Property.ExtendedPositionDescription.ShowsEPD MaybePieceByCoordinates where
	showsEPD :: MaybePieceByCoordinates -> ShowS
showsEPD MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (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
Property.ExtendedPositionDescription.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 (Maybe Piece) -> [Maybe Piece]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Data.Foldable.toList ArrayByCoordinates (Maybe Piece)
byCoordinates

instance Property.ForsythEdwards.ReadsFEN MaybePieceByCoordinates

instance Property.ForsythEdwards.ShowsFEN MaybePieceByCoordinates

instance Data.Default.Default MaybePieceByCoordinates where
	def :: MaybePieceByCoordinates
def = String -> MaybePieceByCoordinates
forall a. ReadsFEN a => String -> a
Property.ForsythEdwards.readFEN (String -> MaybePieceByCoordinates)
-> ([String] -> String) -> [String] -> MaybePieceByCoordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
Data.List.intercalate [Char
Property.ExtendedPositionDescription.rankSeparator] ([String] -> MaybePieceByCoordinates)
-> [String] -> MaybePieceByCoordinates
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 Property.Reflectable.ReflectableOnX MaybePieceByCoordinates where
	reflectOnX :: MaybePieceByCoordinates -> MaybePieceByCoordinates
reflectOnX MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
MkMaybePieceByCoordinates (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ([(Coordinates, Maybe Piece)]
    -> ArrayByCoordinates (Maybe Piece))
-> [(Coordinates, Maybe Piece)]
-> MaybePieceByCoordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Coordinates, Maybe Piece)] -> ArrayByCoordinates (Maybe Piece)
forall (a :: * -> * -> *) e.
IArray a e =>
[(Coordinates, e)] -> a Coordinates e
Cartesian.Coordinates.arrayByCoordinates ([(Coordinates, Maybe Piece)] -> ArrayByCoordinates (Maybe Piece))
-> ([(Coordinates, Maybe Piece)] -> [(Coordinates, Maybe Piece)])
-> [(Coordinates, Maybe Piece)]
-> ArrayByCoordinates (Maybe Piece)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Coordinates, Maybe Piece) -> (Coordinates, Maybe Piece))
-> [(Coordinates, Maybe Piece)] -> [(Coordinates, Maybe Piece)]
forall a b. (a -> b) -> [a] -> [b]
map (
		Coordinates -> Coordinates
forall a. ReflectableOnX a => a -> a
Property.Reflectable.reflectOnX (Coordinates -> Coordinates)
-> (Maybe Piece -> Maybe Piece)
-> (Coordinates, Maybe Piece)
-> (Coordinates, 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, Maybe Piece)] -> MaybePieceByCoordinates)
-> [(Coordinates, Maybe Piece)] -> MaybePieceByCoordinates
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates (Maybe Piece) -> [(Coordinates, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates (Maybe Piece)
byCoordinates

instance Property.Reflectable.ReflectableOnY MaybePieceByCoordinates where
	reflectOnY :: MaybePieceByCoordinates -> MaybePieceByCoordinates
reflectOnY MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
MkMaybePieceByCoordinates (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
forall a b. (a -> b) -> a -> b
$ (Coordinates, Coordinates)
-> (Coordinates -> Coordinates)
-> ArrayByCoordinates (Maybe Piece)
-> ArrayByCoordinates (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
forall a. Bounded a => a
minBound, Coordinates
forall a. Bounded a => a
maxBound) Coordinates -> Coordinates
forall a. ReflectableOnY a => a -> a
Property.Reflectable.reflectOnY ArrayByCoordinates (Maybe Piece)
byCoordinates

instance Property.Empty.Empty MaybePieceByCoordinates where
	empty :: MaybePieceByCoordinates
empty	= ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
MkMaybePieceByCoordinates (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ([Maybe Piece] -> ArrayByCoordinates (Maybe Piece))
-> [Maybe Piece]
-> MaybePieceByCoordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Piece] -> ArrayByCoordinates (Maybe Piece)
forall (a :: * -> * -> *) e. IArray a e => [e] -> a Coordinates e
Cartesian.Coordinates.listArrayByCoordinates ([Maybe Piece] -> MaybePieceByCoordinates)
-> [Maybe Piece] -> MaybePieceByCoordinates
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 MaybePieceByCoordinates where
	rnf :: MaybePieceByCoordinates -> ()
rnf MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= ArrayByCoordinates (Maybe Piece) -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf ArrayByCoordinates (Maybe Piece)
byCoordinates

instance StateProperty.Censor.Censor MaybePieceByCoordinates where
	countPiecesByLogicalColour :: MaybePieceByCoordinates -> (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 -> [Piece])
-> MaybePieceByCoordinates
-> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates -> [Piece]
getPieces

	countPieces :: MaybePieceByCoordinates -> Int
countPieces	= Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int)
-> (MaybePieceByCoordinates -> Int)
-> MaybePieceByCoordinates
-> 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 -> [Piece])
-> MaybePieceByCoordinates
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates -> [Piece]
getPieces

	countPieceDifferenceByRank :: MaybePieceByCoordinates -> 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 -> [(Rank, Int)])
-> MaybePieceByCoordinates
-> 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 -> [Piece])
-> MaybePieceByCoordinates
-> [(Rank, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates -> [Piece]
getPieces

	hasInsufficientMaterial :: MaybePieceByCoordinates -> Bool
hasInsufficientMaterial MaybePieceByCoordinates
maybePieceByCoordinates	= ((Coordinates, Piece) -> Bool) -> [(Coordinates, 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, Piece) -> Rank) -> (Coordinates, Piece) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> Rank
Component.Piece.getRank (Piece -> Rank)
-> ((Coordinates, Piece) -> Piece) -> (Coordinates, Piece) -> Rank
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates, Piece) -> Piece
forall a b. (a, b) -> b
snd {-piece-}
	 ) [(Coordinates, Piece)]
locatedPieces Bool -> Bool -> Bool
&& case [Coordinates]
blackKnights [Coordinates] -> [Coordinates] -> [Coordinates]
forall a. [a] -> [a] -> [a]
++ [Coordinates]
whiteKnights of
		[]	-> [Coordinates] -> Bool
Cartesian.Coordinates.areSquaresIsochromatic [Coordinates]
bishops
		[Coordinates
_]	-> [Coordinates] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Coordinates]
bishops
		[Coordinates]
_	-> Bool
False
		where
			locatedPieces :: [(Coordinates, Piece)]
locatedPieces	= MaybePieceByCoordinates -> [(Coordinates, Piece)]
forall seeker. Seeker seeker => seeker -> [(Coordinates, Piece)]
StateProperty.Seeker.findAllPieces MaybePieceByCoordinates
maybePieceByCoordinates

			[[Coordinates]
blackKnights, [Coordinates]
blackBishops, [Coordinates]
whiteKnights, [Coordinates]
whiteBishops]	= [
				[
					Coordinates
coordinates |
						(Coordinates
coordinates, Piece
piece)	<- [(Coordinates, 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]
bishops	= [Coordinates]
blackBishops [Coordinates] -> [Coordinates] -> [Coordinates]
forall a. [a] -> [a] -> [a]
++ [Coordinates]
whiteBishops

	hasBothKings :: MaybePieceByCoordinates -> Bool
hasBothKings MaybePieceByCoordinates
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 -> [Piece]
getPieces MaybePieceByCoordinates
maybePieceByCoordinates of
		([Piece
_], [Piece
_])	-> Bool
True
		([Piece], [Piece])
_		-> Bool
False

instance StateProperty.Hashable.Hashable MaybePieceByCoordinates where
	listRandoms :: MaybePieceByCoordinates -> Zobrist positionHash -> [positionHash]
listRandoms MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates } Zobrist positionHash
zobrist	= [
		Index -> Zobrist positionHash -> positionHash
forall positionHash. Index -> Zobrist positionHash -> positionHash
Component.Zobrist.dereferenceRandomByCoordinatesByRankByLogicalColour (Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece, Piece -> Rank
Component.Piece.getRank Piece
piece, Coordinates
coordinates) Zobrist positionHash
zobrist |
			(Coordinates
coordinates, Just Piece
piece)	<- ArrayByCoordinates (Maybe Piece) -> [(Coordinates, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates (Maybe Piece)
byCoordinates
	 ] -- List-comprehension.

instance StateProperty.Mutator.Mutator MaybePieceByCoordinates where
	defineCoordinates :: Maybe Piece
-> Coordinates
-> MaybePieceByCoordinates
-> MaybePieceByCoordinates
defineCoordinates Maybe Piece
maybePiece Coordinates
coordinates MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= Bool -> MaybePieceByCoordinates -> MaybePieceByCoordinates
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 (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
coordinates)
	 ) (MaybePieceByCoordinates -> MaybePieceByCoordinates)
-> (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ArrayByCoordinates (Maybe Piece)
-> MaybePieceByCoordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
MkMaybePieceByCoordinates (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece)
-> [(Coordinates, Maybe Piece)] -> ArrayByCoordinates (Maybe Piece)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// [(Coordinates
coordinates, Maybe Piece
maybePiece)]

{- |
	* 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 StateProperty.Seeker.Seeker MaybePieceByCoordinates where
	findProximateKnights :: LogicalColour
-> Coordinates -> MaybePieceByCoordinates -> [Coordinates]
findProximateKnights LogicalColour
logicalColour Coordinates
destination MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= (Coordinates -> Bool) -> [Coordinates] -> [Coordinates]
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 -> Maybe Piece) -> Coordinates -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)
	 ) ([Coordinates] -> [Coordinates]) -> [Coordinates] -> [Coordinates]
forall a b. (a -> b) -> a -> b
$ Coordinates -> Piece -> [Coordinates]
Component.Piece.findAttackDestinations Coordinates
destination Piece
knight where
		knight :: Piece
knight	= LogicalColour -> Piece
Component.Piece.mkKnight LogicalColour
logicalColour

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

instance Component.Accountant.Accountant MaybePieceByCoordinates where
	sumPieceSquareValueByLogicalColour :: PieceSquareByCoordinatesByRank pieceSquareValue
-> Int -> MaybePieceByCoordinates -> [pieceSquareValue]
sumPieceSquareValueByLogicalColour PieceSquareByCoordinatesByRank pieceSquareValue
pieceSquareByCoordinatesByRank Int
nPieces = (
		\(pieceSquareValue
b, pieceSquareValue
w) -> [pieceSquareValue
b, pieceSquareValue
w]
	 ) ((pieceSquareValue, pieceSquareValue) -> [pieceSquareValue])
-> (MaybePieceByCoordinates
    -> (pieceSquareValue, pieceSquareValue))
-> MaybePieceByCoordinates
-> [pieceSquareValue]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((pieceSquareValue, pieceSquareValue)
 -> (Coordinates, Piece) -> (pieceSquareValue, pieceSquareValue))
-> (pieceSquareValue, pieceSquareValue)
-> [(Coordinates, Piece)]
-> (pieceSquareValue, pieceSquareValue)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Data.List.foldl' (
		\(pieceSquareValue
b, pieceSquareValue
w) (Coordinates
coordinates, Piece
piece) -> let
			logicalColour :: LogicalColour
logicalColour		= Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece
			pieceSquareValue :: pieceSquareValue
pieceSquareValue	= PieceSquareByCoordinatesByRank pieceSquareValue
-> Int -> LogicalColour -> Rank -> Coordinates -> pieceSquareValue
forall pieceSquareValue.
PieceSquareByCoordinatesByRank pieceSquareValue
-> Int -> LogicalColour -> Rank -> Coordinates -> pieceSquareValue
Component.PieceSquareByCoordinatesByRank.findPieceSquareValue PieceSquareByCoordinatesByRank pieceSquareValue
pieceSquareByCoordinatesByRank Int
nPieces LogicalColour
logicalColour (Piece -> Rank
Component.Piece.getRank Piece
piece) Coordinates
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, Piece)] -> (pieceSquareValue, pieceSquareValue))
-> (MaybePieceByCoordinates -> [(Coordinates, Piece)])
-> MaybePieceByCoordinates
-> (pieceSquareValue, pieceSquareValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybePieceByCoordinates -> [(Coordinates, Piece)]
forall seeker. Seeker seeker => seeker -> [(Coordinates, Piece)]
StateProperty.Seeker.findAllPieces

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

-- | Infer the type of the specified /move/.
inferMoveType
	:: Component.Move.Move
	-> Maybe Attribute.Rank.Rank	-- ^ The /rank/ to which a @Pawn@ should be promoted; defaulting to @Queen@.
	-> MaybePieceByCoordinates
	-> Attribute.MoveType.MoveType
inferMoveType :: Move -> Maybe Rank -> MaybePieceByCoordinates -> MoveType
inferMoveType Move
move Maybe Rank
maybePromotionRank maybePieceByCoordinates :: MaybePieceByCoordinates
maybePieceByCoordinates@MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }
	| Just Piece
sourcePiece <- ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Move -> Coordinates
Component.Move.getSource Move
move	= MoveType
-> (CastlingMove -> MoveType) -> Maybe CastlingMove -> MoveType
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe (
		if Move -> MaybePieceByCoordinates -> Bool
isEnPassantMove Move
move MaybePieceByCoordinates
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
destination	= Move -> Coordinates
Component.Move.getDestination Move
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 (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
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 -> Piece -> Bool
Component.Piece.isPawnPromotion Coordinates
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 -> MoveType
Component.CastlingMove.getMoveType (Maybe CastlingMove -> MoveType) -> Maybe CastlingMove -> MoveType
forall a b. (a -> b) -> a -> b
$ if Piece -> Bool
Component.Piece.isKing Piece
sourcePiece
		then (CastlingMove -> Bool) -> [CastlingMove] -> Maybe CastlingMove
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
Data.List.find (
			(Move -> Move -> Bool
forall a. Eq a => a -> a -> Bool
== Move
move) (Move -> Bool) -> (CastlingMove -> Move) -> CastlingMove -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CastlingMove -> Move
Component.CastlingMove.getKingsMove
		) ([CastlingMove] -> Maybe CastlingMove)
-> (LogicalColour -> [CastlingMove])
-> LogicalColour
-> Maybe CastlingMove
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogicalColour -> [CastlingMove]
Component.CastlingMove.getCastlingMoves (LogicalColour -> Maybe CastlingMove)
-> LogicalColour -> Maybe CastlingMove
forall a b. (a -> b) -> a -> b
$ Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
sourcePiece
		else Maybe CastlingMove
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 -> ShowS
forall a. Show a => a -> ShowS
shows (Move -> Coordinates
Component.Move.getSource Move
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 -> ShowS
forall a. Show a => a -> ShowS
shows MaybePieceByCoordinates
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
	:: Cartesian.Coordinates.Coordinates					-- ^ The source for which destinations are required.
	-> Component.Piece.Piece						-- ^ The /piece/ at the specified source.
	-> MaybePieceByCoordinates
	-> [(Cartesian.Coordinates.Coordinates, Maybe Attribute.Rank.Rank)]	-- ^ The destination & the rank of any piece taken.
listDestinationsFor :: Coordinates
-> Piece -> MaybePieceByCoordinates -> [(Coordinates, Maybe Rank)]
listDestinationsFor Coordinates
source Piece
piece maybePieceByCoordinates :: MaybePieceByCoordinates
maybePieceByCoordinates@MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= Bool -> [(Coordinates, Maybe Rank)] -> [(Coordinates, Maybe Rank)]
forall a. Partial => Bool -> a -> a
Control.Exception.assert (
	ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
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, Maybe Rank)] -> [(Coordinates, Maybe Rank)])
-> [(Coordinates, Maybe Rank)] -> [(Coordinates, 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, Maybe Rank)]
findAttackDestinations Maybe Piece -> Bool
predicate	= [
			(Coordinates
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
destination	<- Coordinates -> Piece -> [Coordinates]
Component.Piece.findAttackDestinations Coordinates
source Piece
piece,
				let maybeDestinationPiece :: Maybe Piece
maybeDestinationPiece	= ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
destination,
				Maybe Piece -> Bool
predicate Maybe Piece
maybeDestinationPiece
		 ] -- List-comprehension.
	in if Piece -> Bool
Component.Piece.isPawn Piece
piece
		then (Maybe Piece -> Bool) -> [(Coordinates, 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, Maybe Rank)]
-> [(Coordinates, Maybe Rank)] -> [(Coordinates, Maybe Rank)]
forall a. [a] -> [a] -> [a]
++ let
			advance	:: Cartesian.Coordinates.Coordinates -> Cartesian.Coordinates.Coordinates
			advance :: Coordinates -> Coordinates
advance	= LogicalColour -> Coordinates -> Coordinates
Cartesian.Coordinates.advance LogicalColour
logicalColour

			advancedLocation :: Coordinates
advancedLocation	= Coordinates -> Coordinates
advance Coordinates
source
		in if Coordinates -> MaybePieceByCoordinates -> Bool
isVacant Coordinates
advancedLocation MaybePieceByCoordinates
maybePieceByCoordinates
			then (Coordinates -> (Coordinates, Maybe Rank))
-> [Coordinates] -> [(Coordinates, Maybe Rank)]
forall a b. (a -> b) -> [a] -> [b]
map (
				(Coordinates -> Maybe Rank -> (Coordinates, Maybe Rank))
-> Maybe Rank -> Coordinates -> (Coordinates, 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] -> [(Coordinates, Maybe Rank)])
-> [Coordinates] -> [(Coordinates, Maybe Rank)]
forall a b. (a -> b) -> a -> b
$ Coordinates
advancedLocation Coordinates -> [Coordinates] -> [Coordinates]
forall a. a -> [a] -> [a]
: [
				Coordinates
doubleAdvancedLocation |
					LogicalColour -> Coordinates -> Bool
Cartesian.Coordinates.isPawnsFirstRank LogicalColour
logicalColour Coordinates
source,
					let doubleAdvancedLocation :: Coordinates
doubleAdvancedLocation	= Coordinates -> Coordinates
advance Coordinates
advancedLocation,
					Coordinates -> MaybePieceByCoordinates -> Bool
isVacant Coordinates
doubleAdvancedLocation MaybePieceByCoordinates
maybePieceByCoordinates
			] -- List-comprehension.
			else []	-- The path immediately ahead is blocked.
		else {-N,K-} (Maybe Piece -> Bool) -> [(Coordinates, Maybe Rank)]
findAttackDestinations ((Maybe Piece -> Bool) -> [(Coordinates, Maybe Rank)])
-> ((Piece -> Bool) -> Maybe Piece -> Bool)
-> (Piece -> Bool)
-> [(Coordinates, 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, Maybe Rank)])
-> (Piece -> Bool) -> [(Coordinates, 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] -> [(Coordinates, Maybe Rank)]
takeUntil (Coordinates
destination : [Coordinates]
remainder)
			| Just Piece
blockingPiece <- ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
destination	= [
				(
					Coordinates
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
destination, Maybe Rank
forall a. Maybe a
Nothing) (Coordinates, Maybe Rank)
-> [(Coordinates, Maybe Rank)] -> [(Coordinates, Maybe Rank)]
forall a. a -> [a] -> [a]
: [Coordinates] -> [(Coordinates, Maybe Rank)]
takeUntil [Coordinates]
remainder	-- Recurse.
		takeUntil [Coordinates]
_	= []
	in [
		(Coordinates, Maybe Rank)
pairs |
			Direction
direction	<- Piece -> [Direction]
Component.Piece.getAttackDirections Piece
piece,
			(Coordinates, Maybe Rank)
pairs		<- [Coordinates] -> [(Coordinates, Maybe Rank)]
takeUntil ([Coordinates] -> [(Coordinates, Maybe Rank)])
-> [Coordinates] -> [(Coordinates, Maybe Rank)]
forall a b. (a -> b) -> a -> b
$ Direction -> Coordinates -> [Coordinates]
Cartesian.Coordinates.extrapolate Direction
direction Coordinates
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
	:: Type.Length.Column			-- ^ The column-magnification.
	-> Attribute.ColourScheme.ColourScheme
	-> Bool					-- ^ Whether to depict pieces as Unicode figurines.
	-> (Type.Length.X, Type.Length.Y)	-- ^ The origin from which axes are labelled.
	-> MaybePieceByCoordinates
	-> ShowS		-- ^ Output suitable for display on a terminal.
shows2D :: Int
-> ColourScheme
-> Bool
-> (Int, Int)
-> MaybePieceByCoordinates
-> ShowS
shows2D Int
boardColumnMagnification ColourScheme
colourScheme Bool
depictFigurine (Int
xOrigin, Int
yOrigin) MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= (
	((Char, [(Coordinates, Char)]) -> ShowS -> ShowS)
-> ShowS -> [(Char, [(Coordinates, Char)])] -> ShowS
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (
		\(Char
y, [(Coordinates, Char)]
pairs) ShowS
showsRow -> ShowS
showsRow ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
axisGraphicsRendition 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, Char) -> ShowS -> ShowS)
-> ShowS -> [(Coordinates, Char)] -> ShowS
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (
			\(Coordinates
coordinates, Char
c) ShowS
acc' -> String -> ShowS
showString (
				Bool -> ANSIColourCode -> String
Attribute.ANSIColourCode.selectGraphicsRendition Bool
False {-isBold-} (ANSIColourCode -> String)
-> (PhysicalColour -> ANSIColourCode) -> PhysicalColour -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhysicalColour -> ANSIColourCode
Attribute.ANSIColourCode.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 -> LogicalColourOfSquare
Cartesian.Coordinates.getLogicalColourOfSquare Coordinates
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 -> ANSIColourCode -> String
Attribute.ANSIColourCode.selectGraphicsRendition Bool
True {-isBold-} (ANSIColourCode -> String)
-> (PhysicalColour -> ANSIColourCode) -> PhysicalColour -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhysicalColour -> ANSIColourCode
Attribute.ANSIColourCode.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, 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, Char)])] -> ShowS)
-> ([(Coordinates, Maybe Piece)]
    -> [(Char, [(Coordinates, Char)])])
-> [(Coordinates, Maybe Piece)]
-> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> [[(Coordinates, Char)]] -> [(Char, [(Coordinates, 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 -> (Int -> String) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall a. Enum a => a -> [a]
enumFrom (Char -> String) -> (Int -> Char) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Char
Data.Char.chr (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
yOrigin
	) ([[(Coordinates, Char)]] -> [(Char, [(Coordinates, Char)])])
-> ([(Coordinates, Maybe Piece)] -> [[(Coordinates, Char)]])
-> [(Coordinates, Maybe Piece)]
-> [(Char, [(Coordinates, Char)])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Coordinates, Char)] -> [[(Coordinates, Char)]]
forall a. [a] -> [[a]]
listToRaster ([(Coordinates, Char)] -> [[(Coordinates, Char)]])
-> ([(Coordinates, Maybe Piece)] -> [(Coordinates, Char)])
-> [(Coordinates, Maybe Piece)]
-> [[(Coordinates, Char)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Coordinates, Maybe Piece) -> (Coordinates, Char))
-> [(Coordinates, Maybe Piece)] -> [(Coordinates, Char)]
forall a b. (a -> b) -> [a] -> [b]
map (
		(Maybe Piece -> Char)
-> (Coordinates, Maybe Piece) -> (Coordinates, Char)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
Control.Arrow.second ((Maybe Piece -> Char)
 -> (Coordinates, Maybe Piece) -> (Coordinates, Char))
-> ((Piece -> Char) -> Maybe Piece -> Char)
-> (Piece -> Char)
-> (Coordinates, Maybe Piece)
-> (Coordinates, 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, Maybe Piece) -> (Coordinates, Char))
-> (Piece -> Char)
-> (Coordinates, Maybe Piece)
-> (Coordinates, Char)
forall a b. (a -> b) -> a -> b
$ if Bool
depictFigurine
			then Piece -> Char
Notation.Figurine.toFigurine	-- Represent each piece as a Unicode figurine.
			else 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 an ASCII character.
	) ([(Coordinates, Maybe Piece)] -> ShowS)
-> [(Coordinates, Maybe Piece)] -> ShowS
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates (Maybe Piece) -> [(Coordinates, Maybe Piece)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
Data.Array.IArray.assocs ArrayByCoordinates (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 String
axisGraphicsRendition 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]) -> (Int -> [ShowS]) -> Int -> [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]) -> (Int -> String) -> Int -> [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 -> (Int -> String) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall a. Enum a => a -> [a]
enumFrom (Char -> String) -> (Int -> Char) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Char
Data.Char.chr (Int -> [ShowS]) -> Int -> [ShowS]
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
xOrigin
 ) where
	axisGraphicsRendition :: Attribute.ANSIColourCode.GraphicsRendition
	axisGraphicsRendition :: String
axisGraphicsRendition	= Bool -> ANSIColourCode -> String
Attribute.ANSIColourCode.selectGraphicsRendition Bool
True {-isBold-} (ANSIColourCode -> String) -> ANSIColourCode -> String
forall a b. (a -> b) -> a -> b
$ PhysicalColour -> ANSIColourCode
Attribute.ANSIColourCode.mkFgColourCode PhysicalColour
Attribute.PhysicalColour.green

	showsReset :: ShowS
	showsReset :: ShowS
showsReset	= String -> ShowS
showString (String -> ShowS) -> String -> ShowS
forall a b. (a -> b) -> a -> b
$ Bool -> ANSIColourCode -> String
Attribute.ANSIColourCode.selectGraphicsRendition Bool
False ANSIColourCode
forall a. Default a => a
Data.Default.def

-- | Show the board using a two-dimensional representation.
show2D
	:: Type.Length.Column			-- ^ The column-magnification.
	-> Attribute.ColourScheme.ColourScheme
	-> Bool					-- ^ Whether to depict figurines.
	-> (Type.Length.X, Type.Length.Y)	-- ^ The origin from which axes are labelled.
	-> MaybePieceByCoordinates
	-> String		-- ^ The output suitable for display on a terminal.
show2D :: Int
-> ColourScheme
-> Bool
-> (Int, Int)
-> MaybePieceByCoordinates
-> String
show2D Int
boardColumnMagnification ColourScheme
colourScheme Bool
depictFigurine (Int
xOrigin, Int
yOrigin) MaybePieceByCoordinates
maybePieceByCoordinates	= Int
-> ColourScheme
-> Bool
-> (Int, Int)
-> MaybePieceByCoordinates
-> ShowS
shows2D Int
boardColumnMagnification ColourScheme
colourScheme Bool
depictFigurine (Int
xOrigin, Int
yOrigin) MaybePieceByCoordinates
maybePieceByCoordinates String
""

-- | Extract the pieces from the board, discarding their coordinates.
getPieces :: MaybePieceByCoordinates -> [Component.Piece.Piece]
getPieces :: MaybePieceByCoordinates -> [Piece]
getPieces MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (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 (Maybe Piece) -> [Maybe Piece]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Data.Foldable.toList ArrayByCoordinates (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
	:: Attribute.Direction.Direction	-- ^ The direction in which to search.
	-> Cartesian.Coordinates.Coordinates	-- ^ The starting point.
	-> MaybePieceByCoordinates
	-> Maybe Component.Piece.LocatedPiece
findBlockingPiece :: Direction
-> Coordinates
-> MaybePieceByCoordinates
-> Maybe (Coordinates, Piece)
findBlockingPiece Direction
direction Coordinates
source MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= [(Coordinates, Piece)] -> Maybe (Coordinates, Piece)
forall a. [a] -> Maybe a
Data.Maybe.listToMaybe [
	(Coordinates
coordinates, Piece
piece) |
		(Coordinates
coordinates, Just Piece
piece)	<- (Coordinates -> (Coordinates, Maybe Piece))
-> [Coordinates] -> [(Coordinates, Maybe Piece)]
forall a b. (a -> b) -> [a] -> [b]
map (Coordinates -> Coordinates
forall a. a -> a
id (Coordinates -> Coordinates)
-> (Coordinates -> Maybe Piece)
-> Coordinates
-> (Coordinates, Maybe Piece)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& (ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!)) ([Coordinates] -> [(Coordinates, Maybe Piece)])
-> [Coordinates] -> [(Coordinates, Maybe Piece)]
forall a b. (a -> b) -> a -> b
$ Direction -> Coordinates -> [Coordinates]
Cartesian.Coordinates.extrapolate Direction
direction Coordinates
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
	:: 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					-- ^ The defender's square.
	-> MaybePieceByCoordinates
	-> Maybe (Cartesian.Coordinates.Coordinates, Attribute.Rank.Rank)	-- ^ Any opposing /piece/ which can attack the specified square from the specified /direction/.
findAttackerInDirection :: LogicalColour
-> Direction
-> Coordinates
-> MaybePieceByCoordinates
-> Maybe (Coordinates, Rank)
findAttackerInDirection LogicalColour
destinationLogicalColour Direction
direction Coordinates
destination	= ((Coordinates, Piece) -> Maybe (Coordinates, Rank))
-> Maybe (Coordinates, Piece) -> Maybe (Coordinates, Rank)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
(=<<) (
	\(Coordinates
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 -> Coordinates -> Piece -> Bool
Component.Piece.canAttackAlong Coordinates
source Coordinates
destination Piece
sourcePiece
		then (Coordinates, Rank) -> Maybe (Coordinates, Rank)
forall a. a -> Maybe a
Just (Coordinates
source, Piece -> Rank
Component.Piece.getRank Piece
sourcePiece)
		else Maybe (Coordinates, Rank)
forall a. Maybe a
Nothing
 ) (Maybe (Coordinates, Piece) -> Maybe (Coordinates, Rank))
-> (MaybePieceByCoordinates -> Maybe (Coordinates, Piece))
-> MaybePieceByCoordinates
-> Maybe (Coordinates, Rank)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Direction
-> Coordinates
-> MaybePieceByCoordinates
-> Maybe (Coordinates, Piece)
findBlockingPiece Direction
direction Coordinates
destination

-- | Whether the specified /coordinates/ are unoccupied.
isVacant
	:: Cartesian.Coordinates.Coordinates
	-> MaybePieceByCoordinates
	-> Bool
{-# INLINE isVacant #-}
isVacant :: Coordinates -> MaybePieceByCoordinates -> Bool
isVacant Coordinates
coordinates MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (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 (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
coordinates

-- | Whether the specified /coordinates/ are occupied.
isOccupied
	:: Cartesian.Coordinates.Coordinates
	-> MaybePieceByCoordinates
	-> Bool
{-# INLINE isOccupied #-}
isOccupied :: Coordinates -> MaybePieceByCoordinates -> Bool
isOccupied Coordinates
coordinates	= Bool -> Bool
not (Bool -> Bool)
-> (MaybePieceByCoordinates -> Bool)
-> MaybePieceByCoordinates
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates -> MaybePieceByCoordinates -> Bool
isVacant Coordinates
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
	:: Cartesian.Coordinates.Coordinates	-- ^ Source.
	-> Cartesian.Coordinates.Coordinates	-- ^ Destination.
	-> MaybePieceByCoordinates
	-> Bool
{-# INLINABLE isClear #-}	-- N.B.: required to ensure specialisation of 'Cartesian.Coordinates.interpolate'.
isClear :: Coordinates -> Coordinates -> MaybePieceByCoordinates -> Bool
isClear Coordinates
source Coordinates
destination MaybePieceByCoordinates
maybePieceByCoordinates	= Bool -> Bool -> Bool
forall a. Partial => Bool -> a -> a
Control.Exception.assert (
	Coordinates
source Coordinates -> Coordinates -> Bool
forall a. Eq a => a -> a -> Bool
/= Coordinates
destination Bool -> Bool -> Bool
&& Move -> Bool
forall a. Orientated a => a -> Bool
Property.Orientated.isStraight (Coordinates -> Coordinates -> Move
Component.Move.mkMove Coordinates
source Coordinates
destination)
 ) (Bool -> Bool) -> ([Coordinates] -> Bool) -> [Coordinates] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates -> Bool) -> [Coordinates] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Coordinates -> MaybePieceByCoordinates -> Bool
`isVacant` MaybePieceByCoordinates
maybePieceByCoordinates) ([Coordinates] -> Bool)
-> ([Coordinates] -> [Coordinates]) -> [Coordinates] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Coordinates] -> [Coordinates]
forall a. [a] -> [a]
init {-discard the destination-} ([Coordinates] -> Bool) -> [Coordinates] -> Bool
forall a b. (a -> b) -> a -> b
$ Coordinates -> Coordinates -> [Coordinates]
Cartesian.Coordinates.interpolate Coordinates
source Coordinates
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
	:: Cartesian.Coordinates.Coordinates	-- ^ Source.
	-> Cartesian.Coordinates.Coordinates	-- ^ Destination.
	-> MaybePieceByCoordinates
	-> Bool
isObstructed :: Coordinates -> Coordinates -> MaybePieceByCoordinates -> Bool
isObstructed Coordinates
source Coordinates
destination	= Bool -> Bool
not (Bool -> Bool)
-> (MaybePieceByCoordinates -> Bool)
-> MaybePieceByCoordinates
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates -> Coordinates -> MaybePieceByCoordinates -> Bool
isClear Coordinates
source Coordinates
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
	:: Component.Move.Move
	-> MaybePieceByCoordinates
	-> Bool
isEnPassantMove :: Move -> MaybePieceByCoordinates -> Bool
isEnPassantMove Move
move maybePieceByCoordinates :: MaybePieceByCoordinates
maybePieceByCoordinates@MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }
	| Just Piece
piece	<- ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece) -> Coordinates -> Maybe Piece
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
source
	, let logicalColour :: LogicalColour
logicalColour	= Piece -> LogicalColour
Component.Piece.getLogicalColour Piece
piece
	= LogicalColour -> Coordinates -> Bool
Cartesian.Coordinates.isEnPassantRank LogicalColour
logicalColour Coordinates
source Bool -> Bool -> Bool
&& Piece -> Bool
Component.Piece.isPawn Piece
piece Bool -> Bool -> Bool
&& Coordinates
destination Coordinates -> [Coordinates] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Coordinates -> Piece -> [Coordinates]
Component.Piece.findAttackDestinations Coordinates
source Piece
piece Bool -> Bool -> Bool
&& Coordinates -> MaybePieceByCoordinates -> Bool
isVacant Coordinates
destination MaybePieceByCoordinates
maybePieceByCoordinates	-- The move is either En-passant or invalid.
	| Bool
otherwise	= Bool
False	-- No piece.
	where
		(Coordinates
source, Coordinates
destination)	= Move -> Coordinates
Component.Move.getSource (Move -> Coordinates)
-> (Move -> Coordinates) -> Move -> (Coordinates, Coordinates)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Move -> Coordinates
Component.Move.getDestination (Move -> (Coordinates, Coordinates))
-> Move -> (Coordinates, Coordinates)
forall a b. (a -> b) -> a -> b
$ Move
move

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

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

	* CAVEAT: regrettably this allocates an entire array.
-}
movePiece
	:: Component.Move.Move
	-> Component.Piece.Piece			-- ^ The (possibly promoted) piece to place at the destination.
	-> Maybe Cartesian.Coordinates.Coordinates	-- ^ Destination of any En-passant @Pawn@.
	-> Transformation
movePiece :: Move
-> Piece
-> Maybe Coordinates
-> MaybePieceByCoordinates
-> MaybePieceByCoordinates
movePiece Move
move Piece
destinationPiece Maybe Coordinates
maybeEnPassantDestination MkMaybePieceByCoordinates { deconstruct :: MaybePieceByCoordinates -> ArrayByCoordinates (Maybe Piece)
deconstruct = ArrayByCoordinates (Maybe Piece)
byCoordinates }	= ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
MkMaybePieceByCoordinates (ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates)
-> ArrayByCoordinates (Maybe Piece) -> MaybePieceByCoordinates
forall a b. (a -> b) -> a -> b
$ ArrayByCoordinates (Maybe Piece)
byCoordinates ArrayByCoordinates (Maybe Piece)
-> [(Coordinates, Maybe Piece)] -> ArrayByCoordinates (Maybe Piece)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)] -> a i e
// ([(Coordinates, Maybe Piece)] -> [(Coordinates, Maybe Piece)])
-> (Coordinates
    -> [(Coordinates, Maybe Piece)] -> [(Coordinates, Maybe Piece)])
-> Maybe Coordinates
-> [(Coordinates, Maybe Piece)]
-> [(Coordinates, Maybe Piece)]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [(Coordinates, Maybe Piece)] -> [(Coordinates, Maybe Piece)]
forall a. a -> a
id (
	(:) ((Coordinates, Maybe Piece)
 -> [(Coordinates, Maybe Piece)] -> [(Coordinates, Maybe Piece)])
-> (Coordinates -> (Coordinates, Maybe Piece))
-> Coordinates
-> [(Coordinates, Maybe Piece)]
-> [(Coordinates, Maybe Piece)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates -> Maybe Piece -> (Coordinates, Maybe Piece))
-> Maybe Piece -> Coordinates -> (Coordinates, 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
maybeEnPassantDestination [
	(
		Move -> Coordinates
Component.Move.getSource Move
move,
		Maybe Piece
forall a. Maybe a
Nothing	-- Remove the piece from the source.
	), (
		Move -> Coordinates
Component.Move.getDestination Move
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.
	)
 ]