diff options
Diffstat (limited to 'Command')
-rw-r--r-- | Command/Status.hs | 2 | ||||
-rw-r--r-- | Command/Whereis.hs | 28 |
2 files changed, 22 insertions, 8 deletions
diff --git a/Command/Status.hs b/Command/Status.hs index 5facaab9b..dfe847bb8 100644 --- a/Command/Status.hs +++ b/Command/Status.hs @@ -113,7 +113,7 @@ supported_remote_types = stat "supported remote types" $ json unwords $ remote_list :: TrustLevel -> String -> Stat remote_list level desc = stat n $ nojson $ lift $ do - us <- M.keys <$> (M.union <$> uuidMap <*> remoteMap) + us <- M.keys <$> (M.union <$> uuidMap <*> remoteMap Remote.name) rs <- fst <$> trustPartition level us s <- prettyPrintUUIDs n rs return $ if null s then "0" else show (length rs) ++ "\n" ++ beginning s diff --git a/Command/Whereis.hs b/Command/Whereis.hs index 1fbe70799..f62d34642 100644 --- a/Command/Whereis.hs +++ b/Command/Whereis.hs @@ -7,6 +7,8 @@ module Command.Whereis where +import qualified Data.Map as M + import Common.Annex import Command import Remote @@ -17,24 +19,36 @@ def = [command "whereis" paramPaths seek "lists repositories that have file content"] seek :: [CommandSeek] -seek = [withFilesInGit $ whenAnnexed start] +seek = [withValue (remoteMap id) $ \m -> + withFilesInGit $ whenAnnexed $ start m] -start :: FilePath -> (Key, Backend) -> CommandStart -start file (key, _) = do +start :: (M.Map UUID Remote) -> FilePath -> (Key, Backend) -> CommandStart +start remotemap file (key, _) = do showStart "whereis" file - next $ perform key + next $ perform remotemap key -perform :: Key -> CommandPerform -perform key = do - (untrustedlocations, safelocations) <- trustPartition UnTrusted =<< keyLocations key +perform :: (M.Map UUID Remote) -> Key -> CommandPerform +perform remotemap key = do + locations <- keyLocations key + (untrustedlocations, safelocations) <- trustPartition UnTrusted locations let num = length safelocations showNote $ show num ++ " " ++ copiesplural num pp <- prettyPrintUUIDs "whereis" safelocations unless (null safelocations) $ showLongNote pp pp' <- prettyPrintUUIDs "untrusted" untrustedlocations unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp' + forM_ (catMaybes $ map (`M.lookup` remotemap) locations) $ + performRemote key if null safelocations then stop else next $ return True where copiesplural 1 = "copy" copiesplural _ = "copies" untrustedheader = "The following untrusted locations may also have copies:\n" + +performRemote :: Key -> Remote -> Annex () +performRemote key remote = case whereisKey remote of + Nothing -> return () + Just a -> do + ls <- a key + unless (null ls) $ showLongNote $ + unlines $ map (\l -> name remote ++ ": " ++ l) ls |