{-# LANGUAGE CPP #-}
{-
	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@]	The location of a square on the board.
-}

module BishBosh.Cartesian.Coordinates(
-- * Types
-- ** Data-types
	Coordinates(
--		MkCoordinates,
		getX,
		getY
	),
-- ** Type-synonyms
--	Transformation,
	ArrayByCoordinates,
--	UArrayByCoordinates,
-- * Constants
	tag,
	topLeft,
	bottomRight,
	nSquares,
--	extrapolationsByDirectionByCoordinates,
--	interpolationsByDestinationBySource,
-- * Functions
--	extrapolate',
	extrapolate,
	interpolate,
	getLogicalColourOfSquare,
	kingsStartingCoordinates,
	rooksStartingCoordinates,
	measureDistance,
	translate,
	maybeTranslate,
	translateX,
	maybeTranslateX,
	translateY,
	maybeTranslateY,
	getAdjacents,
	advance,
--	maybeAdvance,
	retreat,
	maybeRetreat,
--	rotate,
-- ** Constructors
	mkCoordinates,
	mkMaybeCoordinates,
--	toIx,
	fromIx,
	mkRelativeCoordinates,
	listArrayByCoordinates,
	arrayByCoordinates,
-- ** Predicates
--	inBounds,
	isPawnsFirstRank,
	isEnPassantRank,
	areSquaresIsochromatic
) where

import			Control.Arrow((&&&), (***))
import			Data.Array.IArray((!))
import qualified	BishBosh.Attribute.Direction			as Attribute.Direction
import qualified	BishBosh.Attribute.LogicalColour		as Attribute.LogicalColour
import qualified	BishBosh.Attribute.LogicalColourOfSquare	as Attribute.LogicalColourOfSquare
import qualified	BishBosh.Cartesian.Abscissa			as Cartesian.Abscissa
import qualified	BishBosh.Cartesian.Ordinate			as Cartesian.Ordinate
import qualified	BishBosh.Data.Exception				as Data.Exception
import qualified	BishBosh.Property.FixedMembership		as Property.FixedMembership
import qualified	BishBosh.Property.Opposable			as Property.Opposable
import qualified	BishBosh.Property.Reflectable			as Property.Reflectable
import qualified	BishBosh.Property.Rotatable			as Property.Rotatable
import qualified	BishBosh.Text.ShowList				as Text.ShowList
import qualified	BishBosh.Type.Count				as Type.Count
import qualified	BishBosh.Type.Length				as Type.Length
import qualified	Control.DeepSeq
import qualified	Control.Exception
import qualified	Data.Array.IArray
import qualified	Data.Array.Unboxed
import qualified	Data.Foldable
import qualified	Data.List
import qualified	Data.Map					as Map
import qualified	Data.Maybe

#ifdef USE_PARALLEL
import qualified	Control.Parallel.Strategies
#endif

-- | Used to qualify XML.
tag :: String
tag :: String
tag	= String
"coordinates"

-- | The /coordinates/ of a square on the board.
data Coordinates	= MkCoordinates {
	Coordinates -> X
getX	:: ! Type.Length.X,	-- ^ Abscissa.
	Coordinates -> X
getY	:: ! Type.Length.Y	-- ^ Ordinate.
} deriving Coordinates -> Coordinates -> Bool
(Coordinates -> Coordinates -> Bool)
-> (Coordinates -> Coordinates -> Bool) -> Eq Coordinates
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Coordinates -> Coordinates -> Bool
$c/= :: Coordinates -> Coordinates -> Bool
== :: Coordinates -> Coordinates -> Bool
$c== :: Coordinates -> Coordinates -> Bool
Eq

instance Control.DeepSeq.NFData Coordinates where
	rnf :: Coordinates -> ()
rnf MkCoordinates { getX :: Coordinates -> X
getX = X
x, getY :: Coordinates -> X
getY = X
y }	= (X, X) -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf (X
x, X
y)

instance Show Coordinates where
	showsPrec :: X -> Coordinates -> ShowS
showsPrec X
precedence MkCoordinates { getX :: Coordinates -> X
getX = X
x, getY :: Coordinates -> X
getY = X
y }	= X -> (X, X) -> ShowS
forall a. Show a => X -> a -> ShowS
showsPrec X
precedence (X
x, X
y)

instance Read Coordinates where
	readsPrec :: X -> ReadS Coordinates
readsPrec X
precedence String
s	= [
		(Coordinates
coordinates, String
remainder) |
			((X
x, X
y), String
remainder)	<- X -> ReadS (X, X)
forall a. Read a => X -> ReadS a
readsPrec X
precedence String
s,
			Coordinates
coordinates		<- Maybe Coordinates -> [Coordinates]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe Coordinates -> [Coordinates])
-> Maybe Coordinates -> [Coordinates]
forall a b. (a -> b) -> a -> b
$ X -> X -> Maybe Coordinates
mkMaybeCoordinates X
x X
y
	 ] -- List-comprehension.

