Skip to content

Commit

Permalink
sanitise control characters in message bodies
Browse files Browse the repository at this point in the history
Control characters in message bodies can result in UI corruption
(e.g. when horizontal tab characters occur).  It is also a security
issue (ANSI escapes causing undesired terminal behaviour).

Add a Text sanitisation function and use it when converting entities
for display.

There are most certainly other places in the UI we need to employ
it, and we should properly audit the codebase - perhaps even using
phantom types to taint unsanitised external data.  But this is a
starting point.

Also do a drive-by tidy-up of UI.Utils.

Fixes: #265
  • Loading branch information
frasertweedale authored and romanofski committed Mar 27, 2019
1 parent 7ad0ade commit a085315
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 5 deletions.
3 changes: 2 additions & 1 deletion src/Storage/ParsedMail.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import Data.MIME
import Error
import Storage.Notmuch (mailFilepath)
import Types (NotmuchMail, decodeLenient)
import UI.Utils (sanitise)

parseMail
:: (MonadError Error m, MonadIO m)
Expand Down Expand Up @@ -68,7 +69,7 @@ entityToBytes msg = either err Right (convert msg)
convert m = view body <$> view transferDecoded m

entityToText :: WireEntity -> T.Text
entityToText msg = either err (view body) $
entityToText msg = sanitise . either err (view body) $
view transferDecoded msg >>= view charsetDecoded
where
err :: EncodingError -> T.Text
Expand Down
31 changes: 27 additions & 4 deletions src/UI/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE RankNTypes #-}
-- This file is part of purebred
-- Copyright (C) 2017 Fraser Tweedale and Róman Joost
-- Copyright (C) 2017-2019 Fraser Tweedale and Róman Joost
--
-- purebred is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published by
Expand All @@ -14,17 +13,23 @@
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--

{-# LANGUAGE OverloadedStrings #-}

module UI.Utils
( titleize
, Titleize
, toggledItems
, selectedFiles
, takeFileName
, sanitise
) where
import Data.Text (Text, pack, unpack)

import Data.Char (chr, isControl, ord)
import Data.List (union)

import qualified Data.Text as T
import Data.Text (Text, pack, unpack)
import qualified System.FilePath as FP (takeFileName)
import Control.Lens
(folded, traversed, filtered, toListOf, view, _2)
Expand Down Expand Up @@ -68,3 +73,21 @@ instance Titleize Name where

instance Titleize ViewName where
titleize a = pack $ show a

-- | Convert or strip control characters from input.
--
-- * Tab (HT) is replaced with 8 spaces.
-- * Other C0 codes (except CR and LF) and DEL are replaced with
-- <https://en.wikipedia.org/wiki/Control_Pictures Control Pictures>
-- * C1 and all other control characters are replaced with
-- REPLACEMENT CHARACTER U+FFFD
--
sanitise :: T.Text -> T.Text
sanitise = T.map substControl . T.replace "\t" " "
where
substControl c
| c == '\n' || c == '\r' = c -- CR and LF are OK
| c <= '\x1f' = chr (0x2400 + ord c)
| c == '\DEL' = '\x2421'
| isControl c = '\xfffd' -- REPLACEMENT CHARACTER
| otherwise = c

0 comments on commit a085315

Please sign in to comment.