{-
	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 /x/-axis by which the /board/ is indexed.

	* AKA the /file/ 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.Abscissa(
-- * Types
	ArrayByAbscissa,
-- * Constants
	xOrigin,
	xLength,
	xMin,
	xMax,
	xBounds,
	xRange,
-- * Functions
	toIx,
	fromIx,
	reflect,
	translate,
	maybeTranslate,
	getAdjacents,
-- ** Constructors
	listArrayByAbscissa,
-- ** Predicates
	inBounds
) where

import qualified	BishBosh.Data.Enum	as Data.Enum
import qualified	BishBosh.Types		as T
import qualified	Control.Exception
import qualified	Data.Array.IArray

-- | The position of the origin on the /x/-axis.
xOrigin :: Int
xOrigin :: Int
xOrigin	= Int
0

-- | The constant length of the /x/-axis.
xLength :: T.Distance
xLength :: Int
xLength	= Int
8

-- | The constant lower bound of abscissae.
xMin :: Enum x => x
xMin :: x
xMin	= Int -> x
forall a. Enum a => Int -> a
toEnum Int
xOrigin

-- | The constant upper bound of abscissae.
xMax :: Enum x => x
xMax :: x
xMax	= Int -> x
forall a. Enum a => Int -> a
toEnum (Int -> x) -> Int -> x
forall a b. (a -> b) -> a -> b
$ Int
xOrigin 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 {-fence-post-} Int
xLength)

-- | The constant bounds of abscissae.
xBounds :: Enum x => (x, x)
xBounds :: (x, x)
xBounds	= (x
forall x. Enum x => x
xMin, x
forall x. Enum x => x
xMax)

-- | The constant list of all abscissae.
xRange :: Enum x => [x]
xRange :: [x]
xRange	= (x -> x -> [x]) -> (x, x) -> [x]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry x -> x -> [x]
forall a. Enum a => a -> a -> [a]
enumFromTo (x, x)
forall x. Enum x => (x, x)
xBounds

-- | Convert to an array-index.
toIx :: Enum x => x -> Int
{-# INLINE toIx #-}
toIx :: x -> Int
toIx	= Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
xOrigin (Int -> Int) -> (x -> Int) -> x -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> Int
forall a. Enum a => a -> Int
fromEnum

-- | Convert from an array-index.
fromIx :: Enum x => Int -> x
{-# INLINE fromIx #-}
fromIx :: Int -> x
fromIx	= Int -> x
forall a. Enum a => Int -> a
toEnum (Int -> x) -> (Int -> Int) -> Int -> x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
xOrigin)

-- | Reflects about the mid-point of the axis.
reflect :: Enum x => x -> x
reflect :: x -> x
reflect	= (Int -> Int) -> x -> x
forall a b. (Enum a, Enum b) => (Int -> Int) -> a -> b
Data.Enum.translate ((Int -> Int) -> x -> x) -> (Int -> Int) -> x -> x
forall a b. (a -> b) -> a -> b
$ (
	Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
xOrigin 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
xLength))
 ) (Int -> Int) -> (Int -> Int) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Num a => a -> a
negate

-- | Predicate.
inBounds :: (Enum x, Ord x) => x -> Bool
{-# INLINE inBounds #-}
inBounds :: x -> Bool
inBounds x
x	= x
x x -> x -> Bool
forall a. Ord a => a -> a -> Bool
>= x
forall x. Enum x => x
xMin Bool -> Bool -> Bool
&& x
x x -> x -> Bool
forall a. Ord a => a -> a -> Bool
<= x
forall x. Enum x => x
xMax

-- | Translate the specified ordinate.
translate :: (Enum x, Ord x) => (x -> x) -> x -> x
translate :: (x -> x) -> x -> x
translate x -> x
transformation	= (\x
x -> Bool -> x -> x
forall a. (?callStack::CallStack) => Bool -> a -> a
Control.Exception.assert (x -> Bool
forall x. (Enum x, Ord x) => x -> Bool
inBounds x
x) x
x) (x -> x) -> (x -> x) -> x -> x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> x
transformation

-- | Where legal, translate the specified abscissa.
maybeTranslate :: (Enum x, Ord x) => (x -> x) -> x -> Maybe x
maybeTranslate :: (x -> x) -> x -> Maybe x
maybeTranslate x -> x
transformation	= (
	\x
x -> if x -> Bool
forall x. (Enum x, Ord x) => x -> Bool
inBounds x
x
		then x -> Maybe x
forall a. a -> Maybe a
Just x
x
		else Maybe x
forall a. Maybe a
Nothing
 ) (x -> Maybe x) -> (x -> x) -> x -> Maybe x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> x
transformation

-- | Get the abscissae immediately left & right.
getAdjacents :: (Enum x, Eq x) => x -> [x]
{-# INLINE getAdjacents #-}
getAdjacents :: x -> [x]
getAdjacents x
x
	| x
x x -> x -> Bool
forall a. Eq a => a -> a -> Bool
== x
forall x. Enum x => x
xMin	= [x -> x
forall a. Enum a => a -> a
succ x
forall x. Enum x => x
xMin]
	| x
x x -> x -> Bool
forall a. Eq a => a -> a -> Bool
== x
forall x. Enum x => x
xMax	= [x -> x
forall a. Enum a => a -> a
pred x
forall x. Enum x => x
xMax]
	| Bool
otherwise	= [x -> x
forall a. Enum a => a -> a
pred x
x, x -> x
forall a. Enum a => a -> a
succ x
x]

-- | A boxed array indexed by /coordinates/, of arbitrary elements.
type ArrayByAbscissa x	= Data.Array.IArray.Array {-Boxed-} x

-- | Array-constructor.
listArrayByAbscissa :: (
	Data.Array.IArray.IArray	a e,
	Data.Array.IArray.Ix		x,
	Enum				x
 ) => [e] -> a x e
listArrayByAbscissa :: [e] -> a x e
listArrayByAbscissa	= (x, x) -> [e] -> a x e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
Data.Array.IArray.listArray (x, x)
forall x. Enum x => (x, x)
xBounds