fix mojibake reversion in display of utf8
When displaying a ByteString like "💕", safeOutput operates on
individual bytes like "\240\159\146\149" and isControl '\146' = True,
so it got truncated to just "\240".
So, only treat the low control characters, and DEL, as control
characters.
Also split Utility.Terminal out of Utility.SafeOutput. The latter needs
win32, but Utility.SafeOutput is used by Control.Exception, which is
used by Setup.
Sponsored-by: Nicholas Golder-Manning on Patreon
This commit is contained in:
parent
c50aa21d5f
commit
a576fc3b12
7 changed files with 61 additions and 42 deletions
|
@ -10,6 +10,8 @@ module Annex.UntrustedFilePath where
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
|
import Utility.SafeOutput
|
||||||
|
|
||||||
{- Given a string that we'd like to use as the basis for FilePath, but that
|
{- Given a string that we'd like to use as the basis for FilePath, but that
|
||||||
- was provided by a third party and is not to be trusted, returns the closest
|
- was provided by a third party and is not to be trusted, returns the closest
|
||||||
- sane FilePath.
|
- sane FilePath.
|
||||||
|
@ -55,10 +57,7 @@ sanitizeLeadingFilePathCharacter s = s
|
||||||
controlCharacterInFilePath :: FilePath -> Bool
|
controlCharacterInFilePath :: FilePath -> Bool
|
||||||
controlCharacterInFilePath = any (not . safechar)
|
controlCharacterInFilePath = any (not . safechar)
|
||||||
where
|
where
|
||||||
safechar c
|
safechar c = safeOutputChar c && c /= '\n'
|
||||||
| not (isControl c) = True
|
|
||||||
| c == '\t' = True
|
|
||||||
| otherwise = False
|
|
||||||
|
|
||||||
{- ../ is a path traversal, no matter where it appears.
|
{- ../ is a path traversal, no matter where it appears.
|
||||||
-
|
-
|
||||||
|
|
|
@ -16,7 +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 Utility.Terminal
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
|
|
|
@ -19,7 +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
|
import Utility.Terminal
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = withAnnexOptions [annexedMatchingOptions] $ mkCommand $
|
cmd = withAnnexOptions [annexedMatchingOptions] $ mkCommand $
|
||||||
|
|
|
@ -10,7 +10,7 @@ module Command.FindKeys where
|
||||||
import Command
|
import Command
|
||||||
import qualified Command.Find
|
import qualified Command.Find
|
||||||
import qualified Utility.Format
|
import qualified Utility.Format
|
||||||
import Utility.SafeOutput
|
import Utility.Terminal
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = withAnnexOptions [keyMatchingOptions] $ Command.Find.mkCommand $
|
cmd = withAnnexOptions [keyMatchingOptions] $ Command.Find.mkCommand $
|
||||||
|
|
|
@ -11,55 +11,27 @@
|
||||||
|
|
||||||
module Utility.SafeOutput (
|
module Utility.SafeOutput (
|
||||||
safeOutput,
|
safeOutput,
|
||||||
IsTerminal(..),
|
safeOutputChar,
|
||||||
checkIsTerminal,
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import qualified Data.ByteString as S
|
import qualified Data.ByteString as S
|
||||||
import System.IO
|
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
|
||||||
|
|
||||||
instance SafeOutputtable String where
|
instance SafeOutputtable String where
|
||||||
safeOutput = filter safeChar
|
safeOutput = filter safeOutputChar
|
||||||
|
|
||||||
instance SafeOutputtable S.ByteString where
|
instance SafeOutputtable S.ByteString where
|
||||||
safeOutput = S.filter (safeChar . chr . fromIntegral)
|
safeOutput = S.filter (safeOutputChar . chr . fromIntegral)
|
||||||
|
|
||||||
safeChar :: Char -> Bool
|
safeOutputChar :: Char -> Bool
|
||||||
safeChar c
|
safeOutputChar c
|
||||||
| not (isControl c) = True
|
| not (isControl c) = True
|
||||||
| c == '\n' = True
|
| c == '\n' = True
|
||||||
| c == '\t' = True
|
| c == '\t' = True
|
||||||
|
| c == '\DEL' = False
|
||||||
|
| ord c > 31 = True
|
||||||
| otherwise = False
|
| otherwise = False
|
||||||
|
|
||||||
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
|
|
||||||
|
|
47
Utility/Terminal.hs
Normal file
47
Utility/Terminal.hs
Normal file
|
@ -0,0 +1,47 @@
|
||||||
|
{- Determining if output is to a terminal.
|
||||||
|
-
|
||||||
|
- Copyright 2023 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- License: BSD-2-clause
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
||||||
|
|
||||||
|
module Utility.Terminal (
|
||||||
|
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
|
||||||
|
|
||||||
|
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
|
|
@ -1144,6 +1144,7 @@ Executable git-annex
|
||||||
Utility.SshHost
|
Utility.SshHost
|
||||||
Utility.Su
|
Utility.Su
|
||||||
Utility.SystemDirectory
|
Utility.SystemDirectory
|
||||||
|
Utility.Terminal
|
||||||
Utility.TimeStamp
|
Utility.TimeStamp
|
||||||
Utility.TList
|
Utility.TList
|
||||||
Utility.Tense
|
Utility.Tense
|
||||||
|
|
Loading…
Reference in a new issue