{-# LANGUAGE RankNTypes #-}
module Hoyo.Config (
Config (..)
, defaultConfig
, decodeConfig
, decodeConfigFile
, encodeConfig
, encodeConfigFile
, setConfig
, getKeyVals
) where
import Control.Category ((<<<))
import Control.Monad
import Control.Monad.Catch
import Control.Monad.Except
import Data.Bifunctor (first)
import Data.Maybe (maybeToList)
import qualified Data.Text as T
import Hoyo.Bookmark
import {-# SOURCE #-} Hoyo.CLI.Parse
import Hoyo.Internal.Types
import Hoyo.Utils
import Lens.Micro
import Lens.Micro.Extras
import Options.Applicative
import qualified Toml
import Toml (TomlCodec, (.=))
configCodec :: TomlCodec Config
configCodec :: TomlCodec Config
configCodec = ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
-> Codec Config (ConfigValue 'TBool)
-> Codec
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Bool -> ConfigValue 'TBool
BoolV (Bool -> ConfigValue 'TBool)
-> Codec Bool Bool -> Codec Bool (ConfigValue 'TBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> Codec Bool Bool
Toml.bool Key
"fail_on_error") Codec Bool (ConfigValue 'TBool)
-> (Config -> Bool) -> Codec Config (ConfigValue 'TBool)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting Bool Config Bool -> Config -> Bool
forall a s. Getting a s a -> s -> a
view Getting Bool Config Bool
Lens' Config Bool
failOnError
Codec
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
-> Codec Config (ConfigValue 'TBool)
-> Codec
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> ConfigValue 'TBool
BoolV (Bool -> ConfigValue 'TBool)
-> Codec Bool Bool -> Codec Bool (ConfigValue 'TBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> Codec Bool Bool
Toml.bool Key
"display_creation_time") Codec Bool (ConfigValue 'TBool)
-> (Config -> Bool) -> Codec Config (ConfigValue 'TBool)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting Bool Config Bool -> Config -> Bool
forall a s. Getting a s a -> s -> a
view Getting Bool Config Bool
Lens' Config Bool
displayCreationTime
Codec
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
-> Codec Config (ConfigValue 'TBool)
-> Codec
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> ConfigValue 'TBool
BoolV (Bool -> ConfigValue 'TBool)
-> Codec Bool Bool -> Codec Bool (ConfigValue 'TBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> Codec Bool Bool
Toml.bool Key
"enable_clearing") Codec Bool (ConfigValue 'TBool)
-> (Config -> Bool) -> Codec Config (ConfigValue 'TBool)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting Bool Config Bool -> Config -> Bool
forall a s. Getting a s a -> s -> a
view Getting Bool Config Bool
Lens' Config Bool
enableClearing
Codec
Config
(ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
-> Codec Config (ConfigValue 'TBool)
-> Codec
Config
(ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> ConfigValue 'TBool
BoolV (Bool -> ConfigValue 'TBool)
-> Codec Bool Bool -> Codec Bool (ConfigValue 'TBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> Codec Bool Bool
Toml.bool Key
"enable_reset") Codec Bool (ConfigValue 'TBool)
-> (Config -> Bool) -> Codec Config (ConfigValue 'TBool)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting Bool Config Bool -> Config -> Bool
forall a s. Getting a s a -> s -> a
view Getting Bool Config Bool
Lens' Config Bool
enableReset
Codec
Config
(ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config)
-> Codec Config (ConfigValue 'TBool)
-> Codec
Config
(ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand) -> Config)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> ConfigValue 'TBool
BoolV (Bool -> ConfigValue 'TBool)
-> Codec Bool Bool -> Codec Bool (ConfigValue 'TBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> Codec Bool Bool
Toml.bool Key
"backup_before_clear") Codec Bool (ConfigValue 'TBool)
-> (Config -> Bool) -> Codec Config (ConfigValue 'TBool)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting Bool Config Bool -> Config -> Bool
forall a s. Getting a s a -> s -> a
view Getting Bool Config Bool
Lens' Config Bool
backupBeforeClear
Codec
Config
(ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand) -> Config)
-> Codec Config (ConfigValue ('TList 'TDefaultBookmark))
-> Codec Config (ConfigValue ('TMaybe 'TCommand) -> Config)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([ConfigValue 'TDefaultBookmark]
-> ConfigValue ('TList 'TDefaultBookmark)
forall (a :: ConfigValueType).
[ConfigValue a] -> ConfigValue ('TList a)
ListOfV ([ConfigValue 'TDefaultBookmark]
-> ConfigValue ('TList 'TDefaultBookmark))
-> ([DefaultBookmark] -> [ConfigValue 'TDefaultBookmark])
-> [DefaultBookmark]
-> ConfigValue ('TList 'TDefaultBookmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DefaultBookmark -> ConfigValue 'TDefaultBookmark)
-> [DefaultBookmark] -> [ConfigValue 'TDefaultBookmark]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DefaultBookmark -> ConfigValue 'TDefaultBookmark
DefaultBookmarkV ([DefaultBookmark] -> ConfigValue ('TList 'TDefaultBookmark))
-> Codec [DefaultBookmark] [DefaultBookmark]
-> Codec [DefaultBookmark] (ConfigValue ('TList 'TDefaultBookmark))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TomlCodec DefaultBookmark
-> Key -> Codec [DefaultBookmark] [DefaultBookmark]
forall a. TomlCodec a -> Key -> TomlCodec [a]
Toml.list TomlCodec DefaultBookmark
defaultBookmarkCodec Key
"default_bookmark") Codec [DefaultBookmark] (ConfigValue ('TList 'TDefaultBookmark))
-> (Config -> [DefaultBookmark])
-> Codec Config (ConfigValue ('TList 'TDefaultBookmark))
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting [DefaultBookmark] Config [DefaultBookmark]
-> Config -> [DefaultBookmark]
forall a s. Getting a s a -> s -> a
view Getting [DefaultBookmark] Config [DefaultBookmark]
Lens' Config [DefaultBookmark]
defaultBookmarks
Codec Config (ConfigValue ('TMaybe 'TCommand) -> Config)
-> Codec Config (ConfigValue ('TMaybe 'TCommand))
-> TomlCodec Config
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe (ConfigValue 'TCommand) -> ConfigValue ('TMaybe 'TCommand)
forall (a :: ConfigValueType).
Maybe (ConfigValue a) -> ConfigValue ('TMaybe a)
MaybeV (Maybe (ConfigValue 'TCommand) -> ConfigValue ('TMaybe 'TCommand))
-> (Maybe Command -> Maybe (ConfigValue 'TCommand))
-> Maybe Command
-> ConfigValue ('TMaybe 'TCommand)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Command -> ConfigValue 'TCommand)
-> Maybe Command -> Maybe (ConfigValue 'TCommand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Command -> ConfigValue 'TCommand
CommandV (Maybe Command -> ConfigValue ('TMaybe 'TCommand))
-> Codec (Maybe Command) (Maybe Command)
-> Codec (Maybe Command) (ConfigValue ('TMaybe 'TCommand))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TomlCodec Command -> Codec (Maybe Command) (Maybe Command)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Command
commandCodec Key
"default_command")) Codec (Maybe Command) (ConfigValue ('TMaybe 'TCommand))
-> (Config -> Maybe Command)
-> Codec Config (ConfigValue ('TMaybe 'TCommand))
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Getting (Maybe Command) Config (Maybe Command)
-> Config -> Maybe Command
forall a s. Getting a s a -> s -> a
view Getting (Maybe Command) Config (Maybe Command)
Lens' Config (Maybe Command)
defaultCommand
commandCodec :: Toml.Key -> TomlCodec Command
commandCodec :: Key -> TomlCodec Command
commandCodec = TomlBiMap Command AnyValue -> Key -> TomlCodec Command
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
Toml.match (TomlBiMap Text AnyValue
Toml._Text TomlBiMap Text AnyValue
-> BiMap TomlBiMapError Command Text -> TomlBiMap Command AnyValue
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
<<< BiMap TomlBiMapError Text Command
-> BiMap TomlBiMapError Command Text
forall e a b. BiMap e a b -> BiMap e b a
Toml.invert ((Command -> Text)
-> (Text -> Either TomlBiMapError Command)
-> BiMap TomlBiMapError Text Command
forall field object error.
(field -> object)
-> (object -> Either error field) -> BiMap error object field
Toml.prism Command -> Text
fmt Text -> Either TomlBiMapError Command
prs))
where
fmt :: Command -> T.Text
fmt :: Command -> Text
fmt = [Text] -> Text
formatArgs ([Text] -> Text) -> (Command -> [Text]) -> Command -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Command -> [Text]
formatCommand
prs :: T.Text -> Either Toml.TomlBiMapError Command
prs :: Text -> Either TomlBiMapError Command
prs Text
t = case ParserPrefs
-> ParserInfo Command -> [String] -> ParserResult Command
forall a. ParserPrefs -> ParserInfo a -> [String] -> ParserResult a
execParserPure ParserPrefs
defaultPrefs (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser Command
parseCommand InfoMod Command
forall a. Monoid a => a
mempty) (Text -> [String]
splitArgs Text
t) of
Success Command
cmd -> Command -> Either TomlBiMapError Command
forall a b. b -> Either a b
Right Command
cmd
Failure ParserFailure ParserHelp
err -> do let (String
msg, ExitCode
_) = ParserFailure ParserHelp -> String -> (String, ExitCode)
renderFailure ParserFailure ParserHelp
err String
"hoyo"
TomlBiMapError -> Either TomlBiMapError Command
forall a b. a -> Either a b
Left (Text -> TomlBiMapError
Toml.ArbitraryError (Text -> TomlBiMapError) -> Text -> TomlBiMapError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
msg)
CompletionInvoked CompletionResult
res -> TomlBiMapError -> Either TomlBiMapError Command
forall a b. a -> Either a b
Left (Text -> TomlBiMapError
Toml.ArbitraryError (Text -> TomlBiMapError) -> Text -> TomlBiMapError
forall a b. (a -> b) -> a -> b
$ CompletionResult -> Text
forall a. Show a => a -> Text
tshow CompletionResult
res)
defaultConfig :: Config
defaultConfig :: Config
defaultConfig = Config :: ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue 'TBool
-> ConfigValue ('TList 'TDefaultBookmark)
-> ConfigValue ('TMaybe 'TCommand)
-> Config
Config {
_failOnError :: ConfigValue 'TBool
_failOnError = Bool -> ConfigValue 'TBool
BoolV Bool
False
, _displayCreationTime :: ConfigValue 'TBool
_displayCreationTime = Bool -> ConfigValue 'TBool
BoolV Bool
False
, _enableClearing :: ConfigValue 'TBool
_enableClearing = Bool -> ConfigValue 'TBool
BoolV Bool
False
, _enableReset :: ConfigValue 'TBool
_enableReset = Bool -> ConfigValue 'TBool
BoolV Bool
False
, _backupBeforeClear :: ConfigValue 'TBool
_backupBeforeClear = Bool -> ConfigValue 'TBool
BoolV Bool
False
, _defaultBookmarks :: ConfigValue ('TList 'TDefaultBookmark)
_defaultBookmarks = [ConfigValue 'TDefaultBookmark]
-> ConfigValue ('TList 'TDefaultBookmark)
forall (a :: ConfigValueType).
[ConfigValue a] -> ConfigValue ('TList a)
ListOfV []
, _defaultCommand :: ConfigValue ('TMaybe 'TCommand)
_defaultCommand = Maybe (ConfigValue 'TCommand) -> ConfigValue ('TMaybe 'TCommand)
forall (a :: ConfigValueType).
Maybe (ConfigValue a) -> ConfigValue ('TMaybe a)
MaybeV Maybe (ConfigValue 'TCommand)
forall a. Maybe a
Nothing
}
decodeConfig :: T.Text -> Either HoyoException Config
decodeConfig :: Text -> Either HoyoException Config
decodeConfig = ([TomlDecodeError] -> HoyoException)
-> Either [TomlDecodeError] Config -> Either HoyoException Config
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ([Text] -> HoyoException
ParseException ([Text] -> HoyoException)
-> ([TomlDecodeError] -> [Text])
-> [TomlDecodeError]
-> HoyoException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> [Text])
-> ([TomlDecodeError] -> Text) -> [TomlDecodeError] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TomlDecodeError] -> Text
Toml.prettyTomlDecodeErrors)
(Either [TomlDecodeError] Config -> Either HoyoException Config)
-> (Text -> Either [TomlDecodeError] Config)
-> Text
-> Either HoyoException Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlCodec Config -> Text -> Either [TomlDecodeError] Config
forall a. TomlCodec a -> Text -> Either [TomlDecodeError] a
Toml.decodeExact TomlCodec Config
configCodec
decodeConfigFile :: (MonadIO m, MonadCatch m) => FilePath -> m (Either HoyoException Config)
decodeConfigFile :: String -> m (Either HoyoException Config)
decodeConfigFile = (IOException -> m (Either HoyoException Config))
-> m (Either HoyoException Config)
-> m (Either HoyoException Config)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
handle IOException -> m (Either HoyoException Config)
forall (m :: * -> *) a.
Monad m =>
IOException -> m (Either HoyoException a)
catchIOException
(m (Either HoyoException Config)
-> m (Either HoyoException Config))
-> (String -> m (Either HoyoException Config))
-> String
-> m (Either HoyoException Config)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either [TomlDecodeError] Config -> Either HoyoException Config)
-> m (Either [TomlDecodeError] Config)
-> m (Either HoyoException Config)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([TomlDecodeError] -> HoyoException)
-> Either [TomlDecodeError] Config -> Either HoyoException Config
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ([Text] -> HoyoException
ParseException ([Text] -> HoyoException)
-> ([TomlDecodeError] -> [Text])
-> [TomlDecodeError]
-> HoyoException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> [Text])
-> ([TomlDecodeError] -> Text) -> [TomlDecodeError] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TomlDecodeError] -> Text
Toml.prettyTomlDecodeErrors))
(m (Either [TomlDecodeError] Config)
-> m (Either HoyoException Config))
-> (String -> m (Either [TomlDecodeError] Config))
-> String
-> m (Either HoyoException Config)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlCodec Config -> String -> m (Either [TomlDecodeError] Config)
forall a (m :: * -> *).
MonadIO m =>
TomlCodec a -> String -> m (Either [TomlDecodeError] a)
Toml.decodeFileExact TomlCodec Config
configCodec
encodeConfig :: Config -> T.Text
encodeConfig :: Config -> Text
encodeConfig = TomlCodec Config -> Config -> Text
forall a. TomlCodec a -> a -> Text
Toml.encode TomlCodec Config
configCodec
encodeConfigFile :: (MonadIO m, MonadCatch m) => FilePath -> Config -> m (Either HoyoException ())
encodeConfigFile :: String -> Config -> m (Either HoyoException ())
encodeConfigFile String
fp = (IOException -> m (Either HoyoException ()))
-> m (Either HoyoException ()) -> m (Either HoyoException ())
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
handle IOException -> m (Either HoyoException ())
forall (m :: * -> *) a.
Monad m =>
IOException -> m (Either HoyoException a)
catchIOException (m (Either HoyoException ()) -> m (Either HoyoException ()))
-> (Config -> m (Either HoyoException ()))
-> Config
-> m (Either HoyoException ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (() -> Either HoyoException ())
-> m () -> m (Either HoyoException ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap () -> Either HoyoException ()
forall a b. b -> Either a b
Right (m () -> m (Either HoyoException ()))
-> (Config -> m ()) -> Config -> m (Either HoyoException ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m Text -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m Text -> m ()) -> (Config -> m Text) -> Config -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlCodec Config -> String -> Config -> m Text
forall a (m :: * -> *).
MonadIO m =>
TomlCodec a -> String -> a -> m Text
Toml.encodeToFile TomlCodec Config
configCodec String
fp
getKeyVals :: Config -> [(T.Text, AnyConfigValue)]
getKeyVals :: Config -> [(Text, AnyConfigValue)]
getKeyVals Config
cfg = [
(Text
"fail_on_error", ConfigValue 'TBool -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue 'TBool -> AnyConfigValue)
-> ConfigValue 'TBool -> AnyConfigValue
forall a b. (a -> b) -> a -> b
$ Config -> ConfigValue 'TBool
_failOnError Config
cfg)
, (Text
"display_creation_time", ConfigValue 'TBool -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue 'TBool -> AnyConfigValue)
-> ConfigValue 'TBool -> AnyConfigValue
forall a b. (a -> b) -> a -> b
$ Config -> ConfigValue 'TBool
_displayCreationTime Config
cfg)
, (Text
"enable_clearing", ConfigValue 'TBool -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue 'TBool -> AnyConfigValue)
-> ConfigValue 'TBool -> AnyConfigValue
forall a b. (a -> b) -> a -> b
$ Config -> ConfigValue 'TBool
_enableClearing Config
cfg)
, (Text
"enable_reset", ConfigValue 'TBool -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue 'TBool -> AnyConfigValue)
-> ConfigValue 'TBool -> AnyConfigValue
forall a b. (a -> b) -> a -> b
$ Config -> ConfigValue 'TBool
_enableReset Config
cfg)
, (Text
"backup_before_clear", ConfigValue 'TBool -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue 'TBool -> AnyConfigValue)
-> ConfigValue 'TBool -> AnyConfigValue
forall a b. (a -> b) -> a -> b
$ Config -> ConfigValue 'TBool
_backupBeforeClear Config
cfg)
] [(Text, AnyConfigValue)]
-> [(Text, AnyConfigValue)] -> [(Text, AnyConfigValue)]
forall a. Semigroup a => a -> a -> a
<> Maybe (Text, AnyConfigValue) -> [(Text, AnyConfigValue)]
forall a. Maybe a -> [a]
maybeToList ((Text
"default_command", ) (AnyConfigValue -> (Text, AnyConfigValue))
-> (ConfigValue 'TCommand -> AnyConfigValue)
-> ConfigValue 'TCommand
-> (Text, AnyConfigValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigValue 'TCommand -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue 'TCommand -> (Text, AnyConfigValue))
-> Maybe (ConfigValue 'TCommand) -> Maybe (Text, AnyConfigValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting
(Maybe (ConfigValue 'TCommand))
Config
(Maybe (ConfigValue 'TCommand))
-> Config -> Maybe (ConfigValue 'TCommand)
forall a s. Getting a s a -> s -> a
view ((ConfigValue ('TMaybe 'TCommand)
-> Const
(Maybe (ConfigValue 'TCommand)) (ConfigValue ('TMaybe 'TCommand)))
-> Config -> Const (Maybe (ConfigValue 'TCommand)) Config
Lens' Config (ConfigValue ('TMaybe 'TCommand))
__defaultCommand ((ConfigValue ('TMaybe 'TCommand)
-> Const
(Maybe (ConfigValue 'TCommand)) (ConfigValue ('TMaybe 'TCommand)))
-> Config -> Const (Maybe (ConfigValue 'TCommand)) Config)
-> ((Maybe (ConfigValue 'TCommand)
-> Const
(Maybe (ConfigValue 'TCommand)) (Maybe (ConfigValue 'TCommand)))
-> ConfigValue ('TMaybe 'TCommand)
-> Const
(Maybe (ConfigValue 'TCommand)) (ConfigValue ('TMaybe 'TCommand)))
-> Getting
(Maybe (ConfigValue 'TCommand))
Config
(Maybe (ConfigValue 'TCommand))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (ConfigValue 'TCommand)
-> Const
(Maybe (ConfigValue 'TCommand)) (Maybe (ConfigValue 'TCommand)))
-> ConfigValue ('TMaybe 'TCommand)
-> Const
(Maybe (ConfigValue 'TCommand)) (ConfigValue ('TMaybe 'TCommand))
forall (t :: ConfigValueType).
Lens' (ConfigValue ('TMaybe t)) (Maybe (ConfigValue t))
cfgMaybe) Config
cfg)
[(Text, AnyConfigValue)]
-> [(Text, AnyConfigValue)] -> [(Text, AnyConfigValue)]
forall a. Semigroup a => a -> a -> a
<> [(Text
"default_bookmarks", ConfigValue ('TList 'TDefaultBookmark) -> AnyConfigValue
forall (t :: ConfigValueType). ConfigValue t -> AnyConfigValue
AnyConfigValue (ConfigValue ('TList 'TDefaultBookmark) -> AnyConfigValue)
-> ConfigValue ('TList 'TDefaultBookmark) -> AnyConfigValue
forall a b. (a -> b) -> a -> b
$ Config -> ConfigValue ('TList 'TDefaultBookmark)
_defaultBookmarks Config
cfg)]
setConfig :: MonadError HoyoException m => T.Text -> T.Text -> Config -> m Config
setConfig :: Text -> Text -> Config -> m Config
setConfig Text
"fail_on_error" Text
val Config
cfg = (Bool -> Config -> Config) -> Config -> Bool -> Config
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ASetter Config Config Bool Bool -> Bool -> Config -> Config
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Config Config Bool Bool
Lens' Config Bool
failOnError) Config
cfg
(Bool -> Config) -> m Bool -> m Config
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either HoyoException Bool -> m Bool
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Text -> Either HoyoException Bool
forall (m :: * -> *). MonadError HoyoException m => Text -> m Bool
readBool Text
val)
setConfig Text
"display_creation_time" Text
val Config
cfg = (Bool -> Config -> Config) -> Config -> Bool -> Config
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ASetter Config Config Bool Bool -> Bool -> Config -> Config
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Config Config Bool Bool
Lens' Config Bool
displayCreationTime) Config
cfg
(Bool -> Config) -> m Bool -> m Config
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either HoyoException Bool -> m Bool
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Text -> Either HoyoException Bool
forall (m :: * -> *). MonadError HoyoException m => Text -> m Bool
readBool Text
val)
setConfig Text
"enable_clearing" Text
val Config
cfg = (Bool -> Config -> Config) -> Config -> Bool -> Config
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ASetter Config Config Bool Bool -> Bool -> Config -> Config
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Config Config Bool Bool
Lens' Config Bool
enableClearing) Config
cfg
(Bool -> Config) -> m Bool -> m Config
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either HoyoException Bool -> m Bool
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Text -> Either HoyoException Bool
forall (m :: * -> *). MonadError HoyoException m => Text -> m Bool
readBool Text
val)
setConfig Text
"enable_reset" Text
val Config
cfg = (Bool -> Config -> Config) -> Config -> Bool -> Config
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ASetter Config Config Bool Bool -> Bool -> Config -> Config
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Config Config Bool Bool
Lens' Config Bool
enableReset) Config
cfg
(Bool -> Config) -> m Bool -> m Config
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either HoyoException Bool -> m Bool
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Text -> Either HoyoException Bool
forall (m :: * -> *). MonadError HoyoException m => Text -> m Bool
readBool Text
val)
setConfig Text
"backup_before_clear" Text
val Config
cfg = (Bool -> Config -> Config) -> Config -> Bool -> Config
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ASetter Config Config Bool Bool -> Bool -> Config -> Config
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Config Config Bool Bool
Lens' Config Bool
backupBeforeClear) Config
cfg
(Bool -> Config) -> m Bool -> m Config
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either HoyoException Bool -> m Bool
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Text -> Either HoyoException Bool
forall (m :: * -> *). MonadError HoyoException m => Text -> m Bool
readBool Text
val)
setConfig Text
key Text
_ Config
_ = HoyoException -> m Config
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (HoyoException -> m Config) -> HoyoException -> m Config
forall a b. (a -> b) -> a -> b
$ [Text] -> HoyoException
ConfigException [Text
"Invalid key: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key]