Fix a potential failure to parse git config

Git has an obnoxious special case in git config, a line "foo" is the same
as "foo = true". That means there is no way to examine the output of
git config and tell if it was run with --null or not, since a "foo"
in the first line could be such a boolean, or could be followed by its
value on the next line if --null were used.

So, rather than trying to do such a detection, track the style of config
at all the points where it's generated.
This commit is contained in:
Joey Hess 2020-04-13 13:05:41 -04:00
parent fbd78cff64
commit ca9c6c5f60
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
7 changed files with 31 additions and 32 deletions

View file

@ -111,7 +111,7 @@ storeUUIDIn configfield = setConfig configfield . fromUUID
setUUID :: Git.Repo -> UUID -> IO Git.Repo setUUID :: Git.Repo -> UUID -> IO Git.Repo
setUUID r u = do setUUID r u = do
let s = encodeBS' $ show configkeyUUID ++ "=" ++ fromUUID u let s = encodeBS' $ show configkeyUUID ++ "=" ++ fromUUID u
Git.Config.store s r Git.Config.store s Git.Config.ConfigList r
-- Dummy uuid for the whole web. Do not alter. -- Dummy uuid for the whole web. Do not alter.
webUUID :: UUID webUUID :: UUID

View file

@ -6,6 +6,7 @@ git-annex (8.20200331) UNRELEASED; urgency=medium
* Sped up query commands that read the git-annex branch by around 9%. * Sped up query commands that read the git-annex branch by around 9%.
* Various speed improvements gained by using ByteStrings for git refs and * Various speed improvements gained by using ByteStrings for git refs and
shas. shas.
* Fix a potential failure to parse git config.
-- Joey Hess <id@joeyh.name> Mon, 30 Mar 2020 15:58:34 -0400 -- Joey Hess <id@joeyh.name> Mon, 30 Mar 2020 15:58:34 -0400

View file

@ -96,7 +96,7 @@ gitAnnexGlobalOptions = commonGlobalOptions ++
setgitconfig v = Annex.adjustGitRepo $ \r -> setgitconfig v = Annex.adjustGitRepo $ \r ->
if Param v `elem` gitGlobalOpts r if Param v `elem` gitGlobalOpts r
then return r then return r
else Git.Config.store (encodeBS' v) $ else Git.Config.store (encodeBS' v) Git.Config.ConfigList $
r { gitGlobalOpts = gitGlobalOpts r ++ [Param "-c", Param v] } r { gitGlobalOpts = gitGlobalOpts r ++ [Param "-c", Param v] }
setdesktopnotify v = Annex.changeState $ \s -> s { Annex.desktopnotify = Annex.desktopnotify s <> v } setdesktopnotify v = Annex.changeState $ \s -> s { Annex.desktopnotify = Annex.desktopnotify s <> v }

View file

@ -222,18 +222,18 @@ tryScan r
Nothing -> return $ Just r Nothing -> return $ Just r
| otherwise = liftIO $ safely $ Git.Config.read r | otherwise = liftIO $ safely $ Git.Config.read r
where where
pipedconfig pcmd params = liftIO $ safely $ pipedconfig st pcmd params = liftIO $ safely $
withHandle StdoutHandle createProcessSuccess p $ withHandle StdoutHandle createProcessSuccess p $
Git.Config.hRead r Git.Config.hRead r st
where where
p = proc pcmd $ toCommand params p = proc pcmd $ toCommand params
configlist = Ssh.onRemote NoConsumeStdin r configlist = Ssh.onRemote NoConsumeStdin r
(pipedconfig, return Nothing) "configlist" [] [] (pipedconfig Git.Config.ConfigList, return Nothing) "configlist" [] []
manualconfiglist = do manualconfiglist = do
gc <- Annex.getRemoteGitConfig r gc <- Annex.getRemoteGitConfig r
(sshcmd, sshparams) <- Ssh.toRepo NoConsumeStdin r gc remotecmd (sshcmd, sshparams) <- Ssh.toRepo NoConsumeStdin r gc remotecmd
liftIO $ pipedconfig sshcmd sshparams liftIO $ pipedconfig Git.Config.ConfigNullList sshcmd sshparams
where where
remotecmd = "sh -c " ++ shellEscape remotecmd = "sh -c " ++ shellEscape
(cddir ++ " && " ++ "git config --null --list") (cddir ++ " && " ++ "git config --null --list")

