aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README23
-rw-r--r--pandoc.hs16
-rw-r--r--src/Text/Pandoc/PDF.hs66
3 files changed, 91 insertions, 14 deletions
diff --git a/README b/README
index 6f5f90f47..37a8adfe0 100644
--- a/README
+++ b/README
@@ -24,7 +24,7 @@ markup], [Haddock markup], [OPML], [Emacs Org mode], [DocBook],
[FictionBook2], [Textile], [groff man] pages, [Emacs Org mode],
[AsciiDoc], [InDesign ICML], and [Slidy], [Slideous], [DZSlides],
[reveal.js] or [S5] HTML slide shows. It can also produce [PDF] output
-on systems where LaTeX is installed.
+on systems where LaTeX or ConTeXt is installed.
Pandoc's enhanced version of markdown includes syntax for [footnotes],
[tables], flexible [ordered lists], [definition lists], [fenced code blocks],
@@ -167,7 +167,7 @@ Creating a PDF
--------------
To produce a PDF, specify an output file with a `.pdf` extension.
-Pandoc will use LaTeX to convert it to PDF:
+By default, pandoc will use LaTeX to convert it to PDF:
pandoc test.txt -o test.pdf
@@ -189,7 +189,12 @@ be used for [smart punctuation] if added to the template. The
optionally be used for [citation rendering]. These are included with
all recent versions of [TeX Live].
-PDF output can be controlled using [variables for LaTeX].
+Alternatively, you can ask pandoc to use ConTeXt to create the PDF.
+To do this, specify an output file with a `.pdf` extension,
+as before, but add `-t context` to the command line.
+
+PDF output can be controlled using [variables for LaTeX]
+or [variables for ConTeXt].
[`amsfonts`]: https://ctan.org/pkg/amsfonts
[`amsmath`]: https://ctan.org/pkg/amsmath
@@ -992,9 +997,9 @@ customize the `default.opendocument` template. For `pdf` output,
customize the `default.latex` template.
Templates contain *variables*, which allow for the inclusion of
-arbitrary information at any point in the file. Variables may be set
-within the document using [YAML metadata blocks][Extension: `yaml_metadata_block`].
-They may also be set at the
+arbitrary information at any point in the file. Variables may be set
+within the document using [YAML metadata blocks][Extension:
+`yaml_metadata_block`]. They may also be set at the
command line using the `-V/--variable` option: variables set in this
way override metadata fields with the same name.
@@ -1201,6 +1206,12 @@ LaTeX variables are used when [creating a PDF].
[`mathpazo`]: https://ctan.org/pkg/mathpazo
[LaTeX font encodings]: https://ctan.org/pkg/encguide
+Variables for ConTeXt
+---------------------
+
+`papersize`
+: paper size (defaults to `letter`)
+
Variables for man pages
-----------------------
diff --git a/pandoc.hs b/pandoc.hs
index ecf19dbc3..fce1a8142 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1173,6 +1173,7 @@ main = do
let laTeXOutput = "latex" `isPrefixOf` writerName' ||
"beamer" `isPrefixOf` writerName'
+ let conTeXtOutput = "context" `isPrefixOf` writerName'
writer <- if ".lua" `isSuffixOf` writerName'
-- note: use non-lowercased version writerName
@@ -1256,7 +1257,7 @@ main = do
_ -> Nothing
let readerOpts = def{ readerSmart = smart || (texLigatures &&
- (laTeXOutput || "context" `isPrefixOf` writerName'))
+ (laTeXOutput || conTeXtOutput))
, readerStandalone = standalone'
, readerParseRaw = parseRaw
, readerColumns = columns
@@ -1367,17 +1368,20 @@ main = do
PureStringWriter f
| pdfOutput -> do
-- make sure writer is latex or beamer
- unless laTeXOutput $
+ unless (laTeXOutput || conTeXtOutput) $
err 47 $ "cannot produce pdf output with " ++ writerName' ++
" writer"
+ let texprog = if conTeXtOutput
+ then "context"
+ else latexEngine
-- check for latex program
- mbLatex <- findExecutable latexEngine
+ mbLatex <- findExecutable texprog
when (mbLatex == Nothing) $
- err 41 $ latexEngine ++ " not found. " ++
- latexEngine ++ " is needed for pdf output."
+ err 41 $ texprog ++ " not found. " ++
+ texprog ++ " is needed for pdf output."
- res <- makePDF latexEngine f writerOptions doc'
+ res <- makePDF texprog f writerOptions doc'
case res of
Right pdf -> writeBinary pdf
Left err' -> do
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