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

module BishBosh.UI.PrintObject (
-- * Types
-- ** Data-types
	PrintObject(..),
-- * Constants
	configurationTag,
	helpTag,
	range,
-- * Functions
	autoComplete
 ) where

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.
configurationTag :: String
configurationTag :: String
configurationTag	= String
"configuration"

-- | Input-format.
helpTag :: String
helpTag :: String
helpTag			= String
"help"

-- | A sum-type of objects a user may want to print at runtime.
data PrintObject
	= Configuration
	| Help
	deriving PrintObject -> PrintObject -> Bool
(PrintObject -> PrintObject -> Bool)
-> (PrintObject -> PrintObject -> Bool) -> Eq PrintObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrintObject -> PrintObject -> Bool
$c/= :: PrintObject -> PrintObject -> Bool
== :: PrintObject -> PrintObject -> Bool
$c== :: PrintObject -> PrintObject -> Bool
Eq

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

instance Show PrintObject where
	show :: PrintObject -> String
show PrintObject
Configuration	= String
configurationTag
	show PrintObject
Help		= String
helpTag

instance Read PrintObject where
	readsPrec :: Int -> ReadS PrintObject
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
"configuration", String
remainder)]	-> [(PrintObject
Configuration, String
remainder)]
		[(String
"help", String
remainder)]		-> [(PrintObject
Help, String
remainder)]
		[(String, String)]
_				-> []	-- No parse.

-- | The constant list of possible values.
range :: [PrintObject]
range :: [PrintObject]
range	= [PrintObject
Configuration, PrintObject
Help]

instance Property.FixedMembership.FixedMembership PrintObject where
	members :: [PrintObject]
members	= [PrintObject]
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
configurationTag,
	String
helpTag
 ]