{-
	Copyright (C) 2021 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 directional components of a line parallel to an edge of the board.
-}

module BishBosh.Direction.Parallel(
-- * Types
-- ** Data-types
	Parallel(),
-- * Constants
--	range,
	nParallels
) where

import			Control.Arrow((|||), (+++))
import qualified	BishBosh.Direction.Horizontal		as Direction.Horizontal
import qualified	BishBosh.Direction.Vertical		as Direction.Vertical
import qualified	BishBosh.Property.FixedMembership	as Property.FixedMembership
import qualified	BishBosh.Property.Opposable		as Property.Opposable
import qualified	BishBosh.Property.Orientated		as Property.Orientated
import qualified	BishBosh.Property.Reflectable		as Property.Reflectable
import qualified	BishBosh.Type.Count			as Type.Count
import qualified	Control.DeepSeq
import qualified	Data.List.Extra

-- | Directions parallel to two edges of the board; those in which a Rook can move.
newtype Parallel	= MkParallel (Either Direction.Vertical.Vertical Direction.Horizontal.Horizontal) deriving (Parallel -> Parallel -> Bool
(Parallel -> Parallel -> Bool)
-> (Parallel -> Parallel -> Bool) -> Eq Parallel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Parallel -> Parallel -> Bool
$c/= :: Parallel -> Parallel -> Bool
== :: Parallel -> Parallel -> Bool
$c== :: Parallel -> Parallel -> Bool
Eq, Eq Parallel
Eq Parallel
-> (Parallel -> Parallel -> Ordering)
-> (Parallel -> Parallel -> Bool)
-> (Parallel -> Parallel -> Bool)
-> (Parallel -> Parallel -> Bool)
-> (Parallel -> Parallel -> Bool)
-> (Parallel -> Parallel -> Parallel)
-> (Parallel -> Parallel -> Parallel)
-> Ord Parallel
Parallel -> Parallel -> Bool
Parallel -> Parallel -> Ordering
Parallel -> Parallel -> Parallel
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Parallel -> Parallel -> Parallel
$cmin :: Parallel -> Parallel -> Parallel
max :: Parallel -> Parallel -> Parallel
$cmax :: Parallel -> Parallel -> Parallel
>= :: Parallel -> Parallel -> Bool
$c>= :: Parallel -> Parallel -> Bool
> :: Parallel -> Parallel -> Bool
$c> :: Parallel -> Parallel -> Bool
<= :: Parallel -> Parallel -> Bool
$c<= :: Parallel -> Parallel -> Bool
< :: Parallel -> Parallel -> Bool
$c< :: Parallel -> Parallel -> Bool
compare :: Parallel -> Parallel -> Ordering
$ccompare :: Parallel -> Parallel -> Ordering
$cp1Ord :: Eq Parallel
Ord)

instance Control.DeepSeq.NFData Parallel where
	rnf :: Parallel -> ()
rnf (MkParallel Either Vertical Horizontal
p)	= Vertical -> ()
forall a. a -> ()
Control.DeepSeq.rwhnf (Vertical -> ())
-> (Horizontal -> ()) -> Either Vertical Horizontal -> ()
forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| Horizontal -> ()
forall a. a -> ()
Control.DeepSeq.rwhnf (Either Vertical Horizontal -> ())
-> Either Vertical Horizontal -> ()
forall a b. (a -> b) -> a -> b
$ Either Vertical Horizontal
p

instance Enum Parallel where
	fromEnum :: Parallel -> Int
fromEnum (MkParallel Either Vertical Horizontal
p)	= Vertical -> Int
forall a. Enum a => a -> Int
fromEnum (Vertical -> Int)
-> (Horizontal -> Int) -> Either Vertical Horizontal -> Int
forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Direction.Vertical.nVerticals) (Int -> Int) -> (Horizontal -> Int) -> Horizontal -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Horizontal -> Int
forall a. Enum a => a -> Int
fromEnum (Either Vertical Horizontal -> Int)
-> Either Vertical Horizontal -> Int
forall a b. (a -> b) -> a -> b
$ Either Vertical Horizontal
p

	toEnum :: Int -> Parallel
toEnum Int
i	= Either Vertical Horizontal -> Parallel
MkParallel (Either Vertical Horizontal -> Parallel)
-> Either Vertical Horizontal -> Parallel
forall a b. (a -> b) -> a -> b
$! case Int
i Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Direction.Vertical.nVerticals of
		(Int
0, Int
remainder)	-> Vertical -> Either Vertical Horizontal
forall a b. a -> Either a b
Left (Vertical -> Either Vertical Horizontal)
-> Vertical -> Either Vertical Horizontal
forall a b. (a -> b) -> a -> b
$! Int -> Vertical
forall a. Enum a => Int -> a
toEnum Int
remainder
		(~Int
1, Int
remainder)	-> Horizontal -> Either Vertical Horizontal
forall a b. b -> Either a b
Right (Horizontal -> Either Vertical Horizontal)
-> Horizontal -> Either Vertical Horizontal
forall a b. (a -> b) -> a -> b
$! Int -> Horizontal
forall a. Enum a => Int -> a
toEnum Int
remainder

instance Show Parallel where
	showsPrec :: Int -> Parallel -> ShowS
showsPrec Int
precedence (MkParallel Either Vertical Horizontal
p)	= Int -> Vertical -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
precedence (Vertical -> ShowS)
-> (Horizontal -> ShowS) -> Either Vertical Horizontal -> ShowS
forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| Int -> Horizontal -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
precedence (Either Vertical Horizontal -> ShowS)
-> Either Vertical Horizontal -> ShowS
forall a b. (a -> b) -> a -> b
$ Either Vertical Horizontal
p

