safe output to terminal for calckey inprogress and lookupkey

These are quite low-level, but still there is no point in displaying
escape sequences that have been embedded in a key to the terminal.

I think these are the only remaining commands that didn't use safe
output, except for cases where git-annex is speaking a protocol to
itself.

Sponsored-by: Kevin Mueller on Patreon
This commit is contained in:
Joey Hess 2023-04-12 14:03:44 -04:00
parent a576fc3b12
commit 3346aa9659
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
4 changed files with 24 additions and 12 deletions

View file

@ -6,7 +6,9 @@ git-annex (10.20230408) UNRELEASED; urgency=medium
characters as-is in filenames. characters as-is in filenames.
* Control characters in non-filename data coming from the repository or * Control characters in non-filename data coming from the repository or
other possible untrusted sources are filtered out of the display of many other possible untrusted sources are filtered out of the display of many
commands. commands. When the command output is intended for use in scripting,
control characters are only filtered out when displaying to the
terminal.
* find, findkeys, examinekey: When outputting to a terminal and --format * find, findkeys, examinekey: When outputting to a terminal and --format
is not used, quote unusual characters. is not used, quote unusual characters.
(Similar to the behavior of GNU find.) (Similar to the behavior of GNU find.)

View file

@ -11,6 +11,8 @@ import Command
import Backend (genKey, defaultBackend) import Backend (genKey, defaultBackend)
import Types.KeySource import Types.KeySource
import Utility.Metered import Utility.Metered
import Utility.Terminal
import Utility.SafeOutput
cmd :: Command cmd :: Command
cmd = noCommit $ noMessages $ dontCheck repoExists $ cmd = noCommit $ noMessages $ dontCheck repoExists $
@ -23,7 +25,9 @@ cmd = noCommit $ noMessages $ dontCheck repoExists $
run :: () -> SeekInput -> String -> Annex Bool run :: () -> SeekInput -> String -> Annex Bool
run _ _ file = tryNonAsync (genKey ks nullMeterUpdate =<< defaultBackend) >>= \case run _ _ file = tryNonAsync (genKey ks nullMeterUpdate =<< defaultBackend) >>= \case
Right (k, _) -> do Right (k, _) -> do
liftIO $ putStrLn $ serializeKey k IsTerminal isterminal <- liftIO $ checkIsTerminal stdout
let sk = serializeKey k
liftIO $ putStrLn $ if isterminal then safeOutput sk else sk
return True return True
Left _err -> return False Left _err -> return False
where where

View file

@ -9,6 +9,8 @@ module Command.Inprogress where
import Command import Command
import Annex.Transfer import Annex.Transfer
import Utility.Terminal
import Utility.SafeOutput
import qualified Data.Set as S import qualified Data.Set as S
@ -32,14 +34,14 @@ seek o = do
ts <- map (transferKey . fst) <$> getTransfers ts <- map (transferKey . fst) <$> getTransfers
case keyOptions o of case keyOptions o of
Just WantAllKeys -> Just WantAllKeys ->
forM_ ts $ commandAction . start' forM_ ts $ commandAction . (start' isterminal)
Just (WantSpecificKey k) Just (WantSpecificKey k)
| k `elem` ts -> commandAction (start' k) | k `elem` ts -> commandAction (start' isterminal k)
| otherwise -> commandAction stop | otherwise -> commandAction stop
_ -> do _ -> do
let s = S.fromList ts let s = S.fromList ts
let seeker = AnnexedFileSeeker let seeker = AnnexedFileSeeker
{ startAction = start s { startAction = start isterminal s
, checkContentPresent = Nothing , checkContentPresent = Nothing
, usesLocationLog = False , usesLocationLog = False
} }
@ -48,14 +50,14 @@ seek o = do
where where
ww = WarnUnmatchLsFiles ww = WarnUnmatchLsFiles
start :: S.Set Key -> SeekInput -> RawFilePath -> Key -> CommandStart start :: IsTerminal -> S.Set Key -> SeekInput -> RawFilePath -> Key -> CommandStart
start s _si _file k start isterminal s _si _file k
| S.member k s = start' k | S.member k s = start' isterminal k
| otherwise = stop | otherwise = stop
start' :: Key -> CommandStart start' :: IsTerminal -> Key -> CommandStart
start' k = startingCustomOutput k $ do start' (IsTerminal isterminal) k = startingCustomOutput k $ do
tmpf <- fromRawFilePath <$> fromRepo (gitAnnexTmpObjectLocation k) tmpf <- fromRawFilePath <$> fromRepo (gitAnnexTmpObjectLocation k)
whenM (liftIO $ doesFileExist tmpf) $ whenM (liftIO $ doesFileExist tmpf) $
liftIO $ putStrLn tmpf liftIO $ putStrLn (if isterminal then safeOutput tmpf else tmpf)
next $ return True next $ return True

View file

@ -10,6 +10,8 @@ module Command.LookupKey where
import Command import Command
import Annex.CatFile import Annex.CatFile
import qualified Git.LsFiles import qualified Git.LsFiles
import Utility.Terminal
import Utility.SafeOutput
cmd :: Command cmd :: Command
cmd = notBareRepo $ noCommit $ noMessages $ cmd = notBareRepo $ noCommit $ noMessages $
@ -23,7 +25,9 @@ run _ _ file = seekSingleGitFile file >>= \case
Nothing -> return False Nothing -> return False
Just file' -> catKeyFile file' >>= \case Just file' -> catKeyFile file' >>= \case
Just k -> do Just k -> do
liftIO $ putStrLn $ serializeKey k IsTerminal isterminal <- liftIO $ checkIsTerminal stdout
let sk = serializeKey k
liftIO $ putStrLn $ if isterminal then safeOutput sk else sk
return True return True
Nothing -> return False Nothing -> return False