This commit is contained in:
Joey Hess 2011-09-06 17:19:29 -04:00
parent 6f98fd5391
commit 3623d831d1
4 changed files with 13 additions and 12 deletions

View file

@ -10,7 +10,6 @@ module Command.Fsck where
import Control.Monad (when)
import Control.Monad.State (liftIO)
import System.Directory
import Data.List
import System.Posix.Files
import Command
@ -124,10 +123,7 @@ checkKeySize key = do
checkKeyNumCopies :: Key -> Maybe FilePath -> Maybe Int -> Annex Bool
checkKeyNumCopies key file numcopies = do
needed <- getNumCopies numcopies
locations <- keyLocations key
untrusted <- trustGet UnTrusted
let untrustedlocations = intersect untrusted locations
let safelocations = filter (`notElem` untrusted) locations
(untrustedlocations, safelocations) <- trustPartition UnTrusted =<< keyLocations key
let present = length safelocations
if present < needed
then do

View file

@ -8,7 +8,6 @@
module Command.Whereis where
import Control.Monad
import Data.List
import LocationLog
import Command
@ -32,9 +31,7 @@ start file = isAnnexed file $ \(key, _) -> do
perform :: Key -> CommandPerform
perform key = do
locations <- keyLocations key
untrusted <- trustGet UnTrusted
let untrustedlocations = intersect untrusted locations
let safelocations = filter (`notElem` untrusted) locations
(untrustedlocations, safelocations) <- trustPartition UnTrusted locations
let num = length safelocations
showNote $ show num ++ " " ++ copiesplural num
pp <- prettyPrintUUIDs "whereis" safelocations

View file

@ -181,7 +181,7 @@ keyPossibilities' withtrusted key = do
let validuuids = filter (/= u) uuids
-- note that validuuids is assumed to not have dups
let validtrusteduuids = intersect validuuids trusted
let validtrusteduuids = validuuids `intersect` trusted
-- remotes that match uuids that have the key
allremotes <- genList

View file

@ -9,11 +9,13 @@ module Trust (
TrustLevel(..),
trustLog,
trustGet,
trustSet
trustSet,
trustPartition
) where
import Control.Monad.State
import qualified Data.Map as M
import Data.List
import Types.TrustLevel
import qualified Branch
@ -32,7 +34,7 @@ trustGet level = do
return $ M.keys $ M.filter (== level) m
{- Read the trustLog into a map, overriding with any
- values from forcetrust -}
- values from forcetrust. The map is cached for speed. -}
trustMap :: Annex TrustMap
trustMap = do
cached <- Annex.getState Annex.trustmap
@ -70,3 +72,9 @@ trustSet uuid level = do
where
serialize m = unlines $ map showpair $ M.toList m
showpair (u, t) = u ++ " " ++ show t
{- Partitions a list of UUIDs to those matching a TrustLevel and not. -}
trustPartition :: TrustLevel -> [UUID] -> Annex ([UUID], [UUID])
trustPartition level ls = do
candidates <- trustGet level
return $ partition (`elem` candidates) ls