{-
	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 fields a user can mutate.
-}

module BishBosh.UI.SetObject (
-- * Types
-- ** Data-types
	SetObject(..),
-- * Functions
	autoComplete,
-- ** Constructors
	mkSearchDepth
 ) where

import qualified	BishBosh.Data.Exception		as Data.Exception
import qualified	BishBosh.Input.SearchOptions	as Input.SearchOptions
import qualified	BishBosh.Text.AutoComplete	as Text.AutoComplete
import qualified	BishBosh.Type.Count		as Type.Count
import qualified	Control.Arrow
import qualified	Control.DeepSeq
import qualified	Control.Exception
import qualified	Data.List.Extra

-- | The fields a user can mutate; currently there's only one.
newtype SetObject	= SearchDepth Type.Count.NPlies	deriving SetObject -> SetObject -> Bool
(SetObject -> SetObject -> Bool)
-> (SetObject -> SetObject -> Bool) -> Eq SetObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetObject -> SetObject -> Bool
$c/= :: SetObject -> SetObject -> Bool
== :: SetObject -> SetObject -> Bool
$c== :: SetObject -> SetObject -> Bool
Eq

instance Control.DeepSeq.NFData SetObject where
	rnf :: SetObject -> ()
rnf (SearchDepth NPlies
searchDepth)		= NPlies -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf NPlies
searchDepth

instance Show SetObject where
	showsPrec :: NPlies -> SetObject -> ShowS
showsPrec NPlies
_ (SearchDepth NPlies
searchDepth)	= String -> ShowS
showString String
Input.SearchOptions.searchDepthTag ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NPlies -> ShowS
forall a. Show a => a -> ShowS
shows NPlies
searchDepth

instance Read SetObject where
	readsPrec :: NPlies -> ReadS SetObject
readsPrec NPlies
_ 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
"searchdepth", String
s')]		-> (Integer -> SetObject) -> (Integer, String) -> (SetObject, String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
Control.Arrow.first (NPlies -> SetObject
mkSearchDepth (NPlies -> SetObject)
-> (Integer -> NPlies) -> Integer -> SetObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> NPlies
forall a. Num a => Integer -> a
fromInteger) ((Integer, String) -> (SetObject, String))
-> [(Integer, String)] -> [(SetObject, String)]
forall a b. (a -> b) -> [a] -> [b]
`map` ReadS Integer
forall a. Read a => ReadS a
reads String
s'
		[(String, String)]
_				-> []	-- No parse.

-- | Smart constructor.
mkSearchDepth :: Type.Count.NPlies -> SetObject
mkSearchDepth :: NPlies -> SetObject
mkSearchDepth NPlies
searchDepth
	| NPlies
searchDepth NPlies -> NPlies -> Bool
forall a. Ord a => a -> a -> Bool
< NPlies
Input.SearchOptions.minimumSearchDepth	= Exception -> SetObject
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> SetObject)
-> (String -> Exception) -> String -> SetObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkOutOfBounds (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.UI.SetObject.mkSearchDepth:\t" (String -> SetObject) -> String -> SetObject
forall a b. (a -> b) -> a -> b
$ String -> ShowS
forall a. Show a => a -> ShowS
shows String
Input.SearchOptions.searchDepthTag String
" must be positive."
	| Bool
otherwise						= NPlies -> SetObject
SearchDepth NPlies
searchDepth

-- | Replace the first word of the specified string with the name of a command of which it is an unambiguous case-insensitive prefix.
autoComplete :: ShowS
autoComplete :: ShowS
autoComplete	= [String] -> ShowS
Text.AutoComplete.autoComplete [String
Input.SearchOptions.searchDepthTag]