diff --git a/pandoc.hs b/pandoc.hs index cfe20bd97..b1666d306 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -1222,21 +1222,23 @@ main = do | src `elem` paths = Image lab (dir ++ "/" ++ src, tit) adjustImagePath _ _ x = x - (doc, writerOptions') <- + (doc, media) <- case reader of StringReader r-> do inp <- readSources sources >>= handleIncludes' . convertTabs . intercalate "\n" d <- r readerOpts inp - return (d, writerOptions) + return (d, M.empty) ByteStringReader r -> do (d, media) <- readFiles sources >>= r readerOpts - case mbExtractMedia of - Just dir | not (M.null media) -> do - mapM_ (writeMedia dir) $ M.toList media - let d' = walk (adjustImagePath dir (M.keys media)) d - return (d', writerOptions{ writerMediaBag = media }) - _ -> return (d, writerOptions) + d' <- case mbExtractMedia of + Just dir | not (M.null media) -> do + mapM_ (writeMedia dir) $ M.toList media + return $ walk (adjustImagePath dir (M.keys media)) d + _ -> return d + return (d', media) + + let writerOptions' = writerOptions{ writerMediaBag = media } let doc0 = M.foldWithKey setMeta doc metadata let doc1 = foldr ($) doc0 transforms diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 3263da99d..35554637a 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -45,7 +45,7 @@ import Data.Maybe (fromMaybe) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.Definition import Text.Pandoc.Walk (walkM) -import Text.Pandoc.Shared (fetchItem, warn, withTempDir) +import Text.Pandoc.Shared (fetchItem', warn, withTempDir) import Text.Pandoc.Options (WriterOptions(..)) import Text.Pandoc.MIME (extensionFromMimeType) import Text.Pandoc.Process (pipeProcess) @@ -65,26 +65,26 @@ makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex) -> Pandoc -- ^ document -> IO (Either ByteString ByteString) makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do - doc' <- handleImages (writerSourceURL opts) tmpdir doc + doc' <- handleImages opts tmpdir doc let source = writer opts doc' tex2pdf' tmpdir program source -handleImages :: Maybe String -- ^ source base URL +handleImages :: WriterOptions -> FilePath -- ^ temp dir to store images -> Pandoc -- ^ document -> IO Pandoc -handleImages baseURL tmpdir = walkM (handleImage' baseURL tmpdir) +handleImages opts tmpdir = walkM (handleImage' opts tmpdir) -handleImage' :: Maybe String +handleImage' :: WriterOptions -> FilePath -> Inline -> IO Inline -handleImage' baseURL tmpdir (Image ils (src,tit)) = do +handleImage' opts tmpdir (Image ils (src,tit)) = do exists <- doesFileExist src if exists then return $ Image ils (src,tit) else do - res <- fetchItem baseURL src + res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of Right (contents, Just mime) -> do let ext = fromMaybe (takeExtension src) $ diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 53f20f232..81aa6cf5a 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -793,10 +793,9 @@ fetchItem sourceURL s return (cont, mime) -- | Like 'fetchItem', but also looks for items in a 'MediaBag'. -fetchItem' :: Maybe MediaBag -> Maybe String -> String +fetchItem' :: MediaBag -> Maybe String -> String -> IO (Either E.SomeException (BS.ByteString, Maybe String)) -fetchItem' Nothing sourceURL s = fetchItem sourceURL s -fetchItem' (Just media) sourceURL s = do +fetchItem' media sourceURL s = do case M.lookup s media of Nothing -> fetchItem sourceURL s Just bs -> do diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 2a1731c1e..6be6eb1d3 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -830,7 +830,8 @@ inlineToOpenXML opts (Image alt (src, tit)) = do case M.lookup src imgs of Just (_,_,_,elt,_) -> return [elt] Nothing -> do - res <- liftIO $ fetchItem (writerSourceURL opts) src + res <- liftIO $ + fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of Left (_ :: E.SomeException) -> do liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..." diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index ec206086a..682b61d78 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -360,7 +360,8 @@ writeEPUB opts doc@(Pandoc meta _) = do walkM (transformBlock opts' mediaRef) pics <- readIORef mediaRef let readPicEntry entries (oldsrc, newsrc) = do - res <- fetchItem (writerSourceURL opts') oldsrc + res <- fetchItem' (writerMediaBag opts') + (writerSourceURL opts') oldsrc case res of Left _ -> do warn $ "Could not find media `" ++ oldsrc ++ "', skipping..." diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 15f7c8be8..02794f76d 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -38,7 +38,7 @@ import qualified Data.ByteString.Lazy as B import Text.Pandoc.UTF8 ( fromStringLazy ) import Codec.Archive.Zip import Text.Pandoc.Options ( WriterOptions(..) ) -import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem, warn ) +import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem', warn ) import Text.Pandoc.ImageSize ( imageSize, sizeInPoints ) import Text.Pandoc.MIME ( getMimeType ) import Text.Pandoc.Definition @@ -131,7 +131,7 @@ writeODT opts doc@(Pandoc meta _) = do transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline transformPicMath opts entriesRef (Image lab (src,_)) = do - res <- fetchItem (writerSourceURL opts) src + res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of Left (_ :: E.SomeException) -> do warn $ "Could not find image `" ++ src ++ "', skipping..."