instance Read Parallel where
	readsPrec :: Int -> ReadS Parallel
readsPrec Int
precedence String
s	= let
		s' :: String
s'	= ShowS
Data.List.Extra.trimStart String
s
	 in case Int -> ReadS Vertical
forall a. Read a => Int -> ReadS a
readsPrec Int
precedence String
s' of
		[(Vertical
vertical, String
s'')]	-> [(Either Vertical Horizontal -> Parallel
MkParallel (Either Vertical Horizontal -> Parallel)
-> Either Vertical Horizontal -> Parallel
forall a b. (a -> b) -> a -> b
$ Vertical -> Either Vertical Horizontal
forall a b. a -> Either a b
Left Vertical
vertical, String
s'')]
		[(Vertical, String)]
_			-> case Int -> ReadS Horizontal
forall a. Read a => Int -> ReadS a
readsPrec Int
precedence String
s' of
			[(Horizontal
horizontal, String
s'')]	-> [(Either Vertical Horizontal -> Parallel
MkParallel (Either Vertical Horizontal -> Parallel)
-> Either Vertical Horizontal -> Parallel
forall a b. (a -> b) -> a -> b
$ Horizontal -> Either Vertical Horizontal
forall a b. b -> Either a b
Right Horizontal
horizontal, String
s'')]
			[(Horizontal, String)]
_			-> []	-- No parse.

instance Property.FixedMembership.FixedMembership Parallel where
	members :: [Parallel]
members	= [Parallel]
range

instance Property.Opposable.Opposable Parallel where
	getOpposite :: Parallel -> Parallel
getOpposite (MkParallel Either Vertical Horizontal
p)	= Either Vertical Horizontal -> Parallel
MkParallel (Either Vertical Horizontal -> Parallel)
-> Either Vertical Horizontal -> Parallel
forall a b. (a -> b) -> a -> b
$ (Vertical -> Vertical
forall a. Opposable a => a -> a
Property.Opposable.getOpposite (Vertical -> Vertical)
-> (Horizontal -> Horizontal)
-> Either Vertical Horizontal
-> Either Vertical Horizontal
forall (a :: * -> * -> *) b c b' c'.
ArrowChoice a =>
a b c -> a b' c' -> a (Either b b') (Either c c')
+++ Horizontal -> Horizontal
forall a. Opposable a => a -> a
Property.Opposable.getOpposite) Either Vertical Horizontal
p

instance Property.Orientated.Orientated Parallel where
	isVertical :: Parallel -> Bool
isVertical (MkParallel (Left Vertical
_))	= Bool
True
	isVertical Parallel
_				= Bool
False

	isHorizontal :: Parallel -> Bool
isHorizontal (MkParallel (Right Horizontal
_))	= Bool
True
	isHorizontal Parallel
_				= Bool
False

	isParallel :: Parallel -> Bool
isParallel	= Bool -> Parallel -> Bool
forall a b. a -> b -> a
const Bool
True

	isDiagonal :: Parallel -> Bool
isDiagonal	= Bool -> Parallel -> Bool
forall a b. a -> b -> a
const Bool
False

	isStraight :: Parallel -> Bool
isStraight	= Bool -> Parallel -> Bool
forall a b. a -> b -> a
const Bool
True

instance Property.Reflectable.ReflectableOnX Parallel where
	reflectOnX :: Parallel -> Parallel
reflectOnX (MkParallel Either Vertical Horizontal
p)	= Either Vertical Horizontal -> Parallel
MkParallel (Either Vertical Horizontal -> Parallel)
-> Either Vertical Horizontal -> Parallel
forall a b. (a -> b) -> a -> b
$ (Vertical -> Vertical
forall a. ReflectableOnX a => a -> a
Property.Reflectable.reflectOnX (Vertical -> Vertical)
-> (Horizontal -> Horizontal)
-> Either Vertical Horizontal
-> Either Vertical Horizontal
forall (a :: * -> * -> *) b c b' c'.
ArrowChoice a =>
a b c -> a b' c' -> a (Either b b') (Either c c')
+++ Horizontal -> Horizontal
forall a. a -> a
id) Either Vertical Horizontal
p

instance Property.Reflectable.ReflectableOnY Parallel where
	reflectOnY :: Parallel -> Parallel
reflectOnY (MkParallel Either Vertical Horizontal
p)	= Either Vertical Horizontal -> Parallel
MkParallel (Either Vertical Horizontal -> Parallel)
-> Either Vertical Horizontal -> Parallel
forall a b. (a -> b) -> a -> b
$ (Vertical -> Vertical
forall a. a -> a
id (Vertical -> Vertical)
-> (Horizontal -> Horizontal)
-> Either Vertical Horizontal
-> Either Vertical Horizontal
forall (a :: * -> * -> *) b c b' c'.
ArrowChoice a =>
a b c -> a b' c' -> a (Either b b') (Either c c')
+++ Horizontal -> Horizontal
forall a. ReflectableOnY a => a -> a
Property.Reflectable.reflectOnY) Either Vertical Horizontal
p

-- | Constant range of values.
range :: [Parallel]
range :: [Parallel]
range	= Int -> [Parallel] -> [Parallel]
forall a. Int -> [a] -> [a]
take (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
Direction.Vertical.nVerticals Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
Direction.Horizontal.nHorizontals) [ Int -> Parallel
forall a. Enum a => Int -> a
toEnum Int
0 .. ]

-- | The number of verticals directions.
nParallels :: Type.Count.NDirections
nParallels :: Int
nParallels	= Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ [Parallel] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Parallel]
range