Add annex-trustlevel configuration settings, which can be used to override the trust level of a remote.

This overrides the trust.log, and is overridden by the command-line trust
parameters.

It would have been nicer to have Logs.Trust.trustMap just look up the
configuration for all remotes, but a dependency loop prevented that
(Remotes depends on Logs.Trust in several ways). So instead, look up
the configuration when building remotes, storing it in the same forcetrust
field used for the command-line trust parameters.
This commit is contained in:
Joey Hess 2012-01-09 23:31:44 -04:00
parent 9ffd97442b
commit 0d5c402210
7 changed files with 64 additions and 26 deletions

View file

@ -40,7 +40,6 @@ import qualified Types.Remote
import Types.Crypto import Types.Crypto
import Types.BranchState import Types.BranchState
import Types.TrustLevel import Types.TrustLevel
import Types.UUID
import qualified Utility.Matcher import qualified Utility.Matcher
import qualified Data.Map as M import qualified Data.Map as M
@ -84,7 +83,7 @@ data AnnexState = AnnexState
, forcebackend :: Maybe String , forcebackend :: Maybe String
, forcenumcopies :: Maybe Int , forcenumcopies :: Maybe Int
, limit :: Matcher (FilePath -> Annex Bool) , limit :: Matcher (FilePath -> Annex Bool)
, forcetrust :: [(UUID, TrustLevel)] , forcetrust :: TrustMap
, trustmap :: Maybe TrustMap , trustmap :: Maybe TrustMap
, ciphers :: M.Map EncryptedCipher Cipher , ciphers :: M.Map EncryptedCipher Cipher
, flags :: M.Map String Bool , flags :: M.Map String Bool
@ -106,7 +105,7 @@ newState gitrepo = AnnexState
, forcebackend = Nothing , forcebackend = Nothing
, forcenumcopies = Nothing , forcenumcopies = Nothing
, limit = Left [] , limit = Left []
, forcetrust = [] , forcetrust = M.empty
, trustmap = Nothing , trustmap = Nothing
, ciphers = M.empty , ciphers = M.empty
, flags = M.empty , flags = M.empty

View file

@ -12,6 +12,8 @@ import qualified Git
import qualified Git.Config import qualified Git.Config
import qualified Git.Command import qualified Git.Command
import qualified Annex import qualified Annex
import qualified Logs.Trust
import Types.TrustLevel
type ConfigKey = String type ConfigKey = String
@ -30,7 +32,7 @@ getConfig r key def = do
def' <- fromRepo $ Git.Config.get ("annex." ++ key) def def' <- fromRepo $ Git.Config.get ("annex." ++ key) def
fromRepo $ Git.Config.get (remoteConfig r key) def' fromRepo $ Git.Config.get (remoteConfig r key) def'
{- Looks up a per-remote config setting in git config. -} {- A per-remote config setting in git config. -}
remoteConfig :: Git.Repo -> ConfigKey -> String remoteConfig :: Git.Repo -> ConfigKey -> String
remoteConfig r key = "remote." ++ fromMaybe "" (Git.remoteName r) ++ ".annex-" ++ key remoteConfig r key = "remote." ++ fromMaybe "" (Git.remoteName r) ++ ".annex-" ++ key
@ -67,9 +69,7 @@ prop_cost_sane = False `notElem`
, semiCheapRemoteCost + encryptedRemoteCostAdj < expensiveRemoteCost , semiCheapRemoteCost + encryptedRemoteCostAdj < expensiveRemoteCost
] ]
{- Checks if a repo should be ignored, based either on annex-ignore {- Checks if a repo should be ignored. -}
- setting, or on command-line options. Allows command-line to override
- annex-ignore. -}
repoNotIgnored :: Git.Repo -> Annex Bool repoNotIgnored :: Git.Repo -> Annex Bool
repoNotIgnored r = not . Git.configTrue <$> getConfig r "ignore" "false" repoNotIgnored r = not . Git.configTrue <$> getConfig r "ignore" "false"
@ -83,3 +83,8 @@ getNumCopies v = perhaps (use v) =<< Annex.getState Annex.forcenumcopies
readMaybe <$> fromRepo (Git.Config.get config "1") readMaybe <$> fromRepo (Git.Config.get config "1")
perhaps fallback = maybe fallback (return . id) perhaps fallback = maybe fallback (return . id)
config = "annex.numcopies" config = "annex.numcopies"
{- Gets the trust level set for a remote in git config. -}
getTrustLevel :: Git.Repo -> Annex (Maybe TrustLevel)
getTrustLevel r = maybe Nothing Logs.Trust.trustName <$>
fromRepo (Git.Config.getMaybe (remoteConfig r "trustlevel"))

View file

@ -20,6 +20,10 @@ import qualified Git.Construct
get :: String -> String -> Repo -> String get :: String -> String -> Repo -> String
get key defaultValue repo = M.findWithDefault defaultValue key (config repo) get key defaultValue repo = M.findWithDefault defaultValue key (config repo)
{- Returns a single git config setting, if set. -}
getMaybe :: String -> Repo -> Maybe String
getMaybe key repo = M.lookup key (config repo)
{- Runs git config and populates a repo with its config. -} {- Runs git config and populates a repo with its config. -}
read :: Repo -> IO Repo read :: Repo -> IO Repo
read repo@(Repo { location = Dir d }) = do read repo@(Repo { location = Dir d }) = do

View file

@ -9,7 +9,8 @@ module Logs.Trust (
TrustLevel(..), TrustLevel(..),
trustGet, trustGet,
trustSet, trustSet,
trustPartition trustPartition,
trustName
) where ) where
import qualified Data.Map as M import qualified Data.Map as M
@ -32,6 +33,15 @@ trustLog = "trust.log"
trustGet :: TrustLevel -> Annex [UUID] trustGet :: TrustLevel -> Annex [UUID]
trustGet level = M.keys . M.filter (== level) <$> trustMap trustGet level = M.keys . M.filter (== level) <$> trustMap
{- Changes the trust level for a uuid in the trustLog. -}
trustSet :: UUID -> TrustLevel -> Annex ()
trustSet uuid@(UUID _) level = do
ts <- liftIO getPOSIXTime
Annex.Branch.change trustLog $
showLog showTrust . changeLog ts uuid level . parseLog (Just . parseTrust)
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
trustSet NoUUID _ = error "unknown UUID; cannot modify trust level"
{- Partitions a list of UUIDs to those matching a TrustLevel and not. -} {- Partitions a list of UUIDs to those matching a TrustLevel and not. -}
trustPartition :: TrustLevel -> [UUID] -> Annex ([UUID], [UUID]) trustPartition :: TrustLevel -> [UUID] -> Annex ([UUID], [UUID])
trustPartition level ls trustPartition level ls
@ -53,9 +63,10 @@ trustMap = do
case cached of case cached of
Just m -> return m Just m -> return m
Nothing -> do Nothing -> do
overrides <- M.fromList <$> Annex.getState Annex.forcetrust overrides <- Annex.getState Annex.forcetrust
m <- (M.union overrides . simpleMap . parseLog (Just . parseTrust)) <$> logged <- simpleMap . parseLog (Just . parseTrust) <$>
Annex.Branch.get trustLog Annex.Branch.get trustLog
let m = M.union overrides logged
Annex.changeState $ \s -> s { Annex.trustmap = Just m } Annex.changeState $ \s -> s { Annex.trustmap = Just m }
return m return m
@ -75,11 +86,9 @@ showTrust UnTrusted = "0"
showTrust DeadTrusted = "X" showTrust DeadTrusted = "X"
showTrust SemiTrusted = "?" showTrust SemiTrusted = "?"
{- Changes the trust level for a uuid in the trustLog. -} trustName :: String -> Maybe TrustLevel
trustSet :: UUID -> TrustLevel -> Annex () trustName "trusted" = Just Trusted
trustSet uuid@(UUID _) level = do trustName "untrusted" = Just UnTrusted
ts <- liftIO getPOSIXTime trustName "deadtrusted" = Just DeadTrusted
Annex.Branch.change trustLog $ trustName "semitrusted" = Just SemiTrusted
showLog showTrust . changeLog ts uuid level . parseLog (Just . parseTrust) trustName _ = Nothing
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
trustSet NoUUID _ = error "unknown UUID; cannot modify trust level"

View file

@ -40,6 +40,7 @@ import Text.JSON.Generic
import Common.Annex import Common.Annex
import Types.Remote import Types.Remote
import qualified Annex import qualified Annex
import qualified Git
import Config import Config
import Annex.UUID import Annex.UUID
import Logs.UUID import Logs.UUID
@ -74,17 +75,15 @@ remoteList = do
if null rs if null rs
then do then do
m <- readRemoteLog m <- readRemoteLog
l <- mapM (process m) remoteTypes rs' <- concat <$> mapM (process m) remoteTypes
let rs' = concat l
Annex.changeState $ \s -> s { Annex.remotes = rs' } Annex.changeState $ \s -> s { Annex.remotes = rs' }
return rs' return rs'
else return rs else return rs
where where
process m t = process m t = enumerate t >>= mapM (gen m t)
enumerate t >>=
mapM (gen m t)
gen m t r = do gen m t r = do
u <- getRepoUUID r u <- getRepoUUID r
checkTrust r u
generate t r u (M.lookup u m) generate t r u (M.lookup u m)
{- All remotes that are not ignored. -} {- All remotes that are not ignored. -}
@ -242,10 +241,24 @@ showTriedRemotes remotes =
(join ", " $ map name remotes) (join ", " $ map name remotes)
forceTrust :: TrustLevel -> String -> Annex () forceTrust :: TrustLevel -> String -> Annex ()
forceTrust level remotename = do forceTrust level remotename = forceTrust' True level =<< nameToUUID remotename
r <- nameToUUID remotename
forceTrust' :: Bool -> TrustLevel -> UUID -> Annex ()
forceTrust' overwrite level u = do
Annex.changeState $ \s -> Annex.changeState $ \s ->
s { Annex.forcetrust = (r, level):Annex.forcetrust s } s { Annex.forcetrust = change u level (Annex.forcetrust s) }
-- This change invalidated any cached trustmap.
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
where
change
| overwrite = M.insert
| otherwise = M.insertWith (\_new old -> old)
checkTrust :: Git.Repo -> UUID -> Annex ()
checkTrust r u = set =<< getTrustLevel r
where
set (Just level) = forceTrust' False level u
set Nothing = return ()
{- Used to log a change in a remote's having a key. The change is logged {- Used to log a change in a remote's having a key. The change is logged
- in the local repo, not on the remote. The process of transferring the - in the local repo, not on the remote. The process of transferring the

2
debian/changelog vendored
View file

@ -2,6 +2,8 @@ git-annex (3.20120107) UNRELEASED; urgency=low
* log: Add --gource mode, which generates output usable by gource. * log: Add --gource mode, which generates output usable by gource.
* map: Fix display of remote repos * map: Fix display of remote repos
* Add annex-trustlevel configuration settings, which can be used to
override the trust level of a remote.
-- Joey Hess <joeyh@debian.org> Sat, 07 Jan 2012 18:12:09 -0400 -- Joey Hess <joeyh@debian.org> Sat, 07 Jan 2012 18:12:09 -0400

View file

@ -606,6 +606,12 @@ Here are all the supported configuration settings.
git-annex caches UUIDs of remote repositories here. git-annex caches UUIDs of remote repositories here.
* `remote.<name>.annex-trustlevel`
Configures a local trust level for the remote. This overrides the value
configured by the trust and untrust commands. The value can be any of
"trusted", "semitrusted" or "untrusted".
* `remote.<name>.annex-ssh-options` * `remote.<name>.annex-ssh-options`
Options to use when using ssh to talk to this remote. Options to use when using ssh to talk to this remote.