aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2013-07-20 12:14:43 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-07-20 12:14:43 -0700
commit7102254e244b37c91d6b35b4940511a8656edc49 (patch)
treea9e59ee7ecb9b74f824d8cd98a5d050d72cf020d
parent93877e5a2290ea9e67e2047d3876fc0b7699b4ff (diff)
downloadpandoc-7102254e244b37c91d6b35b4940511a8656edc49.tar.gz
PDF generation improvements.
* `Text.Pandoc.PDF` exports `makePDF` instead of `tex2pdf`. (API change.) * `makePDF` walks the pandoc AST and checks for the existence of images in the local directory. If they are not found, it attempts to find them, either in the directory containing the first source file, or at an absolute URL, or at a URL relative to the base URL of the first command line argument. * Closes #917.
-rw-r--r--pandoc.hs4
-rw-r--r--src/Text/Pandoc/MIME.hs11
-rw-r--r--src/Text/Pandoc/PDF.hs50
3 files changed, 56 insertions, 9 deletions
diff --git a/pandoc.hs b/pandoc.hs
index 18124da3a..79bade221 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -31,7 +31,7 @@ writers.
-}
module Main where
import Text.Pandoc
-import Text.Pandoc.PDF (tex2pdf)
+import Text.Pandoc.PDF (makePDF)
import Text.Pandoc.Readers.LaTeX (handleIncludes)
import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, safeRead,
headerShift, normalize, err, warn )
@@ -1113,7 +1113,7 @@ main = do
Right (IOByteStringWriter f) -> f writerOptions doc0 >>= writeBinary
Right (PureStringWriter f)
| pdfOutput -> do
- res <- tex2pdf latexEngine $ f writerOptions doc0
+ res <- makePDF latexEngine f writerOptions doc0
case res of
Right pdf -> writeBinary pdf
Left err' -> err 43 $ UTF8.toStringLazy err'
diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs
index eb54bd48d..d9cb94a33 100644
--- a/src/Text/Pandoc/MIME.hs
+++ b/src/Text/Pandoc/MIME.hs
@@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Mime type lookup for ODT writer.
-}
-module Text.Pandoc.MIME ( getMimeType )
+module Text.Pandoc.MIME ( getMimeType, extensionFromMimeType )
where
import System.FilePath
import Data.Char ( toLower )
@@ -37,7 +37,14 @@ import qualified Data.Map as M
getMimeType :: FilePath -> Maybe String
getMimeType "layout-cache" = Just "application/binary" -- in ODT
getMimeType f = M.lookup (map toLower $ drop 1 $ takeExtension f) mimeTypes
- where mimeTypes = M.fromList -- List borrowed from happstack-server.
+ where mimeTypes = M.fromList mimeTypesList
+
+extensionFromMimeType :: String -> Maybe String
+extensionFromMimeType mimetype = M.lookup mimetype reverseMimeTypes
+ where reverseMimeTypes = M.fromList $ map (\(k,v) -> (v,k)) mimeTypesList
+
+mimeTypesList :: [(String, String)]
+mimeTypesList = -- List borrowed from happstack-server.
[("gz","application/x-gzip")
,("cabal","application/x-cabal")
,("%","application/x-trash")
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index b36f2a0af..49b455285 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -28,12 +28,13 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of LaTeX documents to PDF.
-}
-module Text.Pandoc.PDF ( tex2pdf ) where
+module Text.Pandoc.PDF ( makePDF ) where
import System.IO.Temp
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as BC
+import qualified Data.ByteString as BS
import System.Exit (ExitCode (..))
import System.FilePath
import System.Directory
@@ -42,9 +43,15 @@ import System.Environment
import Control.Exception (evaluate)
import System.IO (hClose)
import Control.Concurrent (putMVar, takeMVar, newEmptyMVar, forkIO)
-import Text.Pandoc.UTF8 as UTF8
import Control.Monad (unless)
import Data.List (isInfixOf)
+import qualified Data.ByteString.Base64 as B64
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Definition
+import Text.Pandoc.Generic (bottomUpM)
+import Text.Pandoc.Shared (fetchItem, warn)
+import Text.Pandoc.Options (WriterOptions(..))
+import Text.Pandoc.MIME (extensionFromMimeType)
withTempDir :: String -> (FilePath -> IO a) -> IO a
withTempDir =
@@ -54,12 +61,45 @@ withTempDir =
withSystemTempDirectory
#endif
-tex2pdf :: String -- ^ tex program (pdflatex, lualatex, xelatex)
- -> String -- ^ latex source
+makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex)
+ -> (WriterOptions -> Pandoc -> String) -- ^ writer
+ -> WriterOptions -- ^ options
+ -> Pandoc -- ^ document
-> IO (Either ByteString ByteString)
-tex2pdf program source = withTempDir "tex2pdf." $ \tmpdir ->
+makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do
+ doc' <- handleImages (writerSourceDirectory opts) tmpdir doc
+ let source = writer opts doc'
tex2pdf' tmpdir program source
+handleImages :: String -- ^ source directory/base URL
+ -> FilePath -- ^ temp dir to store images
+ -> Pandoc -- ^ document
+ -> IO Pandoc
+handleImages baseURL tmpdir = bottomUpM (handleImage' baseURL tmpdir)
+
+handleImage' :: String
+ -> FilePath
+ -> Inline
+ -> IO Inline
+handleImage' baseURL tmpdir (Image ils (src,tit)) = do
+ exists <- doesFileExist src
+ if exists
+ then return $ Image ils (src,tit)
+ else do
+ res <- fetchItem baseURL src
+ case res of
+ Right (contents, Just mime) -> do
+ let ext = maybe (takeExtension src) id $
+ extensionFromMimeType mime
+ let basename = UTF8.toString $ B64.encode $ UTF8.fromString src
+ let fname = tmpdir </> basename <.> ext
+ BS.writeFile fname contents
+ return $ Image ils (fname,tit)
+ _ -> do
+ warn $ "Could not find image `" ++ src ++ "', skipping..."
+ return $ Image ils (src,tit)
+handleImage' _ _ x = return x
+
tex2pdf' :: FilePath -- ^ temp directory for output
-> String -- ^ tex program
-> String -- ^ tex source