View file

@ -59,7 +59,7 @@ read' repo = go repo
go Repo { location = LocalUnknown d } = git_config d go Repo { location = LocalUnknown d } = git_config d
go _ = assertLocal repo $ error "internal" go _ = assertLocal repo $ error "internal"
git_config d = withHandle StdoutHandle createProcessSuccess p $ git_config d = withHandle StdoutHandle createProcessSuccess p $
hRead repo hRead repo ConfigNullList
where where
params = ["config", "--null", "--list"] params = ["config", "--null", "--list"]
p = (proc "git" params) p = (proc "git" params)
@ -74,7 +74,7 @@ global = do
ifM (doesFileExist $ home </> ".gitconfig") ifM (doesFileExist $ home </> ".gitconfig")
( do ( do
repo <- withHandle StdoutHandle createProcessSuccess p $ repo <- withHandle StdoutHandle createProcessSuccess p $
hRead (Git.Construct.fromUnknown) hRead (Git.Construct.fromUnknown) ConfigNullList
return $ Just repo return $ Just repo
, return Nothing , return Nothing
) )
@ -83,18 +83,18 @@ global = do
p = (proc "git" params) p = (proc "git" params)
{- Reads git config from a handle and populates a repo with it. -} {- Reads git config from a handle and populates a repo with it. -}
hRead :: Repo -> Handle -> IO Repo hRead :: Repo -> ConfigStyle -> Handle -> IO Repo
hRead repo h = do hRead repo st h = do
val <- S.hGetContents h val <- S.hGetContents h
store val repo store val st repo
{- Stores a git config into a Repo, returning the new version of the Repo. {- Stores a git config into a Repo, returning the new version of the Repo.
- The git config may be multiple lines, or a single line. - The git config may be multiple lines, or a single line.
- Config settings can be updated incrementally. - Config settings can be updated incrementally.
-} -}
store :: S.ByteString -> Repo -> IO Repo store :: S.ByteString -> ConfigStyle -> Repo -> IO Repo
store s repo = do store s st repo = do
let c = parse s let c = parse s st
updateLocation $ repo updateLocation $ repo
{ config = (M.map Prelude.head c) `M.union` config repo { config = (M.map Prelude.head c) `M.union` config repo
, fullconfig = M.unionWith (++) c (fullconfig repo) , fullconfig = M.unionWith (++) c (fullconfig repo)
@ -137,21 +137,19 @@ updateLocation' r l = do
return $ l { worktree = Just (toRawFilePath p) } return $ l { worktree = Just (toRawFilePath p) }
return $ r { location = l' } return $ r { location = l' }
data ConfigStyle = ConfigList | ConfigNullList
{- Parses git config --list or git config --null --list output into a {- Parses git config --list or git config --null --list output into a
- config map. -} - config map. -}
parse :: S.ByteString -> M.Map ConfigKey [ConfigValue] parse :: S.ByteString -> ConfigStyle -> M.Map ConfigKey [ConfigValue]
parse s parse s st
| S.null s = M.empty | S.null s = M.empty
-- --list output will have a '=' in the first line | otherwise = case st of
-- (The first line of --null --list output is the name of a key, ConfigList -> sep eq $ S.split nl s
-- which is assumed to never contain '='.) ConfigNullList -> sep nl $ S.split 0 s
| S.elem eq firstline = sep eq $ S.split nl s
-- --null --list output separates keys from values with newlines
| otherwise = sep nl $ S.split 0 s
where where
nl = fromIntegral (ord '\n') nl = fromIntegral (ord '\n')
eq = fromIntegral (ord '=') eq = fromIntegral (ord '=')
firstline = S.takeWhile (/= nl) s
sep c = M.fromListWith (++) sep c = M.fromListWith (++)
. map (\(k,v) -> (ConfigKey k, [ConfigValue (S.drop 1 v)])) . map (\(k,v) -> (ConfigKey k, [ConfigValue (S.drop 1 v)]))
@ -186,14 +184,14 @@ coreBare = "core.bare"
{- Runs a command to get the configuration of a repo, {- Runs a command to get the configuration of a repo,
- and returns a repo populated with the configuration, as well as the raw - and returns a repo populated with the configuration, as well as the raw
- output and any standard output of the command. -} - output and any standard output of the command. -}
fromPipe :: Repo -> String -> [CommandParam] -> IO (Either SomeException (Repo, S.ByteString, S.ByteString)) fromPipe :: Repo -> String -> [CommandParam] -> ConfigStyle -> IO (Either SomeException (Repo, S.ByteString, S.ByteString))
fromPipe r cmd params = try $ fromPipe r cmd params st = try $
withOEHandles createProcessSuccess p $ \(hout, herr) -> do withOEHandles createProcessSuccess p $ \(hout, herr) -> do
geterr <- async $ S.hGetContents herr geterr <- async $ S.hGetContents herr
getval <- async $ S.hGetContents hout getval <- async $ S.hGetContents hout
val <- wait getval val <- wait getval
err <- wait geterr err <- wait geterr
r' <- store val r r' <- store val st r
return (r', val, err) return (r', val, err)
where where
p = proc cmd $ toCommand params p = proc cmd $ toCommand params
@ -206,7 +204,7 @@ fromFile r f = fromPipe r "git"
, Param "--file" , Param "--file"
, File f , File f
, Param "--list" , Param "--list"
] ] ConfigList
{- Changes a git config setting in the specified config file. {- Changes a git config setting in the specified config file.
- (Creates the file if it does not already exist.) -} - (Creates the file if it does not already exist.) -}

