filter out control characters in warning messages

Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.

Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.

When json is being output, no quoting is done, since json gets its own
quoting.

This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.

Sponsored-by: Brett Eisenberg on Patreon
This commit is contained in:
Joey Hess 2023-04-10 14:47:32 -04:00
parent 007e302637
commit 3290a09a70
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
75 changed files with 259 additions and 229 deletions

View file

@ -5,7 +5,7 @@
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE CPP, OverloadedStrings #-}
module Assistant.Threads.Committer where
@ -433,8 +433,8 @@ safeToAdd lockdowndir lockdownconfig havelsof delayadd pending inprocess = do
canceladd (InProcessAddChange { lockedDown = ld }) = do
let ks = keySource ld
warning $ fromRawFilePath (keyFilename ks)
++ " still has writers, not adding"
warning $ QuotedPath (keyFilename ks)
<> " still has writers, not adding"
-- remove the hard link
when (contentLocation ks /= keyFilename ks) $
void $ liftIO $ tryIO $ removeFile $ fromRawFilePath $ contentLocation ks

View file

@ -74,7 +74,7 @@ dbusThread urlrenderer = do
onerr :: E.SomeException -> Assistant ()
onerr e = do
liftAnnex $
warning $ "dbus failed; falling back to mtab polling (" ++ show e ++ ")"
warning $ UnquotedString $ "dbus failed; falling back to mtab polling (" ++ show e ++ ")"
pollingThread urlrenderer
{- Examine the list of services connected to dbus, to see if there

View file

@ -78,7 +78,7 @@ dbusThread = do
sendRemoteControl RESUME
onerr e _ = do
liftAnnex $
warning $ "lost dbus connection; falling back to polling (" ++ show e ++ ")"
warning $ UnquotedString $ "lost dbus connection; falling back to polling (" ++ show e ++ ")"
{- Wait, in hope that dbus will come back -}
liftIO $ threadDelaySeconds (Seconds 60)

View file

@ -5,6 +5,8 @@
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings #-}
module Assistant.Threads.PairListener where
import Assistant.Common
@ -49,7 +51,7 @@ pairListenerThread urlrenderer = namedThread "PairListener" $ do
debug ["ignoring message that looped back"]
go reqs cache sock
(_, _, False, _) -> do
liftAnnex $ warning $
liftAnnex $ warning $ UnquotedString $
"illegal control characters in pairing message; ignoring (" ++ show (pairMsgData m) ++ ")"
go reqs cache sock
-- PairReq starts a pairing process, so a

View file

@ -127,7 +127,7 @@ sanityCheckerDailyThread urlrenderer = namedThread "SanityCheckerDaily" $ foreve
return r
showerr e = do
liftAnnex $ warning $ show e
liftAnnex $ warning $ UnquotedString $ show e
return False
{- Only run one check per day, from the time of the last check. -}
@ -198,7 +198,7 @@ dailyCheck urlrenderer = do
toonew timestamp now = now < (realToFrac (timestamp + slop) :: POSIXTime)
slop = fromIntegral tenMinutes
insanity msg = do
liftAnnex $ warning msg
liftAnnex $ warning (UnquotedString msg)
void $ addAlert $ sanityCheckFixAlert msg
addsymlink file s = do
Watcher.runHandler Watcher.onAddSymlink file s

View file

@ -184,7 +184,7 @@ runHandler :: Handler -> FilePath -> Maybe FileStatus -> Assistant ()
runHandler handler file filestatus = void $ do
r <- tryIO <~> handler (normalize file) filestatus
case r of
Left e -> liftAnnex $ warning $ show e
Left e -> liftAnnex $ warning $ UnquotedString $ show e
Right Nothing -> noop
Right (Just change) -> recordChange change
where
@ -371,6 +371,6 @@ onDelDir dir _ = do
{- Called when there's an error with inotify or kqueue. -}
onErr :: Handler
onErr msg _ = do
liftAnnex $ warning msg
liftAnnex $ warning (UnquotedString msg)
void $ addAlert $ warningAlert "watcher" msg
noChange