{-
	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://en.wikipedia.org/wiki/ICCF_numeric_notation>.
-}

module BishBosh.Notation.ICCFNumeric(
-- * Types
-- ** Data-types
	ICCFNumeric(
--		MkICCFNumeric,
		getMove
--		getMaybePromotionRank
	),
-- * Constants
	notation,
	regexSyntax,
	toRank,
-- * Functions
-- ** Constructors
	mkICCFNumeric,
	mkICCFNumeric'
) where

import			Control.Arrow((&&&))
import qualified	BishBosh.Attribute.Rank		as Attribute.Rank
import qualified	BishBosh.Component.Move		as Component.Move
import qualified	BishBosh.Data.Exception		as Data.Exception
import qualified	BishBosh.Notation.Notation	as Notation.Notation
import qualified	Control.Arrow
import qualified	Control.Exception
import qualified	Data.List.Extra
import qualified	Data.Maybe
import qualified	Data.Tuple

-- | Define the parameters of the notation, using the minimum permissible values for /x/ & /y/ coordinates.
notation :: Notation.Notation.Notation
notation :: Notation
notation	= CoordinatePairC -> Notation
Notation.Notation.mkNotation (CoordinatePairC -> Notation) -> CoordinatePairC -> Notation
forall a b. (a -> b) -> a -> b
$ (Char -> Char
forall a. a -> a
id (Char -> Char) -> (Char -> Char) -> Char -> CoordinatePairC
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Char -> Char
forall a. a -> a
id) Char
'1'

-- | Defines using a regex, the required syntax.
regexSyntax :: String
regexSyntax :: String
regexSyntax	= String
"[1-8]{4}[1-4]?"

-- | Constant translation from integral promotion-specifications to the corresponding /rank/.
toRank :: [(Int, Attribute.Rank.Rank)]
toRank :: [(Int, Rank)]
toRank	= [Int] -> [Rank] -> [(Int, Rank)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1 ..] [
	Rank
Attribute.Rank.Queen,
	Rank
Attribute.Rank.Rook,
	Rank
Attribute.Rank.Bishop,
	Rank
Attribute.Rank.Knight
 ]

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

-- | Smart constructor.
mkICCFNumeric
	:: Component.Move.Move
	-> Maybe Attribute.Rank.Rank	-- ^ The optional promotion-rank.
	-> ICCFNumeric
mkICCFNumeric :: Move -> Maybe Rank -> ICCFNumeric
mkICCFNumeric Move
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 -> ICCFNumeric
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> ICCFNumeric)
-> (String -> Exception) -> String -> ICCFNumeric
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkInvalidDatum (String -> Exception) -> (String -> String) -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString String
"BishBosh.Notation.ICCFNumeric.mkICCFNumeric:\tcan't promote to a " (String -> ICCFNumeric) -> String -> ICCFNumeric
forall a b. (a -> b) -> a -> b
$ Rank -> String -> String
forall a. Show a => a -> String -> String
shows Rank
rank String
"."
	| Bool
otherwise						= MkICCFNumeric :: Move -> Maybe Rank -> ICCFNumeric
MkICCFNumeric {
		getMove :: Move
getMove			= Move
move,
		getMaybePromotionRank :: Maybe Rank
getMaybePromotionRank	= Maybe Rank
maybePromotionRank
	}

-- | Smart constructor.
mkICCFNumeric'
	:: Attribute.Rank.Promotable promotable
	=> Component.Move.Move
	-> promotable	-- ^ The datum from which to extract the optional promotion-rank.
	-> ICCFNumeric
mkICCFNumeric' :: Move -> promotable -> ICCFNumeric
mkICCFNumeric' Move
move	= Move -> Maybe Rank -> ICCFNumeric
mkICCFNumeric Move
move (Maybe Rank -> ICCFNumeric)
-> (promotable -> Maybe Rank) -> promotable -> ICCFNumeric
forall b c a. (b -> c) -> (a -> b) -> a -> c
. promotable -> Maybe Rank
forall a. Promotable a => a -> Maybe Rank
Attribute.Rank.getMaybePromotionRank

instance Show ICCFNumeric where
	showsPrec :: Int -> ICCFNumeric -> String -> String