View file

@ -474,7 +474,7 @@ getGCryptId fast r gc
| Git.repoIsLocal r || Git.repoIsLocalUnknown r = extract <$> | Git.repoIsLocal r || Git.repoIsLocalUnknown r = extract <$>
liftIO (catchMaybeIO $ Git.Config.read r) liftIO (catchMaybeIO $ Git.Config.read r)
| not fast = extract . liftM fst3 <$> getM (eitherToMaybe <$>) | not fast = extract . liftM fst3 <$> getM (eitherToMaybe <$>)
[ Ssh.onRemote NoConsumeStdin r (\f p -> liftIO (Git.Config.fromPipe r f p), return (Left $ error "configlist failed")) "configlist" [] [] [ Ssh.onRemote NoConsumeStdin r (\f p -> liftIO (Git.Config.fromPipe r f p Git.Config.ConfigList), return (Left $ error "configlist failed")) "configlist" [] []
, getConfigViaRsync r gc , getConfigViaRsync r gc
] ]
| otherwise = return (Nothing, r) | otherwise = return (Nothing, r)

View file

@ -249,7 +249,7 @@ tryGitConfigRead autoinit r
| haveconfig r = return r -- already read | haveconfig r = return r -- already read
| Git.repoIsSsh r = storeUpdatedRemote $ do | Git.repoIsSsh r = storeUpdatedRemote $ do
v <- Ssh.onRemote NoConsumeStdin r v <- Ssh.onRemote NoConsumeStdin r
(pipedconfig autoinit (Git.repoDescribe r), return (Left $ giveup "configlist failed")) (pipedconfig Git.Config.ConfigList autoinit (Git.repoDescribe r), return (Left $ giveup "configlist failed"))
"configlist" [] configlistfields "configlist" [] configlistfields
case v of case v of
Right r' Right r'
@ -264,8 +264,8 @@ tryGitConfigRead autoinit r
where where
haveconfig = not . M.null . Git.config haveconfig = not . M.null . Git.config
pipedconfig mustincludeuuuid configloc cmd params = do pipedconfig st mustincludeuuuid configloc cmd params = do
v <- liftIO $ Git.Config.fromPipe r cmd params v <- liftIO $ Git.Config.fromPipe r cmd params st
case v of case v of
Right (r', val, _err) -> do Right (r', val, _err) -> do
unless (isUUIDConfigured r' || S.null val || not mustincludeuuuid) $ do unless (isUUIDConfigured r' || S.null val || not mustincludeuuuid) $ do
@ -282,7 +282,7 @@ tryGitConfigRead autoinit r
liftIO $ hClose h liftIO $ hClose h
let url = Git.repoLocation r ++ "/config" let url = Git.repoLocation r ++ "/config"
ifM (liftIO $ Url.downloadQuiet nullMeterUpdate url tmpfile uo) ifM (liftIO $ Url.downloadQuiet nullMeterUpdate url tmpfile uo)
( Just <$> pipedconfig False url "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile] ( Just <$> pipedconfig Git.Config.ConfigNullList False url "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile]
, return Nothing , return Nothing
) )
case v of case v of