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

	* <https://www.chessprogramming.org/Algebraic_Chess_Notation#Pure_coordinate_notation>.

	* CAVEAT: <https://en.wikipedia.org/wiki/Chess_notation> defined a variant of this notation.

	* N.B.: used for communication via /CECP/ with /xboard/.
-}

module BishBosh.Notation.Coordinate(
-- * Types
-- ** Data-types
	Coordinate(
--		MkCoordinate,
		getMove
--		getMaybePromotionRank
	),
-- * Constants
--	xOrigin,
--	yOrigin,
	origin,
	regexSyntax,
-- * Functions
--	encode,
	showsCoordinates,
-- ** Constructors
	mkCoordinate,
	mkCoordinate'
) where

import			Control.Arrow((&&&))
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.Move		as Component.Move
import qualified	BishBosh.Data.Exception		as Data.Exception
import qualified	Control.Arrow
import qualified	Control.Exception
import qualified	Data.Char
import qualified	Data.List.Extra
import qualified	Data.Maybe

-- | The /x/-origin.
xOrigin :: Int
xOrigin :: Int
xOrigin	= Char -> Int
Data.Char.ord Char
'a'

-- | The /y/-origin.
yOrigin :: Int
yOrigin :: Int
yOrigin	= Char -> Int
Data.Char.ord Char
'1'

-- | The origin.
origin :: (Int, Int)
origin :: (Int, Int)
origin	= (Int
xOrigin, Int
yOrigin)

-- | Defines using a regex, the required syntax.
regexSyntax :: String
regexSyntax :: String
regexSyntax	= String -> ShowS
showString String
"([a-h][1-8]){2}[" ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString (
	(Rank -> String) -> [Rank] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Rank -> String
forall a. Show a => a -> String
show [Rank]
Attribute.Rank.promotionProspects
 ) String
"]?"

-- | Defines a /move/, to enable i/o in /Coordinate/-notation.
data Coordinate x y	= MkCoordinate {
	Coordinate x y -> Move x y
getMove			:: Component.Move.Move x y,
	Coordinate x y -> Maybe Rank
getMaybePromotionRank	:: Maybe Attribute.Rank.Rank
} deriving Coordinate x y -> Coordinate x y -> Bool
(Coordinate x y -> Coordinate x y -> Bool)
-> (Coordinate x y -> Coordinate x y -> Bool)
-> Eq (Coordinate x y)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall x y.
(Eq x, Eq y) =>
Coordinate x y -> Coordinate x y -> Bool
/= :: Coordinate x y -> Coordinate x y -> Bool
$c/= :: forall x y.
(Eq x, Eq y) =>
Coordinate x y -> Coordinate x y -> Bool
== :: Coordinate x y -> Coordinate x y -> Bool
$c== :: forall x y.
(Eq x, Eq y) =>
Coordinate x y -> Coordinate x y -> Bool
Eq

-- | Smart constructor.
mkCoordinate :: Component.Move.Move x y -> Maybe Attribute.Rank.Rank -> Coordinate x y
mkCoordinate :: Move x y -> Maybe Rank -> Coordinate x y
mkCoordinate Move x y
move Maybe Rank
maybePromotionRank
	| Just Rank
rank	<- Maybe Rank
maybePromotionRank
	, Rank
rank Rank -> [Rank] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Rank]
Attribute.Rank.promotionProspects	= Exception -> Coordinate x y
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Coordinate x y)
-> (String -> Exception) -> String -> Coordinate x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkInvalidDatum (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Notation.Coordinate.Coordinate:\tcan't promote to a " (String -> Coordinate x y) -> String -> Coordinate x y
forall a b. (a -> b) -> a -> b
$ Rank -> ShowS
forall a. Show a => a -> ShowS
shows Rank
rank String
"."
	| Bool
otherwise						= MkCoordinate :: forall x y. Move x y -> Maybe Rank -> Coordinate x y
MkCoordinate {
		getMove :: Move x y
getMove			= Move x y
move,
		getMaybePromotionRank :: Maybe Rank
getMaybePromotionRank	= Maybe Rank
maybePromotionRank
	}

-- | Smart constructor.
mkCoordinate' :: Attribute.Rank.Promotable promotable => Component.Move.Move x y -> promotable -> Coordinate x y
mkCoordinate' :: Move x y -> promotable -> Coordinate x y
mkCoordinate' Move x y
move	= Move x y -> Maybe Rank -> Coordinate x y
forall x y. Move x y -> Maybe Rank -> Coordinate x y
mkCoordinate Move x y
move (Maybe Rank -> Coordinate x y)
-> (promotable -> Maybe Rank) -> promotable -> Coordinate x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. promotable -> Maybe Rank
forall a. Promotable a => a -> Maybe Rank
Attribute.Rank.getMaybePromotionRank

-- | Encodes the ordinate & abscissa.
encode :: (Enum x, Enum y) => Cartesian.Coordinates.Coordinates x y -> (ShowS, ShowS)
encode :: Coordinates x y -> (ShowS, ShowS)
encode	= Char -> ShowS
showChar (Char -> ShowS)
-> (Coordinates x y -> Char) -> Coordinates x y -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Char
Data.Char.chr (Int -> Char)
-> (Coordinates x y -> Int) -> Coordinates x y -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
xOrigin Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
Cartesian.Abscissa.xOrigin)) (Int -> Int) -> (Coordinates x y -> Int) -> Coordinates x y -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> Int
forall a. Enum a => a -> Int
fromEnum (x -> Int) -> (Coordinates x y -> x) -> Coordinates x y -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> x
forall x y. Coordinates x y -> x
Cartesian.Coordinates.getX (Coordinates x y -> ShowS)
-> (Coordinates x y -> ShowS) -> Coordinates x y -> (ShowS, ShowS)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Char -> ShowS
showChar (Char -> ShowS)
-> (Coordinates x y -> Char) -> Coordinates x y -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Char
Data.Char.chr (Int -> Char)
-> (Coordinates x y -> Int) -> Coordinates x y -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
yOrigin Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
Cartesian.Ordinate.yOrigin)) (Int -> Int) -> (Coordinates x y -> Int) -> Coordinates x y -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. y -> Int
forall a. Enum a => a -> Int
fromEnum (y -> Int) -> (Coordinates x y -> y) -> Coordinates x y -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> y
forall x y. Coordinates x y -> y
Cartesian.Coordinates.getY

-- | Shows the specified /coordinates/.
showsCoordinates :: (Enum x, Enum y) => Cartesian.Coordinates.Coordinates x y -> ShowS
showsCoordinates :: Coordinates x y -> ShowS
showsCoordinates	= (ShowS -> ShowS -> ShowS) -> (ShowS, ShowS) -> ShowS
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ((ShowS, ShowS) -> ShowS)
-> (Coordinates x y -> (ShowS, ShowS)) -> Coordinates x y -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> (ShowS, ShowS)
forall x y. (Enum x, Enum y) => Coordinates x y -> (ShowS, ShowS)
encode

instance (Enum x, Enum y) => Show (Coordinate x y) where
	showsPrec :: Int -> Coordinate x y -> ShowS
showsPrec Int
_ MkCoordinate {
		getMove :: forall x y. Coordinate x y -> Move x y
getMove			= Move x y
move,
		getMaybePromotionRank :: forall x y. Coordinate x y -> Maybe Rank
getMaybePromotionRank	= Maybe Rank
maybePromotionRank
	} = Coordinates x y -> ShowS
forall x y. (Enum x, Enum y) => Coordinates x y -> ShowS
showsCoordinates (
		Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getSource Move x y
move
	 ) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates x y -> ShowS
forall x y. (Enum x, Enum y) => Coordinates x y -> ShowS
showsCoordinates (
		Move x y -> Coordinates x y
forall x y. Move x y -> Coordinates x y
Component.Move.getDestination Move x y
move
	 ) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS -> (Rank -> ShowS) -> Maybe Rank -> ShowS
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe ShowS
forall a. a -> a
id Rank -> ShowS
forall a. Show a => a -> ShowS
shows Maybe Rank
maybePromotionRank

-- N.B. this merely validates the syntax, leaving any semantic errors to 'Model.Game.validate'.
instance (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y
 ) => Read (Coordinate x y) where
	readsPrec :: Int -> ReadS (Coordinate x y)
readsPrec Int
_ String
s	= case ShowS
Data.List.Extra.trimStart String
s of
		Char
x : Char
y : Char
x' : Char
y' : String
remainder	-> let
			translate :: Char -> Char -> Maybe (Coordinates x y)
translate Char
x'' Char
y''	= x -> y -> Maybe (Coordinates x y)
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
x -> y -> Maybe (Coordinates x y)
Cartesian.Coordinates.mkMaybeCoordinates (
				Int -> x
forall a. Enum a => Int -> a
toEnum (Int -> x) -> Int -> x
forall a b. (a -> b) -> a -> b
$ Char -> Int
Data.Char.ord Char
x'' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
Cartesian.Abscissa.xOrigin Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
xOrigin)
			 ) (
				Int -> y
forall a. Enum a => Int -> a
toEnum (Int -> y) -> Int -> y
forall a b. (a -> b) -> a -> b
$ Char -> Int
Data.Char.ord Char
y'' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
Cartesian.Ordinate.yOrigin Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
yOrigin)
			 )
		 in [
			(Maybe Rank -> Coordinate x y)
-> (Maybe Rank, String) -> (Coordinate x y, String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first (
				Move x y -> Maybe Rank -> Coordinate x y
forall x y. Move x y -> Maybe Rank -> Coordinate x y
mkCoordinate (Move x y -> Maybe Rank -> Coordinate x y)
-> Move x y -> Maybe Rank -> Coordinate x y
forall a b. (a -> b) -> a -> b
$ Coordinates x y -> Coordinates x y -> Move x y
forall x y.
(Eq x, Eq y) =>
Coordinates x y -> Coordinates x y -> Move x y
Component.Move.mkMove Coordinates x y
source Coordinates x y
destination
			) (
				case ReadS Rank
forall a. Read a => ReadS a
reads ReadS Rank -> ReadS Rank
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
take Int
1 String
remainder of
					[(Rank
rank, String
"")]	-> if Rank
rank Rank -> [Rank] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Rank]
Attribute.Rank.promotionProspects
						then (Rank -> Maybe Rank
forall a. a -> Maybe a
Just Rank
rank, ShowS
forall a. [a] -> [a]
tail String
remainder)
						else (Maybe Rank
forall a. Maybe a
Nothing, String
remainder)
					[(Rank, String)]
_	-> (Maybe Rank
forall a. Maybe a
Nothing, String
remainder)
			) |
				Coordinates x y
source		<- Maybe (Coordinates x y) -> [Coordinates x y]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Coordinates x y) -> [Coordinates x y])
-> Maybe (Coordinates x y) -> [Coordinates x y]
forall a b. (a -> b) -> a -> b
$ Char -> Char -> Maybe (Coordinates x y)
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Char -> Char -> Maybe (Coordinates x y)
translate Char
x Char
y,
				Coordinates x y
destination	<- Maybe (Coordinates x y) -> [Coordinates x y]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Coordinates x y) -> [Coordinates x y])
-> Maybe (Coordinates x y) -> [Coordinates x y]
forall a b. (a -> b) -> a -> b
$ Char -> Char -> Maybe (Coordinates x y)
forall x y.
(Enum x, Enum y, Ord x, Ord y) =>
Char -> Char -> Maybe (Coordinates x y)
translate Char
x' Char
y',
				Coordinates x y
source Coordinates x y -> Coordinates x y -> Bool
forall a. Eq a => a -> a -> Bool
/= Coordinates x y
destination
		 ] -- List-comprehension.
		String
_					-> []	-- No parse.

instance Attribute.Rank.Promotable (Coordinate x y) where
	getMaybePromotionRank :: Coordinate x y -> Maybe Rank
getMaybePromotionRank	= Coordinate x y -> Maybe Rank
forall x y. Coordinate x y -> Maybe Rank
getMaybePromotionRank