showsPrec Int
_ MkICCFNumeric {
		getMove :: ICCFNumeric -> Move
getMove			= Move
move,
		getMaybePromotionRank :: ICCFNumeric -> Maybe Rank
getMaybePromotionRank	= Maybe Rank
maybePromotionRank
	} = Notation -> Coordinates -> String -> String
Notation.Notation.showsCoordinates Notation
notation (
		Move -> Coordinates
Component.Move.getSource Move
move
	 ) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Notation -> Coordinates -> String -> String
Notation.Notation.showsCoordinates Notation
notation (
		Move -> Coordinates
Component.Move.getDestination Move
move
	 ) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String)
-> (Rank -> String -> String) -> Maybe Rank -> String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe String -> String
forall a. a -> a
id (
		Int -> String -> String
forall a. Show a => a -> String -> String
shows (Int -> String -> String)
-> (Rank -> Int) -> Rank -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
Data.Maybe.fromJust (Maybe Int -> Int) -> (Rank -> Maybe Int) -> Rank -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rank -> [(Rank, Int)] -> Maybe Int
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`lookup` ((Int, Rank) -> (Rank, Int)) -> [(Int, Rank)] -> [(Rank, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Rank) -> (Rank, Int)
forall a b. (a, b) -> (b, a)
Data.Tuple.swap [(Int, Rank)]
toRank)
	 ) Maybe Rank
maybePromotionRank

-- N.B. this merely validates the syntax, leaving any semantic errors to 'Model.Game.validate'.
instance Read ICCFNumeric where
	readsPrec :: Int -> ReadS ICCFNumeric
readsPrec Int
_ String
s	= case String -> String
Data.List.Extra.trimStart String
s of
		Char
x : Char
y : Char
x' : Char
y' : String
remainder	-> [
			(Maybe Rank -> ICCFNumeric)
-> (Maybe Rank, String) -> (ICCFNumeric, String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first (
				Move -> Maybe Rank -> ICCFNumeric
mkICCFNumeric (Move -> Maybe Rank -> ICCFNumeric)
-> Move -> Maybe Rank -> ICCFNumeric
forall a b. (a -> b) -> a -> b
$ Coordinates -> Coordinates -> Move
Component.Move.mkMove Coordinates
source Coordinates
destination
			) (
				case ReadS Int
forall a. Read a => ReadS a
reads ReadS Int -> ReadS Int
forall a b. (a -> b) -> a -> b
$ Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
remainder of
					[(Int
digit, String
_)]
						| Just Rank
rank <- Int -> [(Int, Rank)] -> Maybe Rank
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Int
digit [(Int, Rank)]
toRank	-> (Rank -> Maybe Rank
forall a. a -> Maybe a
Just Rank
rank, String -> String
forall a. [a] -> [a]
tail String
remainder)
						| Bool
otherwise				-> (Maybe Rank
forall a. Maybe a
Nothing, String
remainder)
					[(Int, String)]
_						-> (Maybe Rank
forall a. Maybe a
Nothing, String
remainder)
			) |
				let mkCoordinatesList :: CoordinatePairC -> [Coordinates]
mkCoordinatesList	= Maybe Coordinates -> [Coordinates]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe Coordinates -> [Coordinates])
-> (CoordinatePairC -> Maybe Coordinates)
-> CoordinatePairC
-> [Coordinates]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Notation -> CoordinatePairC -> Maybe Coordinates
Notation.Notation.mkMaybeCoordinates Notation
notation,
				Coordinates
source		<- CoordinatePairC -> [Coordinates]
mkCoordinatesList (Char
x, Char
y),
				Coordinates
destination	<- CoordinatePairC -> [Coordinates]
mkCoordinatesList (Char
x', Char
y'),
				Coordinates
source Coordinates -> Coordinates -> Bool
forall a. Eq a => a -> a -> Bool
/= Coordinates
destination
		 ] -- List-comprehension.
		String
_				-> []	-- No parse.

instance Attribute.Rank.Promotable ICCFNumeric where
	getMaybePromotionRank :: ICCFNumeric -> Maybe Rank
getMaybePromotionRank	= ICCFNumeric -> Maybe Rank
getMaybePromotionRank