aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/EPUB.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2013-08-11 15:58:09 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-08-11 15:58:09 -0700
commite279175ea517e2df65fe5d716bc02e383b04fc36 (patch)
treecafdb6b78c8a399e8fb0ac9c8e1c3ba5a8fef153 /src/Text/Pandoc/Writers/EPUB.hs
parent6f736dfa7578faab7b90546ee5b2c275185968c8 (diff)
downloadpandoc-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/Pandoc/Writers/EPUB.hs')
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs21
1 files changed, 7 insertions, 14 deletions
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 $