diff options
author | John MacFarlane <fiddlosopher@gmail.com> | 2013-08-11 15:58:09 -0700 |
---|---|---|
committer | John MacFarlane <fiddlosopher@gmail.com> | 2013-08-11 15:58:09 -0700 |
commit | e279175ea517e2df65fe5d716bc02e383b04fc36 (patch) | |
tree | cafdb6b78c8a399e8fb0ac9c8e1c3ba5a8fef153 /src/Text | |
parent | 6f736dfa7578faab7b90546ee5b2c275185968c8 (diff) | |
download | pandoc-e279175ea517e2df65fe5d716bc02e383b04fc36.tar.gz |
Options: Changed `writerSourceDir` to `writerSourceURL` (now a Maybe).
Previously we used to store the directory of the first input file,
even if it was local, and used this as a base directory for
finding images in ODT, EPUB, Docx, and PDF.
This has been confusing to many users. It seems better to look for
images relative to the current working directory, even if the first
file argument is in another directory.
writerSourceURL is set to 'Just url' when the first command-line
argument is an absolute URL. (So, relative links will be resolved
in relation to the first page.) Otherwise, 'Nothing'.
The ODT, EPUB, Docx, and PDF writers have been modified accordingly.
Note that this change may break some existing workflows. If you
have been assuming that relative links will be interpreted relative
to the directory of the first file argument, you'll need to
make that the current directory before running pandoc.
Closes #942.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Options.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/PDF.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 21 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 9 |
6 files changed, 27 insertions, 36 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 61a85cf6e..c7c37d6b8 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -286,7 +286,7 @@ data WriterOptions = WriterOptions , writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails , writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML -- and for footnote marks in markdown - , writerSourceDirectory :: FilePath -- ^ Directory path of 1st source file + , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file , writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory , writerCiteMethod :: CiteMethod -- ^ How to print cites , writerBiblioFiles :: [FilePath] -- ^ Biblio files to use for citations @@ -329,7 +329,7 @@ instance Default WriterOptions where , writerColumns = 72 , writerEmailObfuscation = JavascriptObfuscation , writerIdentifierPrefix = "" - , writerSourceDirectory = "." + , writerSourceURL = Nothing , writerUserDataDir = Nothing , writerCiteMethod = Citeproc , writerBiblioFiles = [] diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index ce20ac1b4..ae611bc37 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -65,17 +65,17 @@ makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex) -> Pandoc -- ^ document -> IO (Either ByteString ByteString) makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do - doc' <- handleImages (writerSourceDirectory opts) tmpdir doc + doc' <- handleImages (writerSourceURL opts) tmpdir doc let source = writer opts doc' tex2pdf' tmpdir program source -handleImages :: String -- ^ source directory/base URL +handleImages :: Maybe String -- ^ source base URL -> FilePath -- ^ temp dir to store images -> Pandoc -- ^ document -> IO Pandoc handleImages baseURL tmpdir = walkM (handleImage' baseURL tmpdir) -handleImage' :: String +handleImage' :: Maybe String -> FilePath -> Inline -> IO Inline diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 6fd78b188..d670a35bc 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -612,18 +612,18 @@ readDataFileUTF8 userDir fname = -- | Fetch an image or other item from the local filesystem or the net. -- Returns raw content and maybe mime type. -fetchItem :: String -> String +fetchItem :: Maybe String -> String -> IO (Either E.SomeException (BS.ByteString, Maybe String)) -fetchItem sourceDir s = - case s of - _ | isAbsoluteURI s -> openURL s - | isAbsoluteURI sourceDir -> openURL $ sourceDir ++ "/" ++ s - | otherwise -> E.try $ do +fetchItem sourceURL s + | isAbsoluteURI s = openURL s + | otherwise = case sourceURL of + Just u -> openURL (u ++ "/" ++ s) + Nothing -> E.try readLocalFile + where readLocalFile = do let mime = case takeExtension s of - ".gz" -> getMimeType $ dropExtension s - x -> getMimeType x - let f = sourceDir </> s - cont <- BS.readFile f + ".gz" -> getMimeType $ dropExtension s + x -> getMimeType x + cont <- BS.readFile s return (cont, mime) -- | Read from a URL and return raw data and maybe mime type. diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index aa618b2cc..c8673ae48 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -728,8 +728,7 @@ inlineToOpenXML opts (Image alt (src, tit)) = do case M.lookup src imgs of Just (_,_,_,elt,_) -> return [elt] Nothing -> do - let sourceDir = writerSourceDirectory opts - res <- liftIO $ fetchItem sourceDir src + res <- liftIO $ fetchItem (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 fa2b45036..ac0e7610c 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -55,7 +55,7 @@ import Text.Pandoc.UUID import Text.Pandoc.Writers.HTML import Text.Pandoc.Writers.Markdown ( writePlain ) import Data.Char ( toLower ) -import Network.URI ( isAbsoluteURI, unEscapeString ) +import Network.URI ( unEscapeString ) import Text.Pandoc.MIME (getMimeType) #if MIN_VERSION_base(4,6,0) #else @@ -93,7 +93,6 @@ writeEPUB opts doc@(Pandoc meta _) = do then MathML Nothing else writerHTMLMathMethod opts , writerWrapText = False } - let sourceDir = writerSourceDirectory opts' let mbCoverImage = lookup "epub-cover-image" vars -- cover page @@ -117,10 +116,10 @@ writeEPUB opts doc@(Pandoc meta _) = do -- handle pictures picsRef <- newIORef [] Pandoc _ blocks <- walkM - (transformInline opts' sourceDir picsRef) doc + (transformInline opts' picsRef) doc pics <- readIORef picsRef let readPicEntry entries (oldsrc, newsrc) = do - res <- fetchItem sourceDir oldsrc + res <- fetchItem (writerSourceURL opts') oldsrc case res of Left _ -> do warn $ "Could not find image `" ++ oldsrc ++ "', skipping..." @@ -414,19 +413,13 @@ showDateTimeISO8601 :: UTCTime -> String showDateTimeISO8601 = formatTime defaultTimeLocale "%FT%TZ" transformInline :: WriterOptions - -> FilePath -> IORef [(FilePath, FilePath)] -- ^ (oldpath, newpath) images -> Inline -> IO Inline -transformInline opts sourceDir picsRef (Image lab (src,tit)) - | isAbsoluteURI src = do - raw <- makeSelfContained Nothing - $ writeHtmlInline opts (Image lab (src,tit)) - return $ RawInline (Format "html") raw - | otherwise = do +transformInline opts picsRef (Image lab (src,tit)) = do let src' = unEscapeString src pics <- readIORef picsRef - let oldsrc = sourceDir </> src' + let oldsrc = maybe src' (</> src) $ writerSourceURL opts let ext = takeExtension src' newsrc <- case lookup oldsrc pics of Just n -> return n @@ -435,11 +428,11 @@ transformInline opts sourceDir picsRef (Image lab (src,tit)) modifyIORef picsRef ( (oldsrc, new): ) return new return $ Image lab (newsrc, tit) -transformInline opts _ _ (x@(Math _ _)) +transformInline opts _ (x@(Math _ _)) | WebTeX _ <- writerHTMLMathMethod opts = do raw <- makeSelfContained Nothing $ writeHtmlInline opts x return $ RawInline (Format "html") raw -transformInline _ _ _ x = return x +transformInline _ _ x = return x writeHtmlInline :: WriterOptions -> Inline -> String writeHtmlInline opts z = trimr $ diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index fb94d9ffb..751a323f5 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -62,8 +62,7 @@ writeODT opts doc@(Pandoc meta _) = do readDataFile datadir "reference.odt" -- handle pictures picEntriesRef <- newIORef ([] :: [Entry]) - let sourceDir = writerSourceDirectory opts - doc' <- walkM (transformPic sourceDir picEntriesRef) doc + doc' <- walkM (transformPic opts picEntriesRef) doc let newContents = writeOpenDocument opts{writerWrapText = False} doc' epochtime <- floor `fmap` getPOSIXTime let contentEntry = toEntry "content.xml" epochtime $ fromStringLazy newContents @@ -111,9 +110,9 @@ writeODT opts doc@(Pandoc meta _) = do let archive'' = addEntryToArchive metaEntry archive' return $ fromArchive archive'' -transformPic :: FilePath -> IORef [Entry] -> Inline -> IO Inline -transformPic sourceDir entriesRef (Image lab (src,_)) = do - res <- fetchItem sourceDir src +transformPic :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline +transformPic opts entriesRef (Image lab (src,_)) = do + res <- fetchItem (writerSourceURL opts) src case res of Left (_ :: E.SomeException) -> do warn $ "Could not find image `" ++ src ++ "', skipping..." |