config: Added the --show-origin and --for-file options
* config: Added the --show-origin and --for-file options. * config: Support annex.numcopies and annex.mincopies. There is a little bit of redundancy here with other code elsewhere that combines the various configs and selects which to use. But really only for the special case of annex.numcopies, which is a git config that does not override the annex branch setting and for annex.mincopies, which does not have a git config but does have gitattributes settings as well as the annex branch setting. That seems small enough, and unlikely enough to grow into a mess that it was worth supporting annex.numcopies and annex.mincopies in git-annex config --show-origin. Because these settings are a prime thing that someone might get confused about and want to know where they were configured. And, it followed that git-annex config might as well support those two for --set and --get as well. While this is redundant with the speclialized commands, it's only a little code and it makes it more consistent. Note that --set does not have as nice output as numcopies/mincopies commands in some special cases like setting to 0 or a negative number. It does avoid setting to a bad value thanks to the smart constructors (eg configuredNumCopies). As for other git-annex branch configurations that are not set by git-annex config, things like trust and wanted that are specific to a repository don't map to a git config name, so don't really fit into git-annex config. And they are only configured in the git-annex branch with no local override (at least so far), so --show-origin would not be useful for them. Sponsored-by: Dartmouth College's DANDI project
This commit is contained in:
parent
ae98fb1b31
commit
64738ea157
8 changed files with 227 additions and 16 deletions
|
@ -1,6 +1,6 @@
|
|||
{- git-annex command
|
||||
-
|
||||
- Copyright 2017-2020 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2017-2023 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -13,8 +13,12 @@ import Command
|
|||
import Logs.Config
|
||||
import Config
|
||||
import Types.GitConfig (globalConfigs)
|
||||
import Git.Types (fromConfigValue)
|
||||
import Git.Types (fromConfigValue, fromConfigKey)
|
||||
import qualified Git.Command
|
||||
import Utility.SafeOutput
|
||||
import Annex.CheckAttr
|
||||
import Types.NumCopies
|
||||
import Logs.NumCopies
|
||||
|
||||
import qualified Data.ByteString.Char8 as S8
|
||||
|
||||
|
@ -27,12 +31,13 @@ data Action
|
|||
= SetConfig ConfigKey ConfigValue
|
||||
| GetConfig ConfigKey
|
||||
| UnsetConfig ConfigKey
|
||||
| ShowOrigin ConfigKey (Maybe FilePath)
|
||||
|
||||
type Name = String
|
||||
type Value = String
|
||||
|
||||
optParser :: CmdParamsDesc -> Parser Action
|
||||
optParser _ = setconfig <|> getconfig <|> unsetconfig
|
||||
optParser _ = setconfig <|> getconfig <|> unsetconfig <|> showorigin
|
||||
where
|
||||
setconfig = SetConfig
|
||||
<$> strOption
|
||||
|
@ -53,40 +58,158 @@ optParser _ = setconfig <|> getconfig <|> unsetconfig
|
|||
<> help "unset configuration"
|
||||
<> metavar paramName
|
||||
)
|
||||
showorigin = ShowOrigin
|
||||
<$> strOption
|
||||
( long "show-origin"
|
||||
<> help "explain where a value is configured"
|
||||
<> metavar paramName
|
||||
)
|
||||
<*> optional (strOption
|
||||
( long "for-file"
|
||||
<> help "filename to check for in gitattributes"
|
||||
<> metavar paramFile
|
||||
))
|
||||
|
||||
seek :: Action -> CommandSeek
|
||||
seek (SetConfig ck@(ConfigKey name) val) = checkIsGlobalConfig ck $ commandAction $
|
||||
startingUsualMessages (decodeBS name) ai si $ do
|
||||
setGlobalConfig ck val
|
||||
seek (SetConfig ck@(ConfigKey name) val) = checkIsGlobalConfig ck $ \setter _unsetter _getter ->
|
||||
commandAction $ startingUsualMessages (decodeBS name) ai si $ do
|
||||
setter val
|
||||
when (needLocalUpdate ck) $
|
||||
setConfig ck (fromConfigValue val)
|
||||
next $ return True
|
||||
where
|
||||
ai = ActionItemOther (Just (UnquotedString (fromConfigValue val)))
|
||||
si = SeekInput [decodeBS name]
|
||||
seek (UnsetConfig ck@(ConfigKey name)) = checkIsGlobalConfig ck $ commandAction $
|
||||
startingUsualMessages (decodeBS name) ai si $ do
|
||||
unsetGlobalConfig ck
|
||||
seek (UnsetConfig ck@(ConfigKey name)) = checkIsGlobalConfig ck $ \_setter unsetter _getter ->
|
||||
commandAction $ startingUsualMessages (decodeBS name) ai si $ do
|
||||
unsetter
|
||||
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
|
||||
seek (GetConfig ck) = checkIsGlobalConfig ck $ \_setter _unsetter getter ->
|
||||
commandAction $ startingCustomOutput ai $ do
|
||||
getter >>= \case
|
||||
Just (ConfigValue v) -> liftIO $ S8.putStrLn $ safeOutput v
|
||||
Just NoConfigValue -> return ()
|
||||
Nothing -> return ()
|
||||
next $ return True
|
||||
where
|
||||
ai = ActionItemOther Nothing
|
||||
seek (ShowOrigin ck@(ConfigKey name) forfile) = commandAction $
|
||||
startingCustomOutput ai $ next $ checknotconfigured $
|
||||
case checkIsGlobalConfig' ck of
|
||||
Just (_setter, _unsetter, getter) ->
|
||||
ifM gitconfigorigin
|
||||
( return True
|
||||
, checkattrs (checkconfigbranch getter)
|
||||
)
|
||||
Nothing -> ifM gitconfigorigin
|
||||
( return True
|
||||
, checkattrs checkgitconfigunderride
|
||||
)
|
||||
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"
|
||||
gitconfigorigin
|
||||
| name `elem` gitconfigdoesnotoverride = return False
|
||||
| otherwise = gitconfigorigin'
|
||||
gitconfigorigin' = inRepo $ Git.Command.runBool
|
||||
[ Param "config"
|
||||
, Param "--show-origin"
|
||||
, Param (decodeBS name)
|
||||
]
|
||||
|
||||
-- git configs for these do not override values from git attributes
|
||||
-- or the branch
|
||||
gitconfigdoesnotoverride =
|
||||
[ "annex.numcopies"
|
||||
, "annex.mincopies"
|
||||
]
|
||||
|
||||
-- the git config for annex.numcopies is a special case; it's only
|
||||
-- used if not configured anywhere else
|
||||
checkgitconfigunderride
|
||||
| name == "annex.numcopies" = gitconfigorigin'
|
||||
| otherwise = return False
|
||||
|
||||
-- Display similar to git config --show-origin
|
||||
showval loc v = liftIO $ do
|
||||
putStrLn $ loc ++ "\t" ++ v
|
||||
return True
|
||||
|
||||
configbranch v
|
||||
| needLocalUpdate ck = checkgitconfigunderride
|
||||
| otherwise = showval "branch:git-annex" (decodeBS v)
|
||||
|
||||
checkconfigbranch getter = getter >>= \case
|
||||
Just (ConfigValue v) -> configbranch v
|
||||
_ -> checkgitconfigunderride
|
||||
|
||||
checkattrs cont
|
||||
| decodeBS name `elem` annexAttrs =
|
||||
case forfile of
|
||||
Just file -> do
|
||||
v <- checkAttr (decodeBS name) (toRawFilePath file)
|
||||
if null v
|
||||
then cont
|
||||
else showval "gitattributes" v
|
||||
Nothing -> do
|
||||
warnforfile
|
||||
cont
|
||||
| otherwise = cont
|
||||
|
||||
warnforfile = warning $ UnquotedString $ configKeyMessage ck $ unwords
|
||||
[ "may be configured in gitattributes."
|
||||
, "Pass --for-file= with a filename to check"
|
||||
]
|
||||
|
||||
checknotconfigured a = do
|
||||
ok <- a
|
||||
unless ok $
|
||||
warning $ UnquotedString $ configKeyMessage ck
|
||||
"is not configured"
|
||||
return ok
|
||||
|
||||
type Setter = ConfigValue -> Annex ()
|
||||
type Unsetter = Annex ()
|
||||
type Getter = Annex (Maybe ConfigValue)
|
||||
|
||||
checkIsGlobalConfig :: ConfigKey -> (Setter -> Unsetter -> Getter -> Annex a) -> Annex a
|
||||
checkIsGlobalConfig ck a = case checkIsGlobalConfig' ck of
|
||||
Just (setter, unsetter, getter) -> a setter unsetter getter
|
||||
Nothing -> giveup $ configKeyMessage ck "is not a configuration setting that can be stored in the git-annex branch"
|
||||
|
||||
checkIsGlobalConfig' :: ConfigKey -> Maybe (Setter, Unsetter, Getter)
|
||||
checkIsGlobalConfig' ck
|
||||
| elem ck globalConfigs = Just
|
||||
( setGlobalConfig ck
|
||||
, unsetGlobalConfig ck
|
||||
, getGlobalConfig ck
|
||||
)
|
||||
-- These came before this command, but are also global configs,
|
||||
-- so support them here as well.
|
||||
| ck == ConfigKey "annex.numcopies" = Just
|
||||
( mksetter (setGlobalNumCopies . configuredNumCopies)
|
||||
, error "unsetting annex.numcopies is not supported"
|
||||
, mkgetter fromNumCopies getGlobalNumCopies
|
||||
)
|
||||
| ck == ConfigKey "annex.mincopies" = Just
|
||||
( mksetter (setGlobalMinCopies . configuredMinCopies)
|
||||
, error "unsetting annex.mincopies is not supported"
|
||||
, mkgetter fromMinCopies getGlobalMinCopies
|
||||
)
|
||||
| otherwise = Nothing
|
||||
where
|
||||
mksetter f =
|
||||
maybe (error ("invalid value for " ++ fromConfigKey ck)) f
|
||||
. readish . decodeBS . fromConfigValue
|
||||
mkgetter f g = fmap (ConfigValue . encodeBS . show . f) <$> g
|
||||
|
||||
configKeyMessage :: ConfigKey -> String -> String
|
||||
configKeyMessage (ConfigKey name) msg = decodeBS name ++ " " ++ msg
|
||||
|
||||
needLocalUpdate :: ConfigKey -> Bool
|
||||
needLocalUpdate (ConfigKey "annex.securehashesonly") = True
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue