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
|
@ -9,6 +9,7 @@ module Utility.Format (
|
|||
Format,
|
||||
gen,
|
||||
format,
|
||||
escapedFormat,
|
||||
formatContainsVar,
|
||||
decode_c,
|
||||
encode_c,
|
||||
|
@ -53,7 +54,7 @@ format f vars = concatMap expand f
|
|||
where
|
||||
expand (Const s) = s
|
||||
expand (Var name j esc)
|
||||
| esc = justify j $ decodeBS $ encode_c needescape $
|
||||
| esc = justify j $ decodeBS $ escapedFormat $
|
||||
encodeBS $ getvar name
|
||||
| otherwise = justify j $ getvar name
|
||||
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
|
||||
pad i s = take (i - length s) spaces
|
||||
spaces = repeat ' '
|
||||
|
||||
escapedFormat :: S.ByteString -> S.ByteString
|
||||
escapedFormat = encode_c needescape
|
||||
where
|
||||
needescape c = isUtf8Byte c ||
|
||||
isSpace (chr (fromIntegral c)) ||
|
||||
c == fromIntegral (ord '"')
|
||||
|
|
|
@ -6,13 +6,25 @@
|
|||
- License: BSD-2-clause
|
||||
-}
|
||||
|
||||
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
|
||||
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP #-}
|
||||
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
||||
|
||||
module Utility.SafeOutput (safeOutput) where
|
||||
module Utility.SafeOutput (
|
||||
safeOutput,
|
||||
IsTerminal(..),
|
||||
checkIsTerminal,
|
||||
) where
|
||||
|
||||
import Data.Char
|
||||
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
|
||||
safeOutput :: t -> t
|
||||
|
@ -22,3 +34,25 @@ instance SafeOutputtable String where
|
|||
|
||||
instance SafeOutputtable S.ByteString where
|
||||
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
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue