aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-10-20 08:15:12 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2015-10-20 08:16:17 -0700
commit8193ebcd99a1f11e2ab74600ee403f6b100dac32 (patch)
tree0fa9c14bb4db027fdd241d72de9c648989169002 /src/Text
parent82d2719e68a32c132055d4c0f7a755cefef63e14 (diff)
downloadpandoc-8193ebcd99a1f11e2ab74600ee403f6b100dac32.tar.gz
Allow use of ConTeXt to generate PDFs.
pandoc my.md -t context -o my.pdf will now create a PDF using ConTeXt rather than LaTeX. Closes #2463.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/PDF.hs66
1 files changed, 64 insertions, 2 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index f466fcb72..025f7f576 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -47,7 +47,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, inDirectory)
import Text.Pandoc.Options (WriterOptions(..))
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
import Text.Pandoc.Process (pipeProcess)
@@ -71,7 +71,9 @@ makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do
doc' <- handleImages opts tmpdir doc
let source = writer opts doc'
args = writerLaTeXArgs opts
- tex2pdf' (writerVerbose opts) args tmpdir program source
+ case program of
+ "context" -> context2pdf (writerVerbose opts) tmpdir source
+ _ -> tex2pdf' (writerVerbose opts) args tmpdir program source
handleImages :: WriterOptions
-> FilePath -- ^ temp dir to store images
@@ -166,6 +168,14 @@ extractMsg log' = do
then log'
else BC.unlines (msg'' ++ lineno)
+extractConTeXtMsg :: ByteString -> ByteString
+extractConTeXtMsg log' = do
+ let msg' = take 1 $
+ dropWhile (not . ("tex error" `BC.isPrefixOf`)) $ BC.lines log'
+ if null msg'
+ then log'
+ else BC.unlines msg'
+
-- running tex programs
-- Run a TeX program on an input bytestring and return (exit code,
@@ -224,3 +234,55 @@ runTeXProgram verbose program args runNumber numRuns tmpDir source = do
else return Nothing
return (exit, out <> err, pdf)
+context2pdf :: Bool -- ^ Verbose output
+ -> FilePath -- ^ temp directory for output
+ -> String -- ^ ConTeXt source
+ -> IO (Either ByteString ByteString)
+context2pdf verbose tmpDir source = inDirectory tmpDir $ do
+ let file = "input.tex"
+ UTF8.writeFile file source
+#ifdef _WINDOWS
+ -- note: we want / even on Windows, for TexLive
+ let tmpDir' = changePathSeparators tmpDir
+#else
+ let tmpDir' = tmpDir
+#endif
+ let programArgs = ["--batchmode"] ++ [file]
+ env' <- getEnvironment
+ let sep = searchPathSeparator:[]
+ let texinputs = maybe (".." ++ sep) ((".." ++ sep) ++)
+ $ lookup "TEXINPUTS" env'
+ let env'' = ("TEXINPUTS", texinputs) :
+ [(k,v) | (k,v) <- env', k /= "TEXINPUTS"]
+ when verbose $ do
+ putStrLn $ "[makePDF] temp dir:"
+ putStrLn tmpDir'
+ putStrLn $ "[makePDF] Command line:"
+ putStrLn $ "context" ++ " " ++ unwords (map show programArgs)
+ putStr "\n"
+ putStrLn $ "[makePDF] Environment:"
+ mapM_ print env''
+ putStr "\n"
+ putStrLn $ "[makePDF] Contents of " ++ file ++ ":"
+ B.readFile file >>= B.putStr
+ putStr "\n"
+ (exit, out, err) <- pipeProcess (Just env'') "context" programArgs BL.empty
+ when verbose $ do
+ B.hPutStr stdout out
+ B.hPutStr stderr err
+ putStr "\n"
+ let pdfFile = replaceExtension file ".pdf"
+ pdfExists <- doesFileExist pdfFile
+ mbPdf <- if pdfExists
+ -- We read PDF as a strict bytestring to make sure that the
+ -- temp directory is removed on Windows.
+ -- See https://github.com/jgm/pandoc/issues/1192.
+ then (Just . B.fromChunks . (:[])) `fmap` BS.readFile pdfFile
+ else return Nothing
+ let log' = out <> err
+ case (exit, mbPdf) of
+ (ExitFailure _, _) -> do
+ let logmsg = extractConTeXtMsg log'
+ return $ Left logmsg
+ (ExitSuccess, Nothing) -> return $ Left ""
+ (ExitSuccess, Just pdf) -> return $ Right pdf