summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Config.hs16
-rw-r--r--Remote/Helper/Special.hs9
2 files changed, 17 insertions, 8 deletions
diff --git a/Config.hs b/Config.hs
index d9ad80eed..4af4f1284 100644
--- a/Config.hs
+++ b/Config.hs
@@ -5,6 +5,8 @@
- Licensed under the GNU GPL version 3 or higher.
-}
+{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
+
module Config where
import Common.Annex
@@ -14,6 +16,7 @@ import qualified Git.Command
import qualified Annex
import Config.Cost
import Types.Availability
+import Git.Types
type UnqualifiedConfigKey = String
data ConfigKey = ConfigKey String
@@ -41,10 +44,19 @@ reloadConfig = Annex.changeGitRepo =<< inRepo Git.Config.reRead
unsetConfig :: ConfigKey -> Annex ()
unsetConfig (ConfigKey key) = void $ inRepo $ Git.Config.unset key
+class RemoteNameable r where
+ getRemoteName :: r -> RemoteName
+
+instance RemoteNameable Git.Repo where
+ getRemoteName r = fromMaybe "" (Git.remoteName r)
+
+instance RemoteNameable RemoteName where
+ getRemoteName = id
+
{- A per-remote config setting in git config. -}
-remoteConfig :: Git.Repo -> UnqualifiedConfigKey -> ConfigKey
+remoteConfig :: RemoteNameable r => r -> UnqualifiedConfigKey -> ConfigKey
remoteConfig r key = ConfigKey $
- "remote." ++ fromMaybe "" (Git.remoteName r) ++ ".annex-" ++ key
+ "remote." ++ getRemoteName r ++ ".annex-" ++ key
{- A global annex setting in git config. -}
annexConfig :: UnqualifiedConfigKey -> ConfigKey
diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs
index 956d48273..60bf123a5 100644
--- a/Remote/Helper/Special.hs
+++ b/Remote/Helper/Special.hs
@@ -36,6 +36,7 @@ import Common.Annex
import Types.StoreRetrieve
import Types.Remote
import Crypto
+import Config
import Config.Cost
import Utility.Metered
import Remote.Helper.Chunked as X
@@ -44,7 +45,6 @@ import Remote.Helper.Messages
import Annex.Content
import Messages.Progress
import qualified Git
-import qualified Git.Command
import qualified Git.Construct
import qualified Data.ByteString.Lazy as L
@@ -66,13 +66,10 @@ findSpecialRemotes s = do
{- Sets up configuration for a special remote in .git/config. -}
gitConfigSpecialRemote :: UUID -> RemoteConfig -> String -> String -> Annex ()
gitConfigSpecialRemote u c k v = do
- set ("annex-"++k) v
- set ("annex-uuid") (fromUUID u)
+ setConfig (remoteConfig remotename k) v
+ setConfig (remoteConfig remotename "uuid") (fromUUID u)
where
- set a b = inRepo $ Git.Command.run
- [Param "config", Param (configsetting a), Param b]
remotename = fromJust (M.lookup "name" c)
- configsetting s = "remote." ++ remotename ++ "." ++ s
-- Use when nothing needs to be done to prepare a helper.
simplyPrepare :: helper -> Preparer helper