whereis: Added --format option.

One way this can be used is to remove all urls for some website that went
away:

git-annex whereis --format '${file} ${url}\0' | \
	grep -z whatever.com | git-annex rmurl --batch -z

Combining ${url} and ${uuid} is a bit of a combinatorial explosion.
It didn't seem worth only outputting a uuid alongside an url belonging
to it, so each uuid is output beside each url.
This commit is contained in:
Joey Hess 2020-05-19 16:01:02 -04:00
parent 30ac015b79
commit d7c7245438
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
3 changed files with 84 additions and 17 deletions

View file

@ -27,6 +27,7 @@ git-annex (8.20200502) UNRELEASED; urgency=medium
* Display a warning message when asked to operate on a file inside a * Display a warning message when asked to operate on a file inside a
directory that's a symbolic link to elsewhere. directory that's a symbolic link to elsewhere.
* When accessing a remote fails, always display a reason why. * When accessing a remote fails, always display a reason why.
* whereis: Added --format option.
-- Joey Hess <id@joeyh.name> Mon, 04 May 2020 12:46:11 -0400 -- Joey Hess <id@joeyh.name> Mon, 04 May 2020 12:46:11 -0400

View file

@ -1,10 +1,12 @@
{- git-annex command {- git-annex command
- -
- Copyright 2010-2016 Joey Hess <id@joeyh.name> - Copyright 2010-2020 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE TupleSections #-}
module Command.Whereis where module Command.Whereis where
import Command import Command
@ -13,6 +15,9 @@ import Logs.Trust
import Logs.Web import Logs.Web
import Remote.Web (getWebUrls) import Remote.Web (getWebUrls)
import Annex.UUID import Annex.UUID
import qualified Utility.Format
import qualified Command.Find
import Types.ActionItem
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Vector as V import qualified Data.Vector as V
@ -27,6 +32,7 @@ data WhereisOptions = WhereisOptions
{ whereisFiles :: CmdParams { whereisFiles :: CmdParams
, keyOptions :: Maybe KeyOptions , keyOptions :: Maybe KeyOptions
, batchOption :: BatchMode , batchOption :: BatchMode
, formatOption :: Maybe Utility.Format.Format
} }
optParser :: CmdParamsDesc -> Parser WhereisOptions optParser :: CmdParamsDesc -> Parser WhereisOptions
@ -34,40 +40,74 @@ optParser desc = WhereisOptions
<$> cmdParams desc <$> cmdParams desc
<*> optional parseKeyOptions <*> optional parseKeyOptions
<*> parseBatchOption <*> parseBatchOption
<*> optional parseFormatOption
parseFormatOption :: Parser Utility.Format.Format
parseFormatOption = option (Utility.Format.gen <$> str)
( long "format" <> metavar paramFormat
<> help "control format of output"
)
seek :: WhereisOptions -> CommandSeek seek :: WhereisOptions -> CommandSeek
seek o = do seek o = do
m <- remoteMap id m <- remoteMap id
let go = whenAnnexed $ start m let go = whenAnnexed $ start o m
case batchOption o of case batchOption o of
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath) Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
NoBatch -> NoBatch ->
withKeyOptions (keyOptions o) False withKeyOptions (keyOptions o) False
(commandAction . startKeys m) (commandAction . startKeys o m)
(withFilesInGit (commandAction . go)) (withFilesInGit (commandAction . go))
=<< workTreeItems (whereisFiles o) =<< workTreeItems (whereisFiles o)
start :: M.Map UUID Remote -> RawFilePath -> Key -> CommandStart start :: WhereisOptions -> M.Map UUID Remote -> RawFilePath -> Key -> CommandStart
start remotemap file key = startKeys remotemap (key, mkActionItem (key, afile)) start o remotemap file key =
startKeys o remotemap (key, mkActionItem (key, afile))
where where
afile = AssociatedFile (Just file) afile = AssociatedFile (Just file)
startKeys :: M.Map UUID Remote -> (Key, ActionItem) -> CommandStart startKeys :: WhereisOptions -> M.Map UUID Remote -> (Key, ActionItem) -> CommandStart
startKeys remotemap (key, ai) = starting "whereis" ai $ perform remotemap key startKeys o remotemap (key, ai)
| isJust (formatOption o) = startingCustomOutput ai go
| otherwise = starting "whereis" ai go
where
go = perform o remotemap key ai
perform :: M.Map UUID Remote -> Key -> CommandPerform perform :: WhereisOptions -> M.Map UUID Remote -> Key -> ActionItem -> CommandPerform
perform remotemap key = do perform o remotemap key ai = do
locations <- keyLocations key locations <- keyLocations key
urls <- getUUIDUrls key locations remotemap urls <- getUUIDUrls key locations remotemap
(untrustedlocations, safelocations) <- trustPartition UnTrusted locations (untrustedlocations, safelocations) <- trustPartition UnTrusted locations
let num = length safelocations case formatOption o of
showNote $ show num ++ " " ++ copiesplural num Nothing -> do
pp <- ppwhereis "whereis" safelocations urls let num = length safelocations
unless (null safelocations) $ showLongNote pp showNote $ show num ++ " " ++ copiesplural num
pp' <- ppwhereis "untrusted" untrustedlocations urls pp <- ppwhereis "whereis" safelocations urls
unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp' unless (null safelocations) $ showLongNote pp
pp' <- ppwhereis "untrusted" untrustedlocations urls
mapM_ (showRemoteUrls remotemap) urls unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp'
mapM_ (showRemoteUrls remotemap) urls
Just formatter -> liftIO $ do
let vs = catMaybes
[ fmap (("file",) . fromRawFilePath)
(actionItemWorkTreeFile ai)
] ++ Command.Find.keyVars key
let showformatted muuid murl = putStr $
Utility.Format.format formatter $
M.fromList $ vs ++ catMaybes
[ fmap ("uuid",) muuid
, fmap ("url",) murl
]
let showformatted' muuid
| Utility.Format.formatContainsVar "url" formatter =
forM_ (concatMap snd urls) $
showformatted muuid . Just
| otherwise = showformatted muuid Nothing
if Utility.Format.formatContainsVar "uuid" formatter
then forM_ locations $
showformatted' . Just . fromUUID
else showformatted' Nothing
if null safelocations then stop else next $ return True if null safelocations then stop else next $ return True
where where

View file

@ -71,6 +71,32 @@ received from remotes.
Messages that would normally be output to standard error are included in Messages that would normally be output to standard error are included in
the json instead. the json instead.
* `--format=value`
Use custom output formatting.
The value is a format string, in which '${var}' is expanded to the
value of a variable. To right-justify a variable with whitespace,
use '${var;width}' ; to left-justify a variable, use '${var;-width}';
to escape unusual characters in a variable, use '${escaped_var}'
These variables are available for use in formats: file, key, uuid,
url, backend, bytesize, humansize, keyname, hashdirlower, hashdirmixed,
mtime (for the mtime field of a WORM key).
Also, '\\n' is a newline, '\\000' is a NULL, etc.
When the format contains the uuid variable, it will be expanded in turn
for each repository that contains the file content. For example,
with --format="${file} ${uuid}\\n", output will look like:
foo 00000000-0000-0000-0000-000000000001
foo a7f7ddd0-9a08-11ea-ab66-8358e4209d30
bar a7f7ddd0-9a08-11ea-ab66-8358e4209d30
The same applies when the url variable is used and a file has multiple
recorded urls.
# SEE ALSO # SEE ALSO
[[git-annex]](1) [[git-annex]](1)