examinekey: Added a "file" format variable

For consistency with find, and for easier scripting.
This commit is contained in:
Joey Hess 2020-11-16 09:56:32 -04:00
parent 21ab496f6b
commit 5a8d01f63e
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
6 changed files with 25 additions and 10 deletions

View file

@ -1,3 +1,10 @@
git-annex (8.20201117) UNRELEASED; urgency=medium
* examinekey: Added a "file" format variable for consistency with find,
and for easier scripting.
-- Joey Hess <id@joeyh.name> Mon, 16 Nov 2020 09:38:32 -0400
git-annex (8.20201116) upstream; urgency=medium git-annex (8.20201116) upstream; urgency=medium
* move: Fix a regression in the last release that made move --to not * move: Fix a regression in the last release that made move --to not

View file

@ -9,7 +9,7 @@ module Command.ExamineKey where
import Command import Command
import qualified Utility.Format import qualified Utility.Format
import Command.Find (parseFormatOption, showFormatted, keyVars) import Command.Find (parseFormatOption, showFormatted, formatVars)
import Annex.Link import Annex.Link
import Backend import Backend
import Types.Backend import Types.Backend
@ -57,7 +57,7 @@ run o _ input = do
showFormatted (format o) (serializeKey' k) $ showFormatted (format o) (serializeKey' k) $
[ ("objectpath", fromRawFilePath objectpath) [ ("objectpath", fromRawFilePath objectpath)
, ("objectpointer", fromRawFilePath objectpointer) , ("objectpointer", fromRawFilePath objectpointer)
] ++ keyVars k ] ++ formatVars k af
return True return True
where where
-- Parse the input, which is either a key, or in batch mode -- Parse the input, which is either a key, or in batch mode

View file

@ -75,7 +75,8 @@ seek o = do
start :: FindOptions -> SeekInput -> RawFilePath -> Key -> CommandStart start :: FindOptions -> SeekInput -> RawFilePath -> Key -> CommandStart
start o _ file key = startingCustomOutput key $ do start o _ file key = startingCustomOutput key $ do
showFormatted (formatOption o) file $ ("file", fromRawFilePath file) : keyVars key showFormatted (formatOption o) file
(formatVars key (AssociatedFile (Just file)))
next $ return True next $ return True
startKeys :: FindOptions -> (SeekInput, Key, ActionItem) -> CommandStart startKeys :: FindOptions -> (SeekInput, Key, ActionItem) -> CommandStart
@ -92,8 +93,9 @@ showFormatted format unformatted vars =
Utility.Format.format formatter $ Utility.Format.format formatter $
M.fromList vars M.fromList vars
keyVars :: Key -> [(String, String)] formatVars :: Key -> AssociatedFile -> [(String, String)]
keyVars key = formatVars key (AssociatedFile af) =
(maybe id (\f l -> (("file", fromRawFilePath f) : l)) af)
[ ("key", serializeKey key) [ ("key", serializeKey key)
, ("backend", decodeBS $ formatKeyVariety $ fromKey keyVariety key) , ("backend", decodeBS $ formatKeyVariety $ fromKey keyVariety key)
, ("bytesize", size show) , ("bytesize", size show)

View file

@ -95,10 +95,8 @@ perform o remotemap key ai = do
mapM_ (showRemoteUrls remotemap) urls mapM_ (showRemoteUrls remotemap) urls
Just formatter -> liftIO $ do Just formatter -> liftIO $ do
let vs = catMaybes let vs = Command.Find.formatVars key
[ fmap (("file",) . fromRawFilePath) (AssociatedFile (actionItemWorkTreeFile ai))
(actionItemWorkTreeFile ai)
] ++ Command.Find.keyVars key
let showformatted muuid murl = putStr $ let showformatted muuid murl = putStr $
Utility.Format.format formatter $ Utility.Format.format formatter $
M.fromList $ vs ++ catMaybes M.fromList $ vs ++ catMaybes

View file

@ -28,7 +28,8 @@ that can be determined purely by looking at the key.
These variables are also available for use in formats: ${key}, ${backend}, These variables are also available for use in formats: ${key}, ${backend},
${bytesize}, ${humansize}, ${keyname}, ${hashdirlower}, ${hashdirmixed}, ${bytesize}, ${humansize}, ${keyname}, ${hashdirlower}, ${hashdirmixed},
${mtime} (for the mtime field of a WORM key). ${mtime} (for the mtime field of a WORM key), ${file} (when a filename is
provided to examinekey).
Also, '\\n' is a newline, '\\000' is a NULL, etc. Also, '\\n' is a newline, '\\000' is a NULL, etc.

View file

@ -0,0 +1,7 @@
[[!comment format=mdwn
username="joey"
subject="""comment 6"""
date="2020-11-16T13:52:12Z"
content="""
Good idea, I added ${file}
"""]]