instance Ord Coordinates where
	MkCoordinates { getX :: Coordinates -> X
getX = X
x, getY :: Coordinates -> X
getY = X
y } compare :: Coordinates -> Coordinates -> Ordering
`compare` MkCoordinates { getX :: Coordinates -> X
getX = X
x', getY :: Coordinates -> X
getY = X
y' }	= (X
y, X
x) (X, X) -> (X, X) -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` (X
y', X
x')	-- N.B.: x is less significant than y, as required by the implementation of 'Data.Array.IArray.Ix.inRange'.

instance Bounded Coordinates where
	minBound :: Coordinates
minBound = MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
		getX :: X
getX	= X
Cartesian.Abscissa.xMin,
		getY :: X
getY	= X
Cartesian.Ordinate.yMin
	} -- Bottom Left.
	maxBound :: Coordinates
maxBound = MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
		getX :: X
getX	= X
Cartesian.Abscissa.xMax,
		getY :: X
getY	= X
Cartesian.Ordinate.yMax
	} -- Top Right.

instance Data.Array.IArray.Ix Coordinates where
	range :: (Coordinates, Coordinates) -> [Coordinates]
range (Coordinates
lower, Coordinates
upper)			= Bool -> [Coordinates] -> [Coordinates]
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (Coordinates
lower Coordinates -> Coordinates -> Bool
forall a. Eq a => a -> a -> Bool
== Coordinates
forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Coordinates
upper Coordinates -> Coordinates -> Bool
forall a. Eq a => a -> a -> Bool
== Coordinates
forall a. Bounded a => a
maxBound) [Coordinates]
forall a. FixedMembership a => [a]
Property.FixedMembership.members
	inRange :: (Coordinates, Coordinates) -> Coordinates -> Bool
inRange (Coordinates
lower, Coordinates
upper) Coordinates
coordinates	= Bool -> Bool -> Bool
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (Coordinates
coordinates Coordinates -> Coordinates -> Bool
forall a. Ord a => a -> a -> Bool
>= Coordinates
lower Bool -> Bool -> Bool
&& Coordinates
coordinates Coordinates -> Coordinates -> Bool
forall a. Ord a => a -> a -> Bool
<= Coordinates
upper) Bool
True
	index :: (Coordinates, Coordinates) -> Coordinates -> X
index (Coordinates
lower, Coordinates
upper)			= Bool -> X -> X
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (Coordinates
lower Coordinates -> Coordinates -> Bool
forall a. Eq a => a -> a -> Bool
== Coordinates
forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Coordinates
upper Coordinates -> Coordinates -> Bool
forall a. Eq a => a -> a -> Bool
== Coordinates
forall a. Bounded a => a
maxBound) (X -> X) -> (Coordinates -> X) -> Coordinates -> X
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates -> X
toIx

instance Property.Reflectable.ReflectableOnX Coordinates where
	reflectOnX :: Coordinates -> Coordinates
reflectOnX coordinates :: Coordinates
coordinates@MkCoordinates { getY :: Coordinates -> X
getY = X
y }	= Coordinates
coordinates { getY :: X
getY = X -> X
Cartesian.Ordinate.reflect X
y }

instance Property.Reflectable.ReflectableOnY Coordinates where
	reflectOnY :: Coordinates -> Coordinates
reflectOnY coordinates :: Coordinates
coordinates@MkCoordinates { getX :: Coordinates -> X
getX = X
x }	= Coordinates
coordinates { getX :: X
getX = X -> X
Cartesian.Abscissa.reflect X
x }

instance Property.Rotatable.Rotatable Coordinates where
	rotate90 :: Coordinates -> Coordinates
rotate90	= Direction -> Coordinates -> Coordinates
rotate Direction
Attribute.Direction.w
	rotate180 :: Coordinates -> Coordinates
rotate180	= Direction -> Coordinates -> Coordinates
rotate Direction
Attribute.Direction.s
	rotate270 :: Coordinates -> Coordinates
rotate270	= Direction -> Coordinates -> Coordinates
rotate Direction
Attribute.Direction.e

-- | Constant.
topLeft :: Coordinates
topLeft :: Coordinates
topLeft = MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
	getX :: X
getX	= X
Cartesian.Abscissa.xMin,
	getY :: X
getY	= X
Cartesian.Ordinate.yMax
}

-- | Constant.
bottomRight :: Coordinates
bottomRight :: Coordinates
bottomRight = MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
	getX :: X
getX	= X
Cartesian.Abscissa.xMax,
	getY :: X
getY	= X
Cartesian.Ordinate.yMin
}

-- | The constant number of squares on the board.
nSquares :: Type.Count.NCoordinates
nSquares :: X
nSquares	= X -> X
forall a b. (Integral a, Num b) => a -> b
fromIntegral X
Cartesian.Abscissa.xLength X -> X -> X
forall a. Num a => a -> a -> a
* X -> X
forall a b. (Integral a, Num b) => a -> b
fromIntegral X
Cartesian.Ordinate.yLength

instance Property.FixedMembership.FixedMembership Coordinates where
	members :: [Coordinates]
members	= [
		MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
			getX :: X
getX	= X
x,
			getY :: X
getY	= X
y
		} |
			X
y	<- [X]
Cartesian.Ordinate.yRange,
			X
x	<- [X]
Cartesian.Abscissa.xRange
	 ] -- List-comprehension.

-- | Predicate.
inBounds
	:: Type.Length.X	-- ^ Abscissa.
	-> Type.Length.Y	-- ^ Ordinate.
	-> Bool
inBounds :: X -> X -> Bool
inBounds X
x X
y	= X -> Bool
Cartesian.Abscissa.inBounds X
x Bool -> Bool -> Bool
&& X -> Bool
Cartesian.Ordinate.inBounds X
y

-- | Constructor.
mkCoordinates
	:: Type.Length.X	-- ^ Abscissa.
	-> Type.Length.Y	-- ^ Ordinate.
	-> Coordinates
mkCoordinates :: X -> X -> Coordinates
mkCoordinates X
x X
y	= Bool -> Coordinates -> Coordinates
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (X -> X -> Bool
inBounds X
x X
y) (Coordinates -> Coordinates) -> Coordinates -> Coordinates
forall a b. (a -> b) -> a -> b
$ X -> X -> Coordinates
MkCoordinates X
x X
y

-- | Safe constructor.
mkMaybeCoordinates
	:: Type.Length.X	-- ^ Abscissa.
	-> Type.Length.Y	-- ^ Ordinate.
	-> Maybe Coordinates
mkMaybeCoordinates :: X -> X -> Maybe Coordinates
mkMaybeCoordinates X
x X
y
	| X -> X -> Bool
inBounds X
x X
y	= Coordinates -> Maybe Coordinates
forall a. a -> Maybe a
Just MkCoordinates :: X -> X -> Coordinates
MkCoordinates { getX :: X
getX = X
x, getY :: X
getY = X
y }
	| Bool
otherwise	= Maybe Coordinates
forall a. Maybe a
Nothing

-- | Convert to an array-index.
toIx :: Coordinates -> Int
toIx :: Coordinates -> X
toIx MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x,
	getY :: Coordinates -> X
getY	= X
y
} = X -> X
forall a b. (Integral a, Num b) => a -> b
fromIntegral X
Cartesian.Abscissa.xLength X -> X -> X
forall a. Num a => a -> a -> a
* X -> X
Cartesian.Ordinate.toIx X
y X -> X -> X
forall a. Num a => a -> a -> a
+ X -> X
Cartesian.Abscissa.toIx X
x

{- |
	* Construct from the specified array-index.

	* CAVEAT: assumes that the array is indexed by the whole range of /coordinates/.
-}
fromIx :: Int -> Coordinates
fromIx :: X -> Coordinates
fromIx	= (
	\(X
y, X
x) -> MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
		getX :: X
getX	= X -> X
Cartesian.Abscissa.fromIx X
x,
		getY :: X
getY	= X -> X
Cartesian.Ordinate.fromIx X
y
	}
 ) ((X, X) -> Coordinates) -> (X -> (X, X)) -> X -> Coordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (X -> X -> (X, X)
forall a. Integral a => a -> a -> (a, a)
`divMod` X -> X
forall a b. (Integral a, Num b) => a -> b
fromIntegral X
Cartesian.Abscissa.xLength)

{- |
	* Translate the specified /coordinates/ using the specified mapping.

	* CAVEAT: the caller must ensure that the results are legal.
-}
translate :: ((Type.Length.X, Type.Length.Y) -> (Type.Length.X, Type.Length.Y)) -> Coordinates -> Coordinates
translate :: ((X, X) -> (X, X)) -> Coordinates -> Coordinates
translate (X, X) -> (X, X)
transformation MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x,
	getY :: Coordinates -> X
getY	= X
y
} = (X -> X -> Coordinates) -> (X, X) -> Coordinates
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry X -> X -> Coordinates
mkCoordinates ((X, X) -> Coordinates) -> (X, X) -> Coordinates
forall a b. (a -> b) -> a -> b
$ (X, X) -> (X, X)
transformation (X
x, X
y)

-- | Where legal, translate the specified /coordinates/.
maybeTranslate :: ((Type.Length.X, Type.Length.Y) -> (Type.Length.X, Type.Length.Y)) -> Coordinates -> Maybe Coordinates
maybeTranslate :: ((X, X) -> (X, X)) -> Coordinates -> Maybe Coordinates
maybeTranslate (X, X) -> (X, X)
transformation MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x,
	getY :: Coordinates -> X
getY	= X
y
} = (X -> X -> Maybe Coordinates) -> (X, X) -> Maybe Coordinates
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry X -> X -> Maybe Coordinates
mkMaybeCoordinates ((X, X) -> Maybe Coordinates) -> (X, X) -> Maybe Coordinates
forall a b. (a -> b) -> a -> b
$ (X, X) -> (X, X)
transformation (X
x, X
y)

{- |
	* Translate the specified abscissa.

	* CAVEAT: the caller must ensure that the results are legal.
-}
translateX :: (Type.Length.X -> Type.Length.X) -> Transformation
translateX :: (X -> X) -> Coordinates -> Coordinates
translateX X -> X
transformation coordinates :: Coordinates
coordinates@MkCoordinates { getX :: Coordinates -> X
getX = X
x }	= Coordinates
coordinates { getX :: X
getX = (X -> X) -> X -> X
Cartesian.Abscissa.translate X -> X
transformation X
x }

-- | Where legal, translate the /x/-component of the specified /coordinates/.
maybeTranslateX
	:: (Type.Length.X -> Type.Length.X)	-- ^ Translation.
	-> Coordinates
	-> Maybe Coordinates
maybeTranslateX :: (X -> X) -> Coordinates -> Maybe Coordinates
maybeTranslateX X -> X
transformation coordinates :: Coordinates
coordinates@MkCoordinates { getX :: Coordinates -> X
getX = X
x }	= (\X
x' -> Coordinates
coordinates { getX :: X
getX = X
x' }) (X -> Coordinates) -> Maybe X -> Maybe Coordinates
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (X -> X) -> X -> Maybe X
Cartesian.Abscissa.maybeTranslate X -> X
transformation X
x

{- |
	* Translate the specified ordinate.

	* CAVEAT: the caller must ensure that the results are legal.
-}
translateY :: (Type.Length.Y -> Type.Length.Y) -> Transformation
translateY :: (X -> X) -> Coordinates -> Coordinates
translateY X -> X
transformation coordinates :: Coordinates
coordinates@MkCoordinates { getY :: Coordinates -> X
getY = X
y }	= Coordinates
coordinates { getY :: X
getY = (X -> X) -> X -> X
Cartesian.Ordinate.translate X -> X
transformation X
y }

-- | Where legal, translate the /y/-component of the specified /coordinates/.
maybeTranslateY
	:: (Type.Length.Y -> Type.Length.Y)	-- ^ Translation.
	-> Coordinates
	-> Maybe Coordinates
maybeTranslateY :: (X -> X) -> Coordinates -> Maybe Coordinates
maybeTranslateY X -> X
transformation coordinates :: Coordinates
coordinates@MkCoordinates { getY :: Coordinates -> X
getY = X
y }	= (\X
y' -> Coordinates
coordinates { getY :: X
getY = X
y' }) (X -> Coordinates) -> Maybe X -> Maybe Coordinates
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (X -> X) -> X -> Maybe X
Cartesian.Ordinate.maybeTranslate X -> X
transformation X
y

{- |
	* Construct /coordinates/ relative to 'minBound'.

	* CAVEAT: the caller must ensure that the results are legal.
-}
mkRelativeCoordinates :: ((Type.Length.X, Type.Length.Y) -> (Type.Length.X, Type.Length.Y)) -> Coordinates
mkRelativeCoordinates :: ((X, X) -> (X, X)) -> Coordinates
mkRelativeCoordinates	= (((X, X) -> (X, X)) -> Coordinates -> Coordinates
`translate` Coordinates
forall a. Bounded a => a
minBound)

{- |
	* Move one step towards the opponent.

	* CAVEAT: the caller must ensure that the results are legal.
-}
advance
	:: Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the /piece/ which is to advance.
	-> Transformation
advance :: LogicalColour -> Coordinates -> Coordinates
advance LogicalColour
logicalColour	= (X -> X) -> Coordinates -> Coordinates
translateY ((X -> X) -> Coordinates -> Coordinates)
-> (X -> X) -> Coordinates -> Coordinates
forall a b. (a -> b) -> a -> b
$ if LogicalColour -> Bool
Attribute.LogicalColour.isBlack LogicalColour
logicalColour
	then X -> X
forall a. Enum a => a -> a
pred
	else X -> X
forall a. Enum a => a -> a
succ

-- | Where legal, move one step towards the opponent.
maybeAdvance
	:: Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the /piece/ which is to advance.
	-> Coordinates				-- ^ The location from which to advanced.
	-> Maybe Coordinates
maybeAdvance :: LogicalColour -> Coordinates -> Maybe Coordinates
maybeAdvance LogicalColour
logicalColour	= (X -> X) -> Coordinates -> Maybe Coordinates
maybeTranslateY ((X -> X) -> Coordinates -> Maybe Coordinates)
-> (X -> X) -> Coordinates -> Maybe Coordinates
forall a b. (a -> b) -> a -> b
$ if LogicalColour -> Bool
Attribute.LogicalColour.isBlack LogicalColour
logicalColour
	then X -> X
forall a. Enum a => a -> a
pred
	else X -> X
forall a. Enum a => a -> a
succ

{- |
	* Move one step away from the opponent.

	* CAVEAT: the caller must ensure that the results are legal.
-}
retreat
	:: Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the /piece/ which is to retreat.
	-> Transformation
retreat :: LogicalColour -> Coordinates -> Coordinates
retreat	= LogicalColour -> Coordinates -> Coordinates
advance (LogicalColour -> Coordinates -> Coordinates)
-> (LogicalColour -> LogicalColour)
-> LogicalColour
-> Coordinates
-> Coordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogicalColour -> LogicalColour
forall a. Opposable a => a -> a
Property.Opposable.getOpposite

-- | Where legal, move one step away from the opponent.
maybeRetreat
	:: Attribute.LogicalColour.LogicalColour	-- ^ The /logical colour/ of the /piece/ which is to retreat.
	-> Coordinates				-- ^ The location from which to retreat.
	-> Maybe Coordinates
maybeRetreat :: LogicalColour -> Coordinates -> Maybe Coordinates
maybeRetreat	= LogicalColour -> Coordinates -> Maybe Coordinates
maybeAdvance (LogicalColour -> Coordinates -> Maybe Coordinates)
-> (LogicalColour -> LogicalColour)
-> LogicalColour
-> Coordinates
-> Maybe Coordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogicalColour -> LogicalColour
forall a. Opposable a => a -> a
Property.Opposable.getOpposite

-- | Get the /coordinates/ immediately left & right.
getAdjacents :: Coordinates -> [Coordinates]
getAdjacents :: Coordinates -> [Coordinates]
getAdjacents coordinates :: Coordinates
coordinates@MkCoordinates { getX :: Coordinates -> X
getX = X
x }	= (X -> Coordinates) -> [X] -> [Coordinates]
forall a b. (a -> b) -> [a] -> [b]
map (\X
x' -> Coordinates
coordinates { getX :: X
getX = X
x' }) ([X] -> [Coordinates]) -> [X] -> [Coordinates]
forall a b. (a -> b) -> a -> b
$ X -> [X]
Cartesian.Abscissa.getAdjacents X
x

-- | Generates a line of /coordinates/, starting just after the specified source & proceeding in the specified /direction/ to the edge of the board.
extrapolate'
	:: Attribute.Direction.Direction	-- ^ The direction in which to proceed.
	-> Coordinates			-- ^ The point from which to start.
	-> [Coordinates]
extrapolate' :: Direction -> Coordinates -> [Coordinates]
extrapolate' Direction
direction MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x,
	getY :: Coordinates -> X
getY	= X
y
} = (X -> X -> Coordinates) -> [X] -> [X] -> [Coordinates]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith X -> X -> Coordinates
MkCoordinates (
	case Direction -> Ordering
Attribute.Direction.getXDirection Direction
direction of
		Ordering
GT	-> [X -> X
forall a. Enum a => a -> a
succ X
x .. X
Cartesian.Abscissa.xMax]
		Ordering
LT	-> let startX :: X
startX = X -> X
forall a. Enum a => a -> a
pred X
x in X
startX X -> [X] -> [X]
`seq` [X
startX, X -> X
forall a. Enum a => a -> a
pred X
startX .. X
Cartesian.Abscissa.xMin]
		Ordering
EQ	-> X -> [X]
forall a. a -> [a]
repeat X
x
 ) (
	case Direction -> Ordering
Attribute.Direction.getYDirection Direction
direction of
		Ordering
GT	-> [X -> X
forall a. Enum a => a -> a
succ X
y .. X
Cartesian.Ordinate.yMax]
		Ordering
LT	-> let startY :: X
startY = X -> X
forall a. Enum a => a -> a
pred X
y in X
startY X -> [X] -> [X]
`seq` [X
startY, X -> X
forall a. Enum a => a -> a
pred X
startY .. X
Cartesian.Ordinate.yMin]
		Ordering
EQ	-> X -> [X]
forall a. a -> [a]
repeat X
y
 )

{- |
	* Generates a line of /coordinates/, starting just after the specified source & proceeding in the specified /direction/ to the edge of the board.

	* CAVEAT: this is a performance-hotspot (it's also responsible for the allocation of a third of the application's memory); refactor => re-profile.
	In consequence, it is typically automatically avoided using a rewrite-rule to lookup an array of the results from all possible calls.
-}
extrapolate
	:: Attribute.Direction.Direction	-- ^ The direction in which to proceed.
	-> Coordinates			-- ^ The point from which to start.
	-> [Coordinates]
extrapolate :: Direction -> Coordinates -> [Coordinates]
extrapolate Direction
direction Coordinates
coordinates	= ArrayByCoordinates (ArrayByDirection [Coordinates])
extrapolationsByDirectionByCoordinates ArrayByCoordinates (ArrayByDirection [Coordinates])
-> Coordinates -> ArrayByDirection [Coordinates]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
coordinates ArrayByDirection [Coordinates] -> Direction -> [Coordinates]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Direction
direction

-- | The constant lists of /coordinates/, extrapolated from every /coordinate/ in the /board/, in every /direction/.
extrapolationsByDirectionByCoordinates :: ArrayByCoordinates (Attribute.Direction.ArrayByDirection [Coordinates])
extrapolationsByDirectionByCoordinates :: ArrayByCoordinates (ArrayByDirection [Coordinates])
extrapolationsByDirectionByCoordinates	= [ArrayByDirection [Coordinates]]
-> ArrayByCoordinates (ArrayByDirection [Coordinates])
forall (a :: * -> * -> *) e. IArray a e => [e] -> a Coordinates e
listArrayByCoordinates
#ifdef USE_PARALLEL
	([ArrayByDirection [Coordinates]]
 -> ArrayByCoordinates (ArrayByDirection [Coordinates]))
-> ([ArrayByDirection [Coordinates]]
    -> [ArrayByDirection [Coordinates]])
-> [ArrayByDirection [Coordinates]]
-> ArrayByCoordinates (ArrayByDirection [Coordinates])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Strategy [ArrayByDirection [Coordinates]]
-> [ArrayByDirection [Coordinates]]
-> [ArrayByDirection [Coordinates]]
forall a. Strategy a -> a -> a
Control.Parallel.Strategies.withStrategy (Strategy (ArrayByDirection [Coordinates])
-> Strategy [ArrayByDirection [Coordinates]]
forall a. Strategy a -> Strategy [a]
Control.Parallel.Strategies.parList Strategy (ArrayByDirection [Coordinates])
forall a. NFData a => Strategy a
Control.Parallel.Strategies.rdeepseq)
#endif
	([ArrayByDirection [Coordinates]]
 -> ArrayByCoordinates (ArrayByDirection [Coordinates]))
-> [ArrayByDirection [Coordinates]]
-> ArrayByCoordinates (ArrayByDirection [Coordinates])
forall a b. (a -> b) -> a -> b
$ (Coordinates -> ArrayByDirection [Coordinates])
-> [Coordinates] -> [ArrayByDirection [Coordinates]]
forall a b. (a -> b) -> [a] -> [b]
map (
		\Coordinates
coordinates	-> [[Coordinates]] -> ArrayByDirection [Coordinates]
forall (a :: * -> * -> *) e. IArray a e => [e] -> a Direction e
Attribute.Direction.listArrayByDirection ([[Coordinates]] -> ArrayByDirection [Coordinates])
-> [[Coordinates]] -> ArrayByDirection [Coordinates]
forall a b. (a -> b) -> a -> b
$ (Direction -> [Coordinates]) -> [Direction] -> [[Coordinates]]
forall a b. (a -> b) -> [a] -> [b]
map (Direction -> Coordinates -> [Coordinates]
`extrapolate'` Coordinates
coordinates) [Direction]
forall a. FixedMembership a => [a]
Property.FixedMembership.members
	) [Coordinates]
