find, findkeys, examinekey: escape output to terminal when --format is not used
Note that filenames are not quoted, only escaped. This is to match the output of --format with escaping. Sponsored-by: Lawrence Brogan on Patreon
This commit is contained in:
parent
df6f9f1ee8
commit
afa5b883dc
10 changed files with 85 additions and 28 deletions
|
@ -7,6 +7,9 @@ git-annex (10.20230408) UNRELEASED; urgency=medium
|
||||||
* Control characters in information coming from the repository or other
|
* Control characters in information coming from the repository or other
|
||||||
possible untrusted sources are filtered out of the display of many
|
possible untrusted sources are filtered out of the display of many
|
||||||
commands.
|
commands.
|
||||||
|
* find, findkeys, examinekey: When outputting to a terminal and --format
|
||||||
|
is not used, quote unusual characters.
|
||||||
|
(Similar to the behavior of GNU find.)
|
||||||
* addurl --preserve-filename now rejects filenames that contain other
|
* addurl --preserve-filename now rejects filenames that contain other
|
||||||
control characters, besides the escape sequences it already rejected.
|
control characters, besides the escape sequences it already rejected.
|
||||||
|
|
||||||
|
|
|
@ -5,6 +5,8 @@
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module Command.ExamineKey where
|
module Command.ExamineKey where
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
|
@ -14,6 +16,7 @@ import Annex.Link
|
||||||
import Backend
|
import Backend
|
||||||
import Types.Backend
|
import Types.Backend
|
||||||
import Types.Key
|
import Types.Key
|
||||||
|
import Utility.SafeOutput
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
|
@ -54,7 +57,8 @@ run o _ input = do
|
||||||
|
|
||||||
objectpath <- calcRepo $ gitAnnexLocation k
|
objectpath <- calcRepo $ gitAnnexLocation k
|
||||||
let objectpointer = formatPointer k
|
let objectpointer = formatPointer k
|
||||||
showFormatted (format o) (serializeKey' k) $
|
isterminal <- liftIO $ checkIsTerminal stdout
|
||||||
|
showFormatted isterminal (format o) (serializeKey' k) $
|
||||||
[ ("objectpath", fromRawFilePath objectpath)
|
[ ("objectpath", fromRawFilePath objectpath)
|
||||||
, ("objectpointer", fromRawFilePath objectpointer)
|
, ("objectpointer", fromRawFilePath objectpointer)
|
||||||
] ++ formatVars k af
|
] ++ formatVars k af
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex command
|
{- git-annex command
|
||||||
-
|
-
|
||||||
- Copyright 2010-2018 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2023 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -19,6 +19,7 @@ import Types.Key
|
||||||
import Git.FilePath
|
import Git.FilePath
|
||||||
import qualified Utility.Format
|
import qualified Utility.Format
|
||||||
import Utility.DataUnits
|
import Utility.DataUnits
|
||||||
|
import Utility.SafeOutput
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = withAnnexOptions [annexedMatchingOptions] $ mkCommand $
|
cmd = withAnnexOptions [annexedMatchingOptions] $ mkCommand $
|
||||||
|
@ -60,14 +61,15 @@ seek :: FindOptions -> CommandSeek
|
||||||
seek o = do
|
seek o = do
|
||||||
unless (isJust (keyOptions o)) $
|
unless (isJust (keyOptions o)) $
|
||||||
checkNotBareRepo
|
checkNotBareRepo
|
||||||
|
isterminal <- liftIO $ checkIsTerminal stdout
|
||||||
seeker <- contentPresentUnlessLimited $ AnnexedFileSeeker
|
seeker <- contentPresentUnlessLimited $ AnnexedFileSeeker
|
||||||
{ startAction = start o
|
{ startAction = start o isterminal
|
||||||
, checkContentPresent = Nothing
|
, checkContentPresent = Nothing
|
||||||
, usesLocationLog = False
|
, usesLocationLog = False
|
||||||
}
|
}
|
||||||
case batchOption o of
|
case batchOption o of
|
||||||
NoBatch -> withKeyOptions (keyOptions o) False seeker
|
NoBatch -> withKeyOptions (keyOptions o) False seeker
|
||||||
(commandAction . startKeys o)
|
(commandAction . startKeys o isterminal)
|
||||||
(withFilesInGitAnnex ww seeker)
|
(withFilesInGitAnnex ww seeker)
|
||||||
=<< workTreeItems ww (findThese o)
|
=<< workTreeItems ww (findThese o)
|
||||||
Batch fmt -> batchOnly (keyOptions o) (findThese o) $
|
Batch fmt -> batchOnly (keyOptions o) (findThese o) $
|
||||||
|
@ -86,22 +88,25 @@ contentPresentUnlessLimited s = do
|
||||||
else Just True
|
else Just True
|
||||||
}
|
}
|
||||||
|
|
||||||
start :: FindOptions -> SeekInput -> RawFilePath -> Key -> CommandStart
|
start :: FindOptions -> IsTerminal -> SeekInput -> RawFilePath -> Key -> CommandStart
|
||||||
start o _ file key = startingCustomOutput key $ do
|
start o isterminal _ file key = startingCustomOutput key $ do
|
||||||
showFormatted (formatOption o) file
|
showFormatted isterminal (formatOption o) file
|
||||||
(formatVars key (AssociatedFile (Just file)))
|
(formatVars key (AssociatedFile (Just file)))
|
||||||
next $ return True
|
next $ return True
|
||||||
|
|
||||||
startKeys :: FindOptions -> (SeekInput, Key, ActionItem) -> CommandStart
|
startKeys :: FindOptions -> IsTerminal -> (SeekInput, Key, ActionItem) -> CommandStart
|
||||||
startKeys o (si, key, ActionItemBranchFilePath (BranchFilePath _ topf) _) =
|
startKeys o isterminal (si, key, ActionItemBranchFilePath (BranchFilePath _ topf) _) =
|
||||||
start o si (getTopFilePath topf) key
|
start o isterminal si (getTopFilePath topf) key
|
||||||
startKeys _ _ = stop
|
startKeys _ _ _ = stop
|
||||||
|
|
||||||
showFormatted :: Maybe Utility.Format.Format -> S.ByteString -> [(String, String)] -> Annex ()
|
showFormatted :: IsTerminal -> Maybe Utility.Format.Format -> S.ByteString -> [(String, String)] -> Annex ()
|
||||||
showFormatted format unformatted vars =
|
showFormatted (IsTerminal isterminal) format unformatted vars =
|
||||||
unlessM (showFullJSON $ JSONChunk vars) $
|
unlessM (showFullJSON $ JSONChunk vars) $
|
||||||
case format of
|
case format of
|
||||||
Nothing -> liftIO $ S8.putStrLn unformatted
|
Nothing -> do
|
||||||
|
liftIO $ S8.putStrLn $ if isterminal
|
||||||
|
then Utility.Format.escapedFormat unformatted
|
||||||
|
else unformatted
|
||||||
Just formatter -> liftIO $ putStr $
|
Just formatter -> liftIO $ putStr $
|
||||||
Utility.Format.format formatter $
|
Utility.Format.format formatter $
|
||||||
M.fromList vars
|
M.fromList vars
|
||||||
|
|
|
@ -8,8 +8,9 @@
|
||||||
module Command.FindKeys where
|
module Command.FindKeys where
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Utility.Format
|
|
||||||
import qualified Command.Find
|
import qualified Command.Find
|
||||||
|
import qualified Utility.Format
|
||||||
|
import Utility.SafeOutput
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = withAnnexOptions [keyMatchingOptions] $ Command.Find.mkCommand $
|
cmd = withAnnexOptions [keyMatchingOptions] $ Command.Find.mkCommand $
|
||||||
|
@ -26,22 +27,23 @@ optParser _ = FindKeysOptions
|
||||||
|
|
||||||
seek :: FindKeysOptions -> CommandSeek
|
seek :: FindKeysOptions -> CommandSeek
|
||||||
seek o = do
|
seek o = do
|
||||||
|
isterminal <- liftIO $ checkIsTerminal stdout
|
||||||
seeker <- Command.Find.contentPresentUnlessLimited $ AnnexedFileSeeker
|
seeker <- Command.Find.contentPresentUnlessLimited $ AnnexedFileSeeker
|
||||||
{ checkContentPresent = Nothing
|
{ checkContentPresent = Nothing
|
||||||
, usesLocationLog = False
|
, usesLocationLog = False
|
||||||
-- startAction is not actually used since this
|
-- startAction is not actually used since this
|
||||||
-- is not used to seek files
|
-- is not used to seek files
|
||||||
, startAction = \_ _ key -> start' o key
|
, startAction = \_ _ key -> start' o isterminal key
|
||||||
}
|
}
|
||||||
withKeyOptions (Just WantAllKeys) False seeker
|
withKeyOptions (Just WantAllKeys) False seeker
|
||||||
(commandAction . start o)
|
(commandAction . start o isterminal)
|
||||||
(const noop) (WorkTreeItems [])
|
(const noop) (WorkTreeItems [])
|
||||||
|
|
||||||
start :: FindKeysOptions -> (SeekInput, Key, ActionItem) -> CommandStart
|
start :: FindKeysOptions -> IsTerminal -> (SeekInput, Key, ActionItem) -> CommandStart
|
||||||
start o (_si, key, _ai) = start' o key
|
start o isterminal (_si, key, _ai) = start' o isterminal key
|
||||||
|
|
||||||
start' :: FindKeysOptions -> Key -> CommandStart
|
start' :: FindKeysOptions -> IsTerminal -> Key -> CommandStart
|
||||||
start' o key = startingCustomOutput key $ do
|
start' o isterminal key = startingCustomOutput key $ do
|
||||||
Command.Find.showFormatted (formatOption o) (serializeKey' key)
|
Command.Find.showFormatted isterminal (formatOption o) (serializeKey' key)
|
||||||
(Command.Find.formatVars key (AssociatedFile Nothing))
|
(Command.Find.formatVars key (AssociatedFile Nothing))
|
||||||
next $ return True
|
next $ return True
|
||||||
|
|
|
@ -17,7 +17,6 @@ import Remote.Web (getWebUrls)
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import qualified Utility.Format
|
import qualified Utility.Format
|
||||||
import qualified Command.Find
|
import qualified Command.Find
|
||||||
import Utility.SafeOutput
|
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Vector as V
|
import qualified Data.Vector as V
|
||||||
|
|
|
@ -9,6 +9,7 @@ module Utility.Format (
|
||||||
Format,
|
Format,
|
||||||
gen,
|
gen,
|
||||||
format,
|
format,
|
||||||
|
escapedFormat,
|
||||||
formatContainsVar,
|
formatContainsVar,
|
||||||
decode_c,
|
decode_c,
|
||||||
encode_c,
|
encode_c,
|
||||||
|
@ -53,7 +54,7 @@ format f vars = concatMap expand f
|
||||||
where
|
where
|
||||||
expand (Const s) = s
|
expand (Const s) = s
|
||||||
expand (Var name j esc)
|
expand (Var name j esc)
|
||||||
| esc = justify j $ decodeBS $ encode_c needescape $
|
| esc = justify j $ decodeBS $ escapedFormat $
|
||||||
encodeBS $ getvar name
|
encodeBS $ getvar name
|
||||||
| otherwise = justify j $ getvar name
|
| otherwise = justify j $ getvar name
|
||||||
getvar name = fromMaybe "" $ M.lookup name vars
|
getvar name = fromMaybe "" $ M.lookup name vars
|
||||||
|
@ -62,6 +63,10 @@ format f vars = concatMap expand f
|
||||||
justify (RightJustified i) s = pad i s ++ s
|
justify (RightJustified i) s = pad i s ++ s
|
||||||
pad i s = take (i - length s) spaces
|
pad i s = take (i - length s) spaces
|
||||||
spaces = repeat ' '
|
spaces = repeat ' '
|
||||||
|
|
||||||
|
escapedFormat :: S.ByteString -> S.ByteString
|
||||||
|
escapedFormat = encode_c needescape
|
||||||
|
where
|
||||||
needescape c = isUtf8Byte c ||
|
needescape c = isUtf8Byte c ||
|
||||||
isSpace (chr (fromIntegral c)) ||
|
isSpace (chr (fromIntegral c)) ||
|
||||||
c == fromIntegral (ord '"')
|
c == fromIntegral (ord '"')
|
||||||
|
|
|
@ -6,13 +6,25 @@
|
||||||
- License: BSD-2-clause
|
- License: BSD-2-clause
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
|
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
||||||
|
|
||||||
module Utility.SafeOutput (safeOutput) where
|
module Utility.SafeOutput (
|
||||||
|
safeOutput,
|
||||||
|
IsTerminal(..),
|
||||||
|
checkIsTerminal,
|
||||||
|
) where
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import qualified Data.ByteString as S
|
import qualified Data.ByteString as S
|
||||||
|
import System.IO
|
||||||
|
#ifdef mingw32_HOST_OS
|
||||||
|
import System.Win32.MinTTY (isMinTTYHandle)
|
||||||
|
import System.Win32.File
|
||||||
|
import System.Win32.Types
|
||||||
|
import Graphics.Win32.Misc
|
||||||
|
import Control.Exception
|
||||||
|
#endif
|
||||||
|
|
||||||
class SafeOutputtable t where
|
class SafeOutputtable t where
|
||||||
safeOutput :: t -> t
|
safeOutput :: t -> t
|
||||||
|
@ -22,3 +34,25 @@ instance SafeOutputtable String where
|
||||||
|
|
||||||
instance SafeOutputtable S.ByteString where
|
instance SafeOutputtable S.ByteString where
|
||||||
safeOutput = S.filter (not . isControl . chr . fromIntegral)
|
safeOutput = S.filter (not . isControl . chr . fromIntegral)
|
||||||
|
|
||||||
|
newtype IsTerminal = IsTerminal Bool
|
||||||
|
|
||||||
|
checkIsTerminal :: Handle -> IO IsTerminal
|
||||||
|
checkIsTerminal h = do
|
||||||
|
#ifndef mingw32_HOST_OS
|
||||||
|
b <- hIsTerminalDevice h
|
||||||
|
return (IsTerminal b)
|
||||||
|
#else
|
||||||
|
b <- hIsTerminalDevice h
|
||||||
|
if b
|
||||||
|
then return (IsTerminal b)
|
||||||
|
else do
|
||||||
|
h' <- getStdHandle sTD_OUTPUT_HANDLE
|
||||||
|
`catch` \(_ :: IOError) ->
|
||||||
|
return nullHANDLE
|
||||||
|
if h == nullHANDLE
|
||||||
|
then return (IsTerminal False)
|
||||||
|
else do
|
||||||
|
b' <- isMinTTYHandle h'
|
||||||
|
return (IsTerminal b)
|
||||||
|
#endif
|
||||||
|
|
|
@ -34,6 +34,9 @@ that can be determined purely by looking at the key.
|
||||||
|
|
||||||
Also, '\\n' is a newline, '\\000' is a NULL, etc.
|
Also, '\\n' is a newline, '\\000' is a NULL, etc.
|
||||||
|
|
||||||
|
The default output format is the same as `--format='${escapedkey}\\n'`
|
||||||
|
when outputting to the terminal, and otherwise `--format='${key}\\n'`
|
||||||
|
|
||||||
* `--json`
|
* `--json`
|
||||||
|
|
||||||
Enable JSON output. This is intended to be parsed by programs that use
|
Enable JSON output. This is intended to be parsed by programs that use
|
||||||
|
|
|
@ -50,7 +50,8 @@ finds files in the current directory and its subdirectories.
|
||||||
|
|
||||||
Also, '\\n' is a newline, '\\000' is a NULL, etc.
|
Also, '\\n' is a newline, '\\000' is a NULL, etc.
|
||||||
|
|
||||||
The default output format is the same as `--format='${file}\\n'`
|
The default output format is the same as `--format='${escaped_file}\\n'`
|
||||||
|
when outputting to the terminal, and otherwise `--format='${file}\\n'`
|
||||||
|
|
||||||
* `--json`
|
* `--json`
|
||||||
|
|
||||||
|
|
|
@ -45,7 +45,8 @@ Outputs a list of keys known to git-annex.
|
||||||
|
|
||||||
Also, '\\n' is a newline, '\\000' is a NULL, etc.
|
Also, '\\n' is a newline, '\\000' is a NULL, etc.
|
||||||
|
|
||||||
The default output format is the same as `--format='${key}\\n'`
|
The default output format is the same as `--format='${escapedkey}\\n'`
|
||||||
|
when outputting to the terminal, and otherwise `--format='${key}\\n'`
|
||||||
|
|
||||||
* `--json`
|
* `--json`
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue