parent
0b86371751
commit
0c9252520b
@ -0,0 +1,92 @@
|
|||||||
|
commit 5e381e3878b5da87ee7542f7e51c3c1a7fd84b89
|
||||||
|
Author: John MacFarlane <jgm@berkeley.edu>
|
||||||
|
Date: Tue Jun 20 13:50:13 2023 -0700
|
||||||
|
|
||||||
|
Fix a security vulnerability in MediaBag and T.P.Class.IO.writeMedia.
|
||||||
|
|
||||||
|
This vulnerability, discovered by Entroy C, allows users to write
|
||||||
|
arbitrary files to any location by feeding pandoc a specially crafted
|
||||||
|
URL in an image element. The vulnerability is serious for anyone
|
||||||
|
using pandoc to process untrusted input. The vulnerability does
|
||||||
|
not affect pandoc when run with the `--sandbox` flag.
|
||||||
|
|
||||||
|
--- pandoc-2.14.0.3/src/Text/Pandoc/Class/IO.hs.orig 2021-06-11 07:26:17.000000000 +0800
|
||||||
|
+++ pandoc-2.14.0.3/src/Text/Pandoc/Class/IO.hs 2024-03-22 16:39:03.445837785 +0800
|
||||||
|
@@ -48,7 +48,7 @@
|
||||||
|
import Network.HTTP.Client.TLS (mkManagerSettings)
|
||||||
|
import Network.HTTP.Types.Header ( hContentType )
|
||||||
|
import Network.Socket (withSocketsDo)
|
||||||
|
-import Network.URI (unEscapeString)
|
||||||
|
+import Network.URI (URI(..), parseURI)
|
||||||
|
import System.Directory (createDirectoryIfMissing)
|
||||||
|
import System.Environment (getEnv)
|
||||||
|
import System.FilePath ((</>), takeDirectory, normalise)
|
||||||
|
@@ -119,11 +119,11 @@
|
||||||
|
|
||||||
|
openURL :: (PandocMonad m, MonadIO m) => Text -> m (B.ByteString, Maybe MimeType)
|
||||||
|
openURL u
|
||||||
|
- | Just u'' <- T.stripPrefix "data:" u = do
|
||||||
|
- let mime = T.takeWhile (/=',') u''
|
||||||
|
- let contents = UTF8.fromString $
|
||||||
|
- unEscapeString $ T.unpack $ T.drop 1 $ T.dropWhile (/=',') u''
|
||||||
|
- return (decodeLenient contents, Just mime)
|
||||||
|
+ | Just (URI{ uriScheme = "data:",
|
||||||
|
+ uriPath = upath }) <- parseURI (T.unpack u) = do
|
||||||
|
+ let (mime, rest) = break (== '.') upath
|
||||||
|
+ let contents = UTF8.fromString $ drop 1 rest
|
||||||
|
+ return (decodeLenient contents, Just (T.pack mime))
|
||||||
|
| otherwise = do
|
||||||
|
let toReqHeader (n, v) = (CI.mk (UTF8.fromText n), UTF8.fromText v)
|
||||||
|
customHeaders <- map toReqHeader <$> getsCommonState stRequestHeaders
|
||||||
|
--- pandoc-2.14.0.3/src/Text/Pandoc/MediaBag.hs.orig 2021-06-19 04:15:43.000000000 +0800
|
||||||
|
+++ pandoc-2.14.0.3/src/Text/Pandoc/MediaBag.hs 2024-03-22 16:33:37.600005389 +0800
|
||||||
|
@@ -33,7 +33,7 @@
|
||||||
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import Data.Digest.Pure.SHA (sha1, showDigest)
|
||||||
|
-import Network.URI (URI (..), parseURI)
|
||||||
|
+import Network.URI (URI (..), parseURI, isURI, unEscapeString)
|
||||||
|
|
||||||
|
data MediaItem =
|
||||||
|
MediaItem
|
||||||
|
@@ -52,9 +52,12 @@
|
||||||
|
instance Show MediaBag where
|
||||||
|
show bag = "MediaBag " ++ show (mediaDirectory bag)
|
||||||
|
|
||||||
|
--- | We represent paths with /, in normalized form.
|
||||||
|
+-- | We represent paths with /, in normalized form. Percent-encoding
|
||||||
|
+-- is resolved.
|
||||||
|
canonicalize :: FilePath -> Text
|
||||||
|
-canonicalize = T.replace "\\" "/" . T.pack . normalise
|
||||||
|
+canonicalize fp
|
||||||
|
+ | isURI fp = T.pack fp
|
||||||
|
+ | otherwise = T.replace "\\" "/" . T.pack . normalise . unEscapeString $ fp
|
||||||
|
|
||||||
|
-- | Delete a media item from a 'MediaBag', or do nothing if no item corresponds
|
||||||
|
-- to the given path.
|
||||||
|
@@ -77,17 +80,18 @@
|
||||||
|
, mediaContents = contents
|
||||||
|
, mediaMimeType = mt }
|
||||||
|
fp' = canonicalize fp
|
||||||
|
+ fp'' = T.unpack fp'
|
||||||
|
uri = parseURI fp
|
||||||
|
- newpath = if isRelative fp
|
||||||
|
+ newpath = if isRelative fp''
|
||||||
|
&& isNothing uri
|
||||||
|
- && ".." `notElem` splitPath fp
|
||||||
|
- then T.unpack fp'
|
||||||
|
+ && not (".." `T.isInfixOf` fp')
|
||||||
|
+ then fp''
|
||||||
|
else showDigest (sha1 contents) <> "." <> ext
|
||||||
|
- fallback = case takeExtension fp of
|
||||||
|
- ".gz" -> getMimeTypeDef $ dropExtension fp
|
||||||
|
- _ -> getMimeTypeDef fp
|
||||||
|
+ fallback = case takeExtension fp'' of
|
||||||
|
+ ".gz" -> getMimeTypeDef $ dropExtension fp''
|
||||||
|
+ _ -> getMimeTypeDef fp''
|
||||||
|
mt = fromMaybe fallback mbMime
|
||||||
|
- path = maybe fp uriPath uri
|
||||||
|
+ path = maybe fp'' (unEscapeString . uriPath) uri
|
||||||
|
ext = case takeExtension path of
|
||||||
|
'.':e -> e
|
||||||
|
_ -> maybe "" T.unpack $ extensionFromMimeType mt
|
@ -0,0 +1,49 @@
|
|||||||
|
commit eddedbfc14916aa06fc01ff04b38aeb30ae2e625
|
||||||
|
Author: John MacFarlane <jgm@berkeley.edu>
|
||||||
|
Date: Thu Jul 20 09:26:38 2023 -0700
|
||||||
|
|
||||||
|
Fix new variant of the vulnerability in CVE-2023-35936.
|
||||||
|
|
||||||
|
Guilhem Moulin noticed that the fix to CVE-2023-35936 was incomplete.
|
||||||
|
An attacker could get around it by double-encoding the malicious
|
||||||
|
extension to create or override arbitrary files.
|
||||||
|
|
||||||
|
$ echo '![](data://image/png;base64,cHJpbnQgImhlbGxvIgo=;.lua+%252f%252e%252e%252f%252e%252e%252fb%252elua)' >b.md
|
||||||
|
$ .cabal/bin/pandoc b.md --extract-media=bar
|
||||||
|
<p><img
|
||||||
|
src="bar/2a0eaa89f43fada3e6c577beea4f2f8f53ab6a1d.lua+%2f%2e%2e%2f%2e%2e%2fb%2elua" /></p>
|
||||||
|
$ cat b.lua
|
||||||
|
print "hello"
|
||||||
|
$ find bar
|
||||||
|
bar/
|
||||||
|
bar/2a0eaa89f43fada3e6c577beea4f2f8f53ab6a1d.lua+
|
||||||
|
|
||||||
|
This commit adds a test case for this more complex attack and fixes
|
||||||
|
the vulnerability. (The fix is quite simple: if the URL-unescaped
|
||||||
|
filename or extension contains a '%', we just use the sha1 hash of the
|
||||||
|
contents as the canonical name, just as we do if the filename contains
|
||||||
|
'..'.)
|
||||||
|
|
||||||
|
--- pandoc-2.14.0.3/src/Text/Pandoc/MediaBag.hs.orig 2024-03-22 16:40:07.874200094 +0800
|
||||||
|
+++ pandoc-2.14.0.3/src/Text/Pandoc/MediaBag.hs 2024-03-22 16:42:13.289905373 +0800
|
||||||
|
@@ -85,16 +85,17 @@
|
||||||
|
newpath = if isRelative fp''
|
||||||
|
&& isNothing uri
|
||||||
|
&& not (".." `T.isInfixOf` fp')
|
||||||
|
+ && '%' `notElem` fp''
|
||||||
|
then fp''
|
||||||
|
- else showDigest (sha1 contents) <> "." <> ext
|
||||||
|
+ else showDigest (sha1 contents) <> ext
|
||||||
|
fallback = case takeExtension fp'' of
|
||||||
|
".gz" -> getMimeTypeDef $ dropExtension fp''
|
||||||
|
_ -> getMimeTypeDef fp''
|
||||||
|
mt = fromMaybe fallback mbMime
|
||||||
|
path = maybe fp'' (unEscapeString . uriPath) uri
|
||||||
|
ext = case takeExtension path of
|
||||||
|
- '.':e -> e
|
||||||
|
- _ -> maybe "" T.unpack $ extensionFromMimeType mt
|
||||||
|
+ '.':e | '%' `notElem` e -> '.':e
|
||||||
|
+ _ -> maybe "" (\x -> '.':T.unpack x) $ extensionFromMimeType mt
|
||||||
|
|
||||||
|
|
||||||
|
-- | Lookup a media item in a 'MediaBag', returning mime type and contents.
|
Loading…
Reference in new issue