forall a. FixedMembership a => [a]
Property.FixedMembership.members

-- | The list of /coordinates/, between every permutation of source & valid destination on the /board/.
interpolationsByDestinationBySource :: ArrayByCoordinates (Map.Map Coordinates [Coordinates])
interpolationsByDestinationBySource :: ArrayByCoordinates (Map Coordinates [Coordinates])
interpolationsByDestinationBySource	= (ArrayByDirection [Coordinates] -> Map Coordinates [Coordinates])
-> ArrayByCoordinates (ArrayByDirection [Coordinates])
-> ArrayByCoordinates (Map Coordinates [Coordinates])
forall (a :: * -> * -> *) e' e i.
(IArray a e', IArray a e, Ix i) =>
(e' -> e) -> a i e' -> a i e
Data.Array.IArray.amap (
	[(Coordinates, [Coordinates])] -> Map Coordinates [Coordinates]
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Coordinates, [Coordinates])] -> Map Coordinates [Coordinates])
-> (ArrayByDirection [Coordinates]
    -> [(Coordinates, [Coordinates])])
-> ArrayByDirection [Coordinates]
-> Map Coordinates [Coordinates]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Coordinates] -> (Coordinates, [Coordinates]))
-> [[Coordinates]] -> [(Coordinates, [Coordinates])]
forall a b. (a -> b) -> [a] -> [b]
map (
		[Coordinates] -> Coordinates
forall a. [a] -> a
last {-destination-} ([Coordinates] -> Coordinates)
-> ([Coordinates] -> [Coordinates])
-> [Coordinates]
-> (Coordinates, [Coordinates])
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& [Coordinates] -> [Coordinates]
forall a. a -> a
id {-interpolation-}
	) ([[Coordinates]] -> [(Coordinates, [Coordinates])])
