2021-10-15 20:24:23 +00:00
{- # LANGUAGE CPP # -}
{- # LANGUAGE DataKinds # -}
{- # LANGUAGE TypeApplications # -}
{- # LANGUAGE FlexibleContexts # -}
{- # LANGUAGE TemplateHaskell # -}
{- # LANGUAGE QuasiQuotes # -}
{- # LANGUAGE OverloadedStrings # -}
{- # LANGUAGE DuplicateRecordFields # -}
{- # LANGUAGE RankNTypes # -}
module GHCup.OptParse.Config where
import GHCup.Errors
import GHCup.Types
import GHCup.Utils
2022-05-21 20:54:18 +00:00
import GHCup.Prelude
import GHCup.Prelude.Logger
import GHCup.Prelude.String.QQ
2022-03-10 19:26:51 +00:00
import GHCup.OptParse.Common
2021-10-15 20:24:23 +00:00
# if ! MIN_VERSION_base ( 4 , 13 , 0 )
import Control.Monad.Fail ( MonadFail )
# endif
2021-10-21 21:17:26 +00:00
import Control.Exception ( displayException )
2021-10-15 20:24:23 +00:00
import Control.Monad.Reader
import Control.Monad.Trans.Resource
import Data.Functor
import Data.Maybe
import Haskus.Utils.Variant.Excepts
2022-03-10 19:26:51 +00:00
import Options.Applicative hiding ( style , ParseError )
2021-10-19 18:38:53 +00:00
import Options.Applicative.Help.Pretty ( text )
2021-10-15 20:24:23 +00:00
import Prelude hiding ( appendFile )
import System.Exit
import qualified Data.Text as T
import qualified Data.ByteString.UTF8 as UTF8
2021-10-21 21:17:26 +00:00
import qualified Data.Yaml.Aeson as Y
2021-10-15 20:24:23 +00:00
import Control.Exception.Safe ( MonadMask )
----------------
--[ Commands ]--
----------------
data ConfigCommand
= ShowConfig
2021-10-19 18:38:53 +00:00
| SetConfig String ( Maybe String )
2021-10-15 20:24:23 +00:00
| InitConfig
2023-10-24 16:35:41 +00:00
| AddReleaseChannel Bool NewURLSource
2023-07-22 09:46:23 +00:00
deriving ( Eq , Show )
2021-10-15 20:24:23 +00:00
---------------
--[ Parsers ]--
---------------
2023-02-08 16:04:36 +00:00
2021-10-15 20:24:23 +00:00
configP :: Parser ConfigCommand
configP = subparser
( command " init " initP
<> command " set " setP -- [set] KEY VALUE at help lhs
<> command " show " showP
2022-03-10 19:26:51 +00:00
<> command " add-release-channel " addP
2021-10-15 20:24:23 +00:00
)
<|> pure ShowConfig
where
initP = info ( pure InitConfig ) ( progDesc " Write default config to ~/.ghcup/config.yaml " )
showP = info ( pure ShowConfig ) ( progDesc " Show current config (default) " )
2021-10-19 18:38:53 +00:00
setP = info argsP ( progDesc " Set config KEY to VALUE (or specify as single json value) " <> footerDoc ( Just $ text configSetFooter ) )
argsP = SetConfig <$> argument str ( metavar " <JSON_VALUE | YAML_KEY> " ) <*> optional ( argument str ( metavar " YAML_VALUE " ) )
2023-10-24 16:35:41 +00:00
addP = info ( AddReleaseChannel <$> switch ( long " force " <> help " Delete existing entry (if any) and append instead of failing " ) <*> argument ( eitherReader parseNewUrlSource ) ( metavar " URL_SOURCE " <> completer urlSourceCompleter ) )
( progDesc " Add a release channel, e.g. from a URI " )
2021-10-15 20:24:23 +00:00
--------------
--[ Footer ]--
--------------
configFooter :: String
configFooter = [ s | Examples :
# show current config
ghcup config
# initialize config
ghcup config init
# set < key > < value > configuration pair
2021-10-19 18:38:53 +00:00
ghcup config set < key > < value >| ]
configSetFooter :: String
configSetFooter = [ s | Examples :
# disable caching
ghcup config set cache false
# switch downloader to wget
ghcup config set downloader Wget
# set mirror for ghcup metadata
ghcup config set ' { u r l - s o u r c e : { O w n S o u r c e : " < u r l > " } }' | ]
2021-10-15 20:24:23 +00:00
-----------------
--[ Utilities ]--
-----------------
formatConfig :: UserSettings -> String
2021-10-21 21:17:26 +00:00
formatConfig = UTF8 . toString . Y . encode
2021-10-15 20:24:23 +00:00
2023-02-08 16:04:36 +00:00
updateSettings :: UserSettings -> UserSettings -> UserSettings
updateSettings usl usr =
let cache' = uCache usl <|> uCache usr
metaCache' = uMetaCache usl <|> uMetaCache usr
metaMode' = uMetaMode usl <|> uMetaMode usr
noVerify' = uNoVerify usl <|> uNoVerify usr
verbose' = uVerbose usl <|> uVerbose usr
keepDirs' = uKeepDirs usl <|> uKeepDirs usr
downloader' = uDownloader usl <|> uDownloader usr
urlSource' = uUrlSource usl <|> uUrlSource usr
noNetwork' = uNoNetwork usl <|> uNoNetwork usr
gpgSetting' = uGPGSetting usl <|> uGPGSetting usr
platformOverride' = uPlatformOverride usl <|> uPlatformOverride usr
mirrors' = uMirrors usl <|> uMirrors usr
2023-10-24 16:35:41 +00:00
in UserSettings cache' metaCache' metaMode' noVerify' verbose' keepDirs' downloader' ( updateKeyBindings ( uKeyBindings usl ) ( uKeyBindings usr ) ) urlSource' noNetwork' gpgSetting' platformOverride' mirrors'
2023-02-08 16:04:36 +00:00
where
updateKeyBindings :: Maybe UserKeyBindings -> Maybe UserKeyBindings -> Maybe UserKeyBindings
updateKeyBindings Nothing Nothing = Nothing
updateKeyBindings ( Just kbl ) Nothing = Just kbl
updateKeyBindings Nothing ( Just kbr ) = Just kbr
updateKeyBindings ( Just kbl ) ( Just kbr ) =
Just $ UserKeyBindings {
kUp = kUp kbl <|> kUp kbr
, kDown = kDown kbl <|> kDown kbr
, kQuit = kQuit kbl <|> kQuit kbr
, kInstall = kInstall kbl <|> kInstall kbr
, kUninstall = kUninstall kbl <|> kUninstall kbr
, kSet = kSet kbl <|> kSet kbr
, kChangelog = kChangelog kbl <|> kChangelog kbr
, kShowAll = kShowAll kbl <|> kShowAll kbr
}
2021-10-15 20:24:23 +00:00
------------------
--[ Entrypoint ]--
------------------
2023-02-19 09:25:14 +00:00
data Duplicate = Duplicate -- ^ there is a duplicate somewhere in the middle
| NoDuplicate -- ^ there is no duplicate
| DuplicateLast -- ^ there's a duplicate, but it's the last element
2021-10-15 20:24:23 +00:00
2022-03-10 19:26:51 +00:00
config :: forall m . ( Monad m
2021-10-15 20:24:23 +00:00
, MonadMask m
, MonadUnliftIO m
, MonadFail m
)
=> ConfigCommand
-> Settings
2023-02-08 16:04:36 +00:00
-> UserSettings
2021-10-15 20:24:23 +00:00
-> KeyBindings
-> ( ReaderT LeanAppState m () -> m () )
-> m ExitCode
2023-02-08 16:04:36 +00:00
config configCommand settings userConf keybindings runLogger = case configCommand of
2021-10-15 20:24:23 +00:00
InitConfig -> do
path <- getConfigFilePath
liftIO $ writeFile path $ formatConfig $ fromSettings settings ( Just keybindings )
runLogger $ logDebug $ " config.yaml initialized at " <> T . pack path
pure ExitSuccess
ShowConfig -> do
liftIO $ putStrLn $ formatConfig $ fromSettings settings ( Just keybindings )
pure ExitSuccess
2022-03-10 19:26:51 +00:00
( SetConfig k mv ) -> do
r <- runE @ '[JSONError, ParseError] $ do
case mv of
Just " " ->
throwE $ ParseError " Empty values are not allowed "
Nothing -> do
usersettings <- decodeSettings k
2023-11-12 08:49:06 +00:00
when ( usersettings == defaultUserSettings )
$ throwE $ ParseError ( " Failed to parse setting (maybe typo?): " <> k )
2022-03-10 19:26:51 +00:00
lift $ doConfig usersettings
pure ()
Just v -> do
usersettings <- decodeSettings ( k <> " : " <> v <> " \ n " )
2023-11-12 08:49:06 +00:00
when ( usersettings == defaultUserSettings )
$ throwE $ ParseError ( " Failed to parse key ' " <> k <> " ' with value ' " <> v <> " ' as user setting. Maybe typo? " )
2022-03-10 19:26:51 +00:00
lift $ doConfig usersettings
pure ()
case r of
VRight _ -> pure ExitSuccess
VLeft ( V ( JSONDecodeError e ) ) -> do
runLogger $ logError $ " Error decoding config: " <> T . pack e
pure $ ExitFailure 65
2023-11-12 08:49:06 +00:00
VLeft e -> do
runLogger ( logError $ T . pack $ prettyHFError e )
pure $ ExitFailure 65
2022-03-10 19:26:51 +00:00
2023-10-24 16:35:41 +00:00
AddReleaseChannel force new -> do
2023-02-12 11:58:08 +00:00
r <- runE @ '[DuplicateReleaseChannel] $ do
2023-10-24 16:35:41 +00:00
let oldSources = fromURLSource ( urlSource settings )
let merged = oldSources ++ [ new ]
case checkDuplicate oldSources new of
Duplicate
| not force -> throwE ( DuplicateReleaseChannel new )
DuplicateLast -> pure ()
_ -> lift $ doConfig ( defaultUserSettings { uUrlSource = Just $ SimpleList merged } )
2023-02-12 11:58:08 +00:00
case r of
VRight _ -> do
2022-12-19 16:57:56 +00:00
pure ExitSuccess
2023-02-12 11:58:08 +00:00
VLeft e -> do
runLogger $ logError $ T . pack $ prettyHFError e
pure $ ExitFailure 15
2021-10-19 18:38:53 +00:00
where
2023-02-19 09:25:14 +00:00
checkDuplicate :: Eq a => [ a ] -> a -> Duplicate
checkDuplicate xs a
| last xs == a = DuplicateLast
| a ` elem ` xs = Duplicate
| otherwise = NoDuplicate
2022-03-10 19:26:51 +00:00
doConfig :: MonadIO m => UserSettings -> m ()
doConfig usersettings = do
2023-02-08 16:04:36 +00:00
let settings' = updateSettings usersettings userConf
2022-03-10 19:26:51 +00:00
path <- liftIO getConfigFilePath
2023-02-08 16:04:36 +00:00
liftIO $ writeFile path $ formatConfig $ settings'
2022-03-10 19:26:51 +00:00
runLogger $ logDebug $ T . pack $ show settings'
pure ()
decodeSettings = lE' ( JSONDecodeError . displayException ) . Y . decodeEither' . UTF8 . fromString