whereis: Prints the urls of files that the web special remote knows about.
This commit is contained in:
parent
8fbc529d68
commit
cb631ce518
12 changed files with 37 additions and 12 deletions
|
@ -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
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue