whereis: Prints the urls of files that the web special remote knows about.

This commit is contained in:
Joey Hess 2012-02-14 03:49:48 -04:00
parent 8fbc529d68
commit cb631ce518
12 changed files with 37 additions and 12 deletions

View file

@ -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

View file

@ -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

View file

@ -15,6 +15,7 @@ module Remote (
removeKey,
hasKey,
hasKeyCheap,
whereisKey,
remoteTypes,
remoteList,
@ -48,16 +49,16 @@ import Logs.Trust
import Logs.Location
import Remote.List
{- Map of UUIDs of Remotes and their names. -}
remoteMap :: Annex (M.Map UUID String)
remoteMap = M.fromList . map (\r -> (uuid r, name r)) .
{- Map from UUIDs of Remotes to a calculated value. -}
remoteMap :: (Remote -> a) -> Annex (M.Map UUID a)
remoteMap c = M.fromList . map (\r -> (uuid r, c r)) .
filter (\r -> uuid r /= NoUUID) <$> remoteList
{- Map of UUIDs and their descriptions.
- The names of Remotes are added to suppliment any description that has
- been set for a repository. -}
uuidDescriptions :: Annex (M.Map UUID String)
uuidDescriptions = M.unionWith addName <$> uuidMap <*> remoteMap
uuidDescriptions = M.unionWith addName <$> uuidMap <*> remoteMap name
addName :: String -> String -> String
addName desc n

View file

@ -53,6 +53,7 @@ gen r u c = do
removeKey = remove,
hasKey = checkPresent r bupr',
hasKeyCheap = bupLocal buprepo,
whereisKey = Nothing,
config = c,
repo = r,
remotetype = remote

View file

@ -45,6 +45,7 @@ gen r u c = do
removeKey = remove dir,
hasKey = checkPresent dir,
hasKeyCheap = True,
whereisKey = Nothing,
config = Nothing,
repo = r,
remotetype = remote

View file

@ -81,6 +81,7 @@ gen r u _ = do
removeKey = dropKey r',
hasKey = inAnnex r',
hasKeyCheap = cheap,
whereisKey = Nothing,
config = Nothing,
repo = r',
remotetype = remote

View file

@ -45,6 +45,7 @@ gen r u c = do
removeKey = remove hooktype,
hasKey = checkPresent r hooktype,
hasKeyCheap = False,
whereisKey = Nothing,
config = Nothing,
repo = r,
remotetype = remote

View file

@ -52,6 +52,7 @@ gen r u c = do
removeKey = remove o,
hasKey = checkPresent r o,
hasKeyCheap = False,
whereisKey = Nothing,
config = Nothing,
repo = r,
remotetype = remote

View file

@ -57,6 +57,7 @@ gen' r u c cst =
removeKey = remove this,
hasKey = checkPresent this,
hasKeyCheap = False,
whereisKey = Nothing,
config = c,
repo = r,
remotetype = remote

View file

@ -45,6 +45,7 @@ gen r _ _ =
removeKey = dropKey,
hasKey = checkKey,
hasKeyCheap = False,
whereisKey = Just getUrls,
config = Nothing,
repo = r,
remotetype = remote

View file

@ -55,6 +55,8 @@ data RemoteA a = Remote {
-- Some remotes can check hasKey without an expensive network
-- operation.
hasKeyCheap :: Bool,
-- Some remotes can provide additional details for whereis.
whereisKey :: Maybe (Key -> a [String]),
-- a Remote can have a persistent configuration store
config :: Maybe RemoteConfig,
-- git configuration for the remote

1
debian/changelog vendored
View file

@ -24,6 +24,7 @@ git-annex (3.20120124) UNRELEASED; urgency=low
its head), and records the size in the key.
* Fixed to use the strict state monad, to avoid leaking all kinds of memory
due to lazy state update thunks when adding/fixing many files.
* whereis: Prints the urls of files that the web special remote knows about.
-- Joey Hess <joeyh@debian.org> Tue, 24 Jan 2012 16:21:55 -0400