use ByteString for git config

The parser and looking up config keys in the map should both be faster
due to using ByteString.

I had hoped this would speed up startup time, but any improvement to
that was too small to measure. Seems worth keeping though.

Note that the parser breaks up the ByteString, but a config map ends up
pointing to the config as read, which is retained in memory until every
value from it is no longer used. This can change memory usage
patterns marginally, but won't affect git-annex.
This commit is contained in:
Joey Hess 2019-11-27 16:54:11 -04:00
parent 37d0f73e66
commit d7833def66
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
27 changed files with 176 additions and 105 deletions

View file

@ -6,6 +6,7 @@
-}
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module Config where
@ -22,25 +23,31 @@ import qualified Types.Remote as Remote
import qualified Annex.SpecialRemote.Config as SpecialRemote
import qualified Data.Map as M
import qualified Data.ByteString as S
type UnqualifiedConfigKey = String
data ConfigKey = ConfigKey String
type UnqualifiedConfigKey = S.ByteString
newtype ConfigKey = ConfigKey S.ByteString
instance Show ConfigKey where
show (ConfigKey s) = s
show (ConfigKey s) = decodeBS' s
{- Looks up a setting in git config. This is not as efficient as using the
- GitConfig type. -}
getConfig :: ConfigKey -> String -> Annex String
getConfig :: ConfigKey -> S.ByteString -> Annex S.ByteString
getConfig (ConfigKey key) d = fromRepo $ Git.Config.get key d
getConfigMaybe :: ConfigKey -> Annex (Maybe String)
getConfigMaybe :: ConfigKey -> Annex (Maybe S.ByteString)
getConfigMaybe (ConfigKey key) = fromRepo $ Git.Config.getMaybe key
{- Changes a git config setting in both internal state and .git/config -}
setConfig :: ConfigKey -> String -> Annex ()
setConfig (ConfigKey key) value = do
inRepo $ Git.Command.run [Param "config", Param key, Param value]
inRepo $ Git.Command.run
[ Param "config"
, Param (decodeBS' key)
, Param value
]
reloadConfig
reloadConfig :: Annex ()
@ -68,11 +75,11 @@ instance RemoteNameable Remote.RemoteConfig where
{- A per-remote config setting in git config. -}
remoteConfig :: RemoteNameable r => r -> UnqualifiedConfigKey -> ConfigKey
remoteConfig r key = ConfigKey $
"remote." ++ getRemoteName r ++ ".annex-" ++ key
"remote." <> encodeBS' (getRemoteName r) <> ".annex-" <> key
{- A global annex setting in git config. -}
annexConfig :: UnqualifiedConfigKey -> ConfigKey
annexConfig key = ConfigKey $ "annex." ++ key
annexConfig key = ConfigKey ("annex." <> key)
{- Calculates cost for a remote. Either the specific default, or as configured
- by remote.<name>.annex-cost, or if remote.<name>.annex-cost-command