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:
Joey Hess 2023-04-12 13:48:21 -04:00
parent c50aa21d5f
commit a576fc3b12
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
7 changed files with 61 additions and 42 deletions

View file

@ -10,6 +10,8 @@ module Annex.UntrustedFilePath where
import Data.Char
import System.FilePath
import Utility.SafeOutput
{- 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
- sane FilePath.
@ -55,10 +57,7 @@ sanitizeLeadingFilePathCharacter s = s
controlCharacterInFilePath :: FilePath -> Bool
controlCharacterInFilePath = any (not . safechar)
where
safechar c
| not (isControl c) = True
| c == '\t' = True
| otherwise = False
safechar c = safeOutputChar c && c /= '\n'
{- ../ is a path traversal, no matter where it appears.
-

View file

@ -16,7 +16,7 @@ import Annex.Link
import Backend
import Types.Backend
import Types.Key
import Utility.SafeOutput
import Utility.Terminal
import Data.Char
import qualified Data.ByteString as B

View file

@ -19,7 +19,7 @@ import Types.Key
import Git.FilePath
import qualified Utility.Format
import Utility.DataUnits
import Utility.SafeOutput
import Utility.Terminal
cmd :: Command
cmd = withAnnexOptions [annexedMatchingOptions] $ mkCommand $

View file

@ -10,7 +10,7 @@ module Command.FindKeys where
import Command
import qualified Command.Find
import qualified Utility.Format
import Utility.SafeOutput
import Utility.Terminal
cmd :: Command
cmd = withAnnexOptions [keyMatchingOptions] $ Command.Find.mkCommand $

View file

@ -11,55 +11,27 @@
module Utility.SafeOutput (
safeOutput,
IsTerminal(..),
checkIsTerminal,
safeOutputChar,
) 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
instance SafeOutputtable String where
safeOutput = filter safeChar
safeOutput = filter safeOutputChar
instance SafeOutputtable S.ByteString where
safeOutput = S.filter (safeChar . chr . fromIntegral)
safeOutput = S.filter (safeOutputChar . chr . fromIntegral)
safeChar :: Char -> Bool
safeChar c
safeOutputChar :: Char -> Bool
safeOutputChar c
| not (isControl c) = True
| c == '\n' = True
| c == '\t' = True
| c == '\DEL' = False
| ord c > 31 = True
| 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
View 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

View file

@ -1144,6 +1144,7 @@ Executable git-annex
Utility.SshHost
Utility.Su
Utility.SystemDirectory
Utility.Terminal
Utility.TimeStamp
Utility.TList
Utility.Tense