{-# LANGUAGE CPP #-}

#ifdef USE_PRIMITIVE
{-# LANGUAGE MagicHash #-}
#endif

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

	* Describes the /y/-axis by which the /board/ is indexed.

	* AKA the /rank/ of a piece.

	* N.B. this coordinate-system is for internal use only, and doesn't attempt to replicate any standard chess-notation.
-}

module BishBosh.Cartesian.Ordinate(
-- * Constants
	yLength,
	yMin,
	yMax,
	yBounds,
	yRange,
-- * Functions
	toIx,
	fromIx,
	firstRank,
	lastRank,
	pawnsFirstRank,
	enPassantRank,
	reflect,
	translate,
	maybeTranslate,
-- ** Predicates
	inBounds
) where

import			Control.Arrow((&&&))
import qualified	BishBosh.Cartesian.Abscissa	as Cartesian.Abscissa
import qualified	BishBosh.Colour.LogicalColour	as Colour.LogicalColour
import qualified	BishBosh.Property.Opposable	as Property.Opposable
import qualified	BishBosh.Type.Length		as Type.Length
import qualified	Control.Exception

#ifdef USE_PRIMITIVE
import			GHC.Exts(Int(I#))
import			GHC.Prim((-#))
#endif

-- | The constant length of the /y/-axis.
yLength :: Type.Length.Y
yLength :: Y
yLength	= Y -> Y
forall a b. (Integral a, Num b) => a -> b
fromIntegral Y
Cartesian.Abscissa.xLength	-- I.E.: the board is square.

-- | The constant bounds of ordinates.
yBounds :: (Type.Length.Y, Type.Length.Y)
yMin, yMax :: Type.Length.Y
yBounds :: (Y, Y)
yBounds@(Y
yMin, Y
yMax)	= (Y
0, Y
yMin Y -> Y -> Y
forall a. Num a => a -> a -> a
+ Y -> Y
forall a. Enum a => a -> a
pred {-fence-post-} Y
yLength)

-- | The constant list of all ordinates.
yRange :: [Type.Length.Y]
yRange :: [Y]
yRange	= (Y -> Y -> [Y]) -> (Y, Y) -> [Y]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Y -> Y -> [Y]
forall a. Enum a => a -> a -> [a]
enumFromTo (Y, Y)
yBounds

-- | Convert to an array-index.
toIx :: Type.Length.Y -> Int
toIx :: Y -> Y
toIx	= Y -> Y
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Y -> Y) -> (Y -> Y) -> Y -> Y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Y -> Y -> Y
forall a. Num a => a -> a -> a
subtract Y
yMin

-- | Convert from an array-index.
fromIx :: Int -> Type.Length.Y
fromIx :: Y -> Y
fromIx	= (Y -> Y -> Y
forall a. Num a => a -> a -> a
+ Y
yMin) (Y -> Y) -> (Y -> Y) -> Y -> Y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Y -> Y
forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | The /rank/ from which /piece/s conventionally start.
firstRank :: Colour.LogicalColour.LogicalColour -> Type.Length.Y
firstRank :: LogicalColour -> Y
firstRank LogicalColour
Colour.LogicalColour.Black	= Y
yMax
firstRank LogicalColour
_				= Y
yMin

-- | The final /rank/; i.e. the one on which a @Pawn@ is promoted.
lastRank :: Colour.LogicalColour.LogicalColour -> Type.Length.Y
lastRank :: LogicalColour -> Y
lastRank	= LogicalColour -> Y
firstRank (LogicalColour -> Y)
-> (LogicalColour -> LogicalColour) -> LogicalColour -> Y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogicalColour -> LogicalColour
forall a. Opposable a => a -> a
Property.Opposable.getOpposite

-- | The /rank/ from which @Pawn@s conventionally start.
pawnsFirstRank :: Colour.LogicalColour.LogicalColour -> Type.Length.Y
{-# INLINE pawnsFirstRank #-}
pawnsFirstRank :: LogicalColour -> Y
pawnsFirstRank LogicalColour
Colour.LogicalColour.Black	= Y -> Y
forall a. Enum a => a -> a
pred Y
yMax
pawnsFirstRank LogicalColour
_				= Y -> Y
forall a. Enum a => a -> a
succ Y
yMin

-- | The /rank/ from which a @Pawn@ may capture /en-passant/.
enPassantRank :: Colour.LogicalColour.LogicalColour -> Type.Length.Y
{-# INLINE enPassantRank #-}
enPassantRank :: LogicalColour -> Y
enPassantRank LogicalColour
Colour.LogicalColour.Black	= Y -> Y
fromIx Y
3
enPassantRank LogicalColour
_					= Y -> Y
fromIx Y
4

-- | Reflects about the mid-point of the axis.
reflect :: Type.Length.Y -> Type.Length.Y
#ifdef USE_PRIMITIVE
reflect :: Y -> Y
reflect (I# Int#
y)	= Int# -> Y
I# (Int#
7# Int# -> Int# -> Int#
-# Int#
y)	-- CAVEAT: hard-coded bounds.
#else
reflect	= (2 * yMin + yMax -)
#endif

-- | Predicate.
inBounds :: Type.Length.Y -> Bool
{-# INLINE inBounds #-}
inBounds :: Y -> Bool
inBounds	= (Bool -> Bool -> Bool) -> (Bool, Bool) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Bool -> Bool -> Bool
(&&) ((Bool, Bool) -> Bool) -> (Y -> (Bool, Bool)) -> Y -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Y -> Y -> Bool
forall a. Ord a => a -> a -> Bool
>= Y
yMin) (Y -> Bool) -> (Y -> Bool) -> Y -> (Bool, Bool)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& (Y -> Y -> Bool
forall a. Ord a => a -> a -> Bool
<= Y
yMax))

-- | Translate the specified ordinate.
translate :: (Type.Length.Y -> Type.Length.Y) -> Type.Length.Y -> Type.Length.Y
translate :: (Y -> Y) -> Y -> Y
translate Y -> Y
transformation	= (\Y
y -> Bool -> Y -> Y
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (Y -> Bool
inBounds Y
y) Y
y) (Y -> Y) -> (Y -> Y) -> Y -> Y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Y -> Y
transformation

-- | Where legal, translate the specified ordinate.
maybeTranslate :: (Type.Length.Y -> Type.Length.Y) -> Type.Length.Y -> Maybe Type.Length.Y
maybeTranslate :: (Y -> Y) -> Y -> Maybe Y
maybeTranslate Y -> Y
transformation	= (
	\Y
y -> if Y -> Bool
inBounds Y
y
		then Y -> Maybe Y
forall a. a -> Maybe a
Just Y
y
		else Maybe Y
forall a. Maybe a
Nothing
 ) (Y -> Maybe Y) -> (Y -> Y) -> Y -> Maybe Y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Y -> Y
transformation