{-
	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@]	Defines the dynamic data a user can request at runtime.
-}

module BishBosh.UI.ReportObject (
-- * Types
-- ** Data-types
	ReportObject(..),
-- * Constants
--	availableMovesTag,
--	boardTag,
--	fenTag,
--	gameTag,
--	maxPositionInstancesTag,
--	movesTag,
--	pgnTag,
--	reversiblePlyCountTag,
	range,
-- * Functions
	autoComplete
 ) where

import qualified	BishBosh.Component.Move				as Component.Move
import qualified	BishBosh.Property.ExtendedPositionDescription	as Property.ExtendedPositionDescription
import qualified	BishBosh.Property.FixedMembership		as Property.FixedMembership
import qualified	BishBosh.Text.AutoComplete			as Text.AutoComplete
import qualified	Control.Arrow
import qualified	Control.DeepSeq
import qualified	Data.List.Extra

-- | Input-format.
availableMovesTag :: String
availableMovesTag :: String
availableMovesTag	= String
"availableMoves"

-- | Input-format.
boardTag :: String
boardTag :: String
boardTag		= String
"board"

-- | Input-format.
fenTag :: String
fenTag :: String
fenTag			= String
"fen"

-- | Input-format.
gameTag :: String
gameTag :: String
gameTag			= String
"game"

-- | Input-format.
maxPositionInstancesTag :: String
maxPositionInstancesTag :: String
maxPositionInstancesTag	= String
"maxPositionInstances"

-- | Input-format.
movesTag :: String
movesTag :: String
movesTag		= String -> ShowS
showString String
Component.Move.tag String
"s"

-- | Input-format.
pgnTag :: String
pgnTag :: String
pgnTag			= String
"pgn"

-- | Input-format.
reversiblePlyCountTag :: String
reversiblePlyCountTag :: String
reversiblePlyCountTag	= String
"reversiblePlyCount"

-- | A sum-type of objects a user may want to print at runtime.
data ReportObject
	= AvailableMoves
	| Board
	| EPD
	| FEN
	| Game
	| MaxPositionInstances
	| Moves
	| PGN
	| ReversiblePlyCount
	deriving ReportObject -> ReportObject -> Bool
(ReportObject -> ReportObject -> Bool)
-> (ReportObject -> ReportObject -> Bool) -> Eq ReportObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReportObject -> ReportObject -> Bool
$c/= :: ReportObject -> ReportObject -> Bool
== :: ReportObject -> ReportObject -> Bool
$c== :: ReportObject -> ReportObject -> Bool
Eq

instance Control.DeepSeq.NFData ReportObject where
	rnf :: ReportObject -> ()
rnf ReportObject
_	= ()

instance Show ReportObject where
	show :: ReportObject -> String
show ReportObject
AvailableMoves		= String
availableMovesTag
	show ReportObject
Board			= String
boardTag
	show ReportObject
EPD			= String
Property.ExtendedPositionDescription.tag
	show ReportObject
FEN			= String
fenTag
	show ReportObject
Game			= String
gameTag
	show ReportObject
MaxPositionInstances	= String
maxPositionInstancesTag
	show ReportObject
Moves			= String
movesTag
	show ReportObject
PGN			= String
pgnTag
	show ReportObject
ReversiblePlyCount		= String
reversiblePlyCountTag

instance Read ReportObject where
	readsPrec :: Int -> ReadS ReportObject
readsPrec Int
_ String
s	= case ShowS -> (String, String) -> (String, String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first ShowS
Data.List.Extra.lower ((String, String) -> (String, String))
-> [(String, String)] -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
`map` ReadS String
lex String
s of
		[(String
"availablemoves", String
remainder)]		-> [(ReportObject
AvailableMoves, String
remainder)]
		[(String
"board", String
remainder)]			-> [(ReportObject
Board, String
remainder)]
		[(String
"epd", String
remainder)]			-> [(ReportObject
EPD, String
remainder)]
		[(String
"fen", String
remainder)]			-> [(ReportObject
FEN, String
remainder)]
		[(String
"game", String
remainder)]			-> [(ReportObject
Game, String
remainder)]
		[(String
"maxpositioninstances", String
remainder)]	-> [(ReportObject
MaxPositionInstances, String
remainder)]
		[(String
"moves", String
remainder)]			-> [(ReportObject
Moves, String
remainder)]
		[(String
"pgn", String
remainder)]			-> [(ReportObject
PGN, String
remainder)]
		[(String
"reversibleplycount", String
remainder)]	-> [(ReportObject
ReversiblePlyCount, String
remainder)]
		[(String, String)]
_					-> []	-- No parse.

-- | The constant list of possible values.
range :: [ReportObject]
range :: [ReportObject]
range	= [ReportObject
AvailableMoves, ReportObject
Board, ReportObject
EPD, ReportObject
FEN, ReportObject
Game, ReportObject
MaxPositionInstances, ReportObject
Moves, ReportObject
PGN, ReportObject
ReversiblePlyCount]

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

-- | Replace the first word of the specified string with the name of the object to print, of which it is an unambiguous case-insensitive prefix.
autoComplete :: ShowS
autoComplete :: ShowS
autoComplete	= [String] -> ShowS
Text.AutoComplete.autoComplete [
	String
availableMovesTag,
	String
boardTag,
	String
Property.ExtendedPositionDescription.tag,
	String
fenTag,
	String
gameTag,
	String
maxPositionInstancesTag,
	String
movesTag,
	String
pgnTag,
	String
reversiblePlyCountTag
 ]