From a3c3694024c1cb58748a31983bccdc4a58af567e Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Sun, 15 Jan 2017 21:30:20 +0100
Subject: [PATCH] Removed writerMediaBag from WriterOpts.

...since this is now handled through PandocMonad.

Added an explicit MediaBag parameter to makePDF and makeSelfContained.
---
 pandoc.hs                        | 10 ++++------
 src/Text/Pandoc/PDF.hs           | 34 +++++++++++++++++++-------------
 src/Text/Pandoc/SelfContained.hs |  6 +++---
 3 files changed, 27 insertions(+), 23 deletions(-)

diff --git a/pandoc.hs b/pandoc.hs
index fe9cdba00..3f09660e5 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -335,7 +335,6 @@ convertWithOpts opts args = do
                             writerEpubChapterLevel = epubChapterLevel,
                             writerTOCDepth         = epubTOCDepth,
                             writerReferenceDoc     = referenceDoc,
-                            writerMediaBag         = mempty,
                             writerVerbose          = verbose,
                             writerLaTeXArgs        = latexEngineArgs
                           }
@@ -394,10 +393,9 @@ convertWithOpts opts args = do
               applyTransforms transforms >=>
               applyFilters datadir filters' [format]) doc
 
-    let writerOptions' = writerOptions{ writerMediaBag = media }
     case writer of
       -- StringWriter f -> f writerOptions doc' >>= writerFn outputFile
-      ByteStringWriter f -> f writerOptions' doc' >>= writeFnBinary outputFile
+      ByteStringWriter f -> f writerOptions doc' >>= writeFnBinary outputFile
       StringWriter f
         | pdfOutput -> do
                 -- make sure writer is latex or beamer or context or html5
@@ -415,7 +413,7 @@ convertWithOpts opts args = do
                      err 41 $ pdfprog ++ " not found. " ++
                        pdfprog ++ " is needed for pdf output."
 
-                res <- makePDF pdfprog f writerOptions' doc'
+                res <- makePDF pdfprog f writerOptions media doc'
                 case res of
                      Right pdf -> writeFnBinary outputFile pdf
                      Left err' -> liftIO $ do
@@ -426,12 +424,12 @@ convertWithOpts opts args = do
                 let htmlFormat = format `elem`
                       ["html","html5","s5","slidy","slideous","dzslides","revealjs"]
                     selfcontain = if selfContained && htmlFormat
-                                  then makeSelfContained writerOptions'
+                                  then makeSelfContained writerOptions media
                                   else return
                     handleEntities = if htmlFormat && ascii
                                      then toEntities
                                      else id
-                output <- f writerOptions' doc'
+                output <- f writerOptions doc'
                 selfcontain (output ++ ['\n' | not standalone']) >>=
                     writerFn outputFile . handleEntities
 
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index 68151f569..be889c052 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -48,6 +48,7 @@ import Data.List (isInfixOf)
 import Data.Maybe (fromMaybe)
 import qualified Text.Pandoc.UTF8 as UTF8
 import Text.Pandoc.Definition
+import Text.Pandoc.MediaBag
 import Text.Pandoc.Walk (walkM)
 import Text.Pandoc.Shared (warn, withTempDir, inDirectory, stringify)
 import Text.Pandoc.Writers.Shared (getField, metaToJSON)
@@ -72,9 +73,10 @@ makePDF :: MonadIO m
                                -- xelatex, context, wkhtmltopdf)
         -> (WriterOptions -> Pandoc -> PandocIO String)  -- ^ writer
         -> WriterOptions       -- ^ options
+        -> MediaBag            -- ^ media
         -> Pandoc              -- ^ document
         -> m (Either ByteString ByteString)
-makePDF "wkhtmltopdf" writer opts doc@(Pandoc meta _) = liftIO $ do
+makePDF "wkhtmltopdf" writer opts _mediabag doc@(Pandoc meta _) = liftIO $ do
   let mathArgs = case writerHTMLMathMethod opts of
                  -- with MathJax, wait til all math is rendered:
                       MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });",
@@ -97,33 +99,37 @@ makePDF "wkhtmltopdf" writer opts doc@(Pandoc meta _) = liftIO $ do
                  ]
   source <- runIOorExplode $ writer opts doc
   html2pdf (writerVerbose opts) args source
-makePDF program writer opts doc = liftIO $ withTempDir "tex2pdf." $ \tmpdir -> do
-  doc' <- handleImages opts tmpdir doc
-  source <- runIOorExplode $ writer opts doc'
-  let args   = writerLaTeXArgs opts
-  case takeBaseName program of
-     "context" -> context2pdf (writerVerbose opts) tmpdir source
-     prog | prog `elem` ["pdflatex", "lualatex", "xelatex"]
-         -> tex2pdf' (writerVerbose opts) args tmpdir program source
-     _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program
+makePDF program writer opts mediabag doc =
+  liftIO $ withTempDir "tex2pdf." $ \tmpdir -> do
+    doc' <- handleImages opts mediabag tmpdir doc
+    source <- runIOorExplode $ writer opts doc'
+    let args   = writerLaTeXArgs opts
+    case takeBaseName program of
+       "context" -> context2pdf (writerVerbose opts) tmpdir source
+       prog | prog `elem` ["pdflatex", "lualatex", "xelatex"]
+           -> tex2pdf' (writerVerbose opts) args tmpdir program source
+       _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program
 
 handleImages :: WriterOptions
+             -> MediaBag
              -> FilePath      -- ^ temp dir to store images
              -> Pandoc        -- ^ document
              -> IO Pandoc
-handleImages opts tmpdir = walkM (convertImages tmpdir) <=< walkM (handleImage' opts tmpdir)
+handleImages opts mediabag tmpdir =
+  walkM (convertImages tmpdir) <=< walkM (handleImage' opts mediabag tmpdir)
 
 handleImage' :: WriterOptions
+             -> MediaBag
              -> FilePath
              -> Inline
              -> IO Inline
-handleImage' opts tmpdir (Image attr ils (src,tit)) = do
+handleImage' opts mediabag tmpdir (Image attr ils (src,tit)) = do
     exists <- doesFileExist src
     if exists
        then return $ Image attr ils (src,tit)
        else do
          res <- runIO $ do
-                  setMediaBag $ writerMediaBag opts
+                  setMediaBag mediabag
                   fetchItem (writerSourceURL opts) src
          case res of
               Right (contents, Just mime) -> do
@@ -137,7 +143,7 @@ handleImage' opts tmpdir (Image attr ils (src,tit)) = do
                 warn $ "Could not find image `" ++ src ++ "', skipping..."
                 -- return alt text
                 return $ Emph ils
-handleImage' _ _ x = return x
+handleImage' _ _ _ x = return x
 
 convertImages :: FilePath -> Inline -> IO Inline
 convertImages tmpdir (Image attr ils (src, tit)) = do
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index 176de99be..85b298a85 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -174,8 +174,8 @@ getDataURI media sourceURL mimetype src = do
 
 -- | Convert HTML into self-contained HTML, incorporating images,
 -- scripts, and CSS using data: URIs.
-makeSelfContained :: MonadIO m => WriterOptions -> String -> m String
-makeSelfContained opts inp = liftIO $ do
+makeSelfContained :: MonadIO m => WriterOptions -> MediaBag -> String -> m String
+makeSelfContained opts mediabag inp = liftIO $ do
   let tags = parseTags inp
-  out' <- mapM (convertTag (writerMediaBag opts) (writerSourceURL opts)) tags
+  out' <- mapM (convertTag mediabag (writerSourceURL opts)) tags
   return $ renderTags' out'