git-annex/Command/Config.hs
Joey Hess fcf5d11c63
add "input" field to json output
The use case of this field is mostly to support -J combined with --json.
When that is implemented, a user will be able to look at the field to
determine which of the requests they have sent it corresponds to.

The field typically has a single value in its list, but in some cases
mutliple values (eg 2 command-line params) are combined together and the
list will have more.

Note that json parsing was already non-strict, so old git-annex metadata
--json --batch can be fed json produced by the new git-annex and will
not stumble over the new field.
2020-09-15 16:22:44 -04:00

92 lines
2.4 KiB
Haskell

{- git-annex command
-
- Copyright 2017-2020 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings #-}
module Command.Config where
import Command
import Logs.Config
import Config
import Types.GitConfig (globalConfigs)
import Git.Types (fromConfigValue)
import qualified Data.ByteString.Char8 as S8
cmd :: Command
cmd = noMessages $ command "config" SectionSetup
"configuration stored in git-annex branch"
paramNothing (seek <$$> optParser)
data Action
= SetConfig ConfigKey ConfigValue
| GetConfig ConfigKey
| UnsetConfig ConfigKey
type Name = String
type Value = String
optParser :: CmdParamsDesc -> Parser Action
optParser _ = setconfig <|> getconfig <|> unsetconfig
where
setconfig = SetConfig
<$> strOption
( long "set"
<> help "set configuration"
<> metavar paramName
)
<*> strArgument
( metavar paramValue
)
getconfig = GetConfig <$> strOption
( long "get"
<> help "get configuration"
<> metavar paramName
)
unsetconfig = UnsetConfig <$> strOption
( long "unset"
<> help "unset configuration"
<> metavar paramName
)
seek :: Action -> CommandSeek
seek (SetConfig ck@(ConfigKey name) val) = checkIsGlobalConfig ck $ commandAction $
startingUsualMessages (decodeBS' name) ai si $ do
setGlobalConfig ck val
when (needLocalUpdate ck) $
setConfig ck (fromConfigValue val)
next $ return True
where
ai = ActionItemOther (Just (fromConfigValue val))
si = SeekInput [decodeBS' name]
seek (UnsetConfig ck@(ConfigKey name)) = checkIsGlobalConfig ck $ commandAction $
startingUsualMessages (decodeBS' name) ai si $ do
unsetGlobalConfig ck
when (needLocalUpdate ck) $
unsetConfig ck
next $ return True
where
ai = ActionItemOther (Just "unset")
si = SeekInput [decodeBS' name]
seek (GetConfig ck) = checkIsGlobalConfig ck $ commandAction $
startingCustomOutput ai $ do
getGlobalConfig ck >>= \case
Just (ConfigValue v) -> liftIO $ S8.putStrLn v
Just NoConfigValue -> return ()
Nothing -> return ()
next $ return True
where
ai = ActionItemOther Nothing
checkIsGlobalConfig :: ConfigKey -> Annex a -> Annex a
checkIsGlobalConfig ck@(ConfigKey name) a
| elem ck globalConfigs = a
| otherwise = giveup $ decodeBS name ++ " is not a configuration setting that can be stored in the git-annex branch"
needLocalUpdate :: ConfigKey -> Bool
needLocalUpdate (ConfigKey "annex.securehashesonly") = True
needLocalUpdate _ = False