-> (ArrayByDirection [Coordinates] -> [[Coordinates]])
-> ArrayByDirection [Coordinates]
-> [(Coordinates, [Coordinates])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Coordinates] -> [[Coordinates]])
-> [[Coordinates]] -> [[Coordinates]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (
		[[Coordinates]] -> [[Coordinates]]
forall a. [a] -> [a]
tail {-remove null list-} ([[Coordinates]] -> [[Coordinates]])
-> ([Coordinates] -> [[Coordinates]])
-> [Coordinates]
-> [[Coordinates]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Coordinates] -> [[Coordinates]]
forall a. [a] -> [[a]]
Data.List.inits	-- Generate all possible interpolations from this extrapolation.
	) ([[Coordinates]] -> [[Coordinates]])
-> (ArrayByDirection [Coordinates] -> [[Coordinates]])
-> ArrayByDirection [Coordinates]
-> [[Coordinates]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayByDirection [Coordinates] -> [[Coordinates]]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Data.Foldable.toList
 ) ArrayByCoordinates (ArrayByDirection [Coordinates])
extrapolationsByDirectionByCoordinates	-- Derive from extrapolations.

{- |
	* Generates a line of /coordinates/ covering the half open interval @(source, destination]@.

	* CAVEAT: the destination-/coordinates/ must be a valid @Queen@'s /move/ from the source; so that all intermediate points lie on a square of the board.
-}
interpolate :: Coordinates -> Coordinates -> [Coordinates]
interpolate :: Coordinates -> Coordinates -> [Coordinates]
interpolate Coordinates
coordinatesSource Coordinates
coordinatesDestination	= ArrayByCoordinates (Map Coordinates [Coordinates])
interpolationsByDestinationBySource ArrayByCoordinates (Map Coordinates [Coordinates])
-> Coordinates -> Map Coordinates [Coordinates]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Coordinates
coordinatesSource Map Coordinates [Coordinates] -> Coordinates -> [Coordinates]
forall k a. Ord k => Map k a -> k -> a
Map.! Coordinates
coordinatesDestination

-- | The type of a function which changes one set of /coordinates/ to another.
type Transformation	= Coordinates -> Coordinates

{- |
	* Rotates the specified /coordinates/, so that the @Black@ pieces start on the specified side of the board; a /direction/ of @N@ involves no change.

	* CAVEAT: one can only request an integral multiple of 90 degrees.
-}
rotate :: Attribute.Direction.Direction -> Transformation
rotate :: Direction -> Coordinates -> Coordinates
rotate Direction
direction coordinates :: Coordinates
coordinates@MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x,
	getY :: Coordinates -> X
getY	= X
y
} = case Direction -> Ordering
Attribute.Direction.getXDirection (Direction -> Ordering)
-> (Direction -> Ordering) -> Direction -> (Ordering, Ordering)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Direction -> Ordering
Attribute.Direction.getYDirection (Direction -> (Ordering, Ordering))
-> Direction -> (Ordering, Ordering)
forall a b. (a -> b) -> a -> b
$ Direction
direction of
	(Ordering
EQ, Ordering
GT)	-> Coordinates
coordinates
	(Ordering
LT, Ordering
EQ)	-> MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
		getX :: X
getX	= X -> X
Cartesian.Abscissa.fromIx X
yDistance',
		getY :: X
getY	= X -> X
Cartesian.Ordinate.fromIx X
xDistance
	} -- +90 degrees, i.e. anti-clockwise.
	(Ordering
EQ, Ordering
LT)	-> MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
		getX :: X
getX	= X -> X
Cartesian.Abscissa.fromIx X
xDistance',
		getY :: X
getY	= X -> X
Cartesian.Ordinate.fromIx X
yDistance'
	} -- 180 degrees.
	(Ordering
GT, Ordering
EQ)	-> MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
		getX :: X
getX	= X -> X
Cartesian.Abscissa.fromIx X
yDistance,
		getY :: X
getY	= X -> X
Cartesian.Ordinate.fromIx X
xDistance'
	} -- -90 degrees, i.e. clockwise.
	(Ordering, Ordering)
_		-> Exception -> Coordinates
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Coordinates)
-> (String -> Exception) -> String -> Coordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkRequestFailure (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Cartesian.Coordinates.rotate:\tunable to rotate to direction" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
Text.ShowList.showsAssociation (String -> Coordinates) -> String -> Coordinates
forall a b. (a -> b) -> a -> b
$ Direction -> ShowS
forall a. Show a => a -> ShowS
shows Direction
direction String
"."
	where
		xDistance :: X
xDistance	= X -> X
Cartesian.Abscissa.toIx X
x
		yDistance :: X
yDistance	= X -> X
Cartesian.Ordinate.toIx X
y
		xDistance' :: X
xDistance'	= X -> X
forall a b. (Integral a, Num b) => a -> b
fromIntegral (X -> X
forall a. Enum a => a -> a
pred X
Cartesian.Abscissa.xLength) X -> X -> X
forall a. Num a => a -> a -> a
- X
xDistance
		yDistance' :: X
yDistance'	= X -> X
forall a b. (Integral a, Num b) => a -> b
fromIntegral (X -> X
forall a. Enum a => a -> a
pred X
Cartesian.Ordinate.yLength) X -> X -> X
forall a. Num a => a -> a -> a
- X
yDistance

{- |
	* Measures the signed distance between source & destination /coordinates/.

	* N.B.: this isn't the /irrational/ distance a rational crow would fly, but rather the integral /x/ & /y/ components of that path.

	* CAVEAT: beware the potential fence-post error.
-}
measureDistance
	:: Coordinates	-- ^ Source.
	-> Coordinates	-- ^ Destination.
	-> (Type.Length.X, Type.Length.Y)
measureDistance :: Coordinates -> Coordinates -> (X, X)
measureDistance MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x,
	getY :: Coordinates -> X
getY	= X
y
} MkCoordinates {
	getX :: Coordinates -> X
getX	= X
x',
	getY :: Coordinates -> X
getY	= X
y'
} = (X
x' X -> X -> X
forall a. Num a => a -> a -> a
- X
x, X
y' X -> X -> X
forall a. Num a => a -> a -> a
- X
y)

-- | The /logical colour/ of the specified square.
getLogicalColourOfSquare :: Coordinates -> Attribute.LogicalColourOfSquare.LogicalColourOfSquare
getLogicalColourOfSquare :: Coordinates -> LogicalColourOfSquare
getLogicalColourOfSquare Coordinates
coordinates
	| (Bool -> Bool -> Bool) -> (Bool, Bool) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
(==) ((Bool, Bool) -> Bool)
-> ((X, X) -> (Bool, Bool)) -> (X, X) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (
		X -> Bool
forall a. Integral a => a -> Bool
even (X -> Bool) -> (X -> Bool) -> (X, X) -> (Bool, Bool)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** X -> Bool
forall a. Integral a => a -> Bool
even
	) ((X, X) -> Bool) -> (X, X) -> Bool
forall a b. (a -> b) -> a -> b
$ Coordinates -> Coordinates -> (X, X)
measureDistance Coordinates
forall a. Bounded a => a
minBound Coordinates
coordinates	= LogicalColourOfSquare
Attribute.LogicalColourOfSquare.black
	| Bool
otherwise					= LogicalColourOfSquare
Attribute.LogicalColourOfSquare.white

-- | Whether the specified squares have the same /logical colour/.
areSquaresIsochromatic :: [Coordinates] -> Bool
areSquaresIsochromatic :: [Coordinates] -> Bool
areSquaresIsochromatic	= (Bool -> Bool -> Bool) -> (Bool, Bool) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Bool -> Bool -> Bool
(||) ((Bool, Bool) -> Bool)
-> ([Coordinates] -> (Bool, Bool)) -> [Coordinates] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((LogicalColourOfSquare -> Bool) -> [LogicalColourOfSquare] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (LogicalColourOfSquare -> LogicalColourOfSquare -> Bool
forall a. Eq a => a -> a -> Bool
== LogicalColourOfSquare
forall a. Bounded a => a
minBound) ([LogicalColourOfSquare] -> Bool)
-> ([LogicalColourOfSquare] -> Bool)
-> [LogicalColourOfSquare]
-> (Bool, Bool)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& (LogicalColourOfSquare -> Bool) -> [LogicalColourOfSquare] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (LogicalColourOfSquare -> LogicalColourOfSquare -> Bool
forall a. Eq a => a -> a -> Bool
== LogicalColourOfSquare
forall a. Bounded a => a
maxBound)) ([LogicalColourOfSquare] -> (Bool, Bool))
-> ([Coordinates] -> [LogicalColourOfSquare])
-> [Coordinates]
-> (Bool, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coordinates -> LogicalColourOfSquare)
-> [Coordinates] -> [LogicalColourOfSquare]
forall a b. (a -> b) -> [a] -> [b]
map Coordinates -> LogicalColourOfSquare
getLogicalColourOfSquare

-- | The conventional starting /coordinates/ for the @King@ of the specified /logical colour/.
kingsStartingCoordinates :: Attribute.LogicalColour.LogicalColour -> Coordinates
kingsStartingCoordinates :: LogicalColour -> Coordinates
kingsStartingCoordinates LogicalColour
logicalColour	= MkCoordinates :: X -> X -> Coordinates
MkCoordinates {
	getX :: X
getX	= X
Cartesian.Abscissa.kingsFile,
	getY :: X
getY	= LogicalColour -> X
Cartesian.Ordinate.firstRank LogicalColour
logicalColour
}

-- | The conventional starting /coordinates/ for each @Rook@.
rooksStartingCoordinates :: Attribute.LogicalColour.LogicalColour -> [Coordinates]
rooksStartingCoordinates :: LogicalColour -> [Coordinates]
rooksStartingCoordinates LogicalColour
Attribute.LogicalColour.Black	= [Coordinates
topLeft, Coordinates
forall a. Bounded a => a
maxBound]
rooksStartingCoordinates LogicalColour
_				= [Coordinates
forall a. Bounded a => a
minBound, Coordinates
bottomRight]

-- | Whether the specified /coordinates/ are where a @Pawn@ of the specified /logical colour/ starts.
isPawnsFirstRank :: Attribute.LogicalColour.LogicalColour -> Coordinates -> Bool
isPawnsFirstRank :: LogicalColour -> Coordinates -> Bool
isPawnsFirstRank LogicalColour
logicalColour MkCoordinates { getY :: Coordinates -> X
getY = X
y }	= X
y X -> X -> Bool
forall a. Eq a => a -> a -> Bool
== LogicalColour -> X
Cartesian.Ordinate.pawnsFirstRank LogicalColour
logicalColour

-- | Whether a @Pawn@ is currently on the appropriate /rank/ to take an opponent's @Pawn@ /en-passant/.
isEnPassantRank :: Attribute.LogicalColour.LogicalColour -> Coordinates -> Bool
isEnPassantRank :: LogicalColour -> Coordinates -> Bool
isEnPassantRank LogicalColour
logicalColour MkCoordinates { getY :: Coordinates -> X
getY = X
y }	= X
y X -> X -> Bool
forall a. Eq a => a -> a -> Bool
== LogicalColour -> X
Cartesian.Ordinate.enPassantRank LogicalColour
logicalColour

-- | A boxed array indexed by /coordinates/, of arbitrary elements.
type ArrayByCoordinates	= Data.Array.IArray.Array Coordinates

-- | An unboxed array indexed by /coordinates/, of fixed-size elements.
type UArrayByCoordinates	= Data.Array.Unboxed.UArray Coordinates

-- | Array-constructor from an ordered list of elements.
listArrayByCoordinates :: Data.Array.IArray.IArray a e => [e] -> a Coordinates e
listArrayByCoordinates :: [e] -> a Coordinates e
listArrayByCoordinates	= (Coordinates, Coordinates) -> [e] -> a Coordinates e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
Data.Array.IArray.listArray (Coordinates
forall a. Bounded a => a
minBound, Coordinates
forall a. Bounded a => a
maxBound)

-- | Array-constructor from an association-list.
arrayByCoordinates :: Data.Array.IArray.IArray a e => [(Coordinates, e)] -> a Coordinates e
arrayByCoordinates :: [(Coordinates, e)] -> a Coordinates e
arrayByCoordinates	= (Coordinates, Coordinates) -> [(Coordinates, e)] -> a Coordinates e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
Data.Array.IArray.array (Coordinates
forall a. Bounded a => a
minBound, Coordinates
forall a. Bounded a => a
maxBound)