aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt3
-rw-r--r--src/Text/Pandoc/App.hs3
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs27
3 files changed, 19 insertions, 14 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 3de9e4250..53630b7e8 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -308,6 +308,7 @@ header when requesting a document from a URL:
- `opml` ([OPML])
- `opendocument` ([OpenDocument])
- `org` ([Emacs Org mode])
+ - `pdf` ([PDF])
- `plain` (plain text),
- `pptx` ([PowerPoint] slide show)
- `rst` ([reStructuredText])
@@ -325,7 +326,7 @@ header when requesting a document from a URL:
- the path of a custom lua writer, see [Custom writers] below
:::
- Note that `odt`, `docx`, and `epub` output will not be directed
+ Note that `odt`, `docx`, `epub`, and `pdf` output will not be directed
to *stdout* unless forced with `-o -`.
Extensions can be individually enabled or
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 0f379419c..db9d029ac 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -185,7 +185,8 @@ convertWithOpts opts = do
-- force this with '-o -'. On posix systems, we detect
-- when stdout is being piped and allow output to stdout
-- in that case, but on Windows we can't.
- when (not (isTextFormat format) && istty && isNothing ( optOutputFile opts)) $
+ when ((pdfOutput || not (isTextFormat format)) &&
+ istty && isNothing ( optOutputFile opts)) $
throwError $ PandocAppError $
"Cannot write " ++ format ++ " output to terminal.\n" ++
"Specify an output file using the -o option, or " ++
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index 3edeea1a1..1d2f66dd6 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -65,21 +65,26 @@ optToOutputSettings opts = do
Nothing -> return Nothing
Just fp -> Just <$> readUtf8File fp
- let pdfOutput = map toLower (takeExtension outputFile) == ".pdf"
+ let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" ||
+ optTo opts == Just "pdf"
(writerName, maybePdfProg) <-
if pdfOutput
- then liftIO $ pdfWriterAndProg (optTo opts) (optPdfEngine opts)
+ then liftIO $ pdfWriterAndProg
+ (case optTo opts of
+ Just "pdf" -> Nothing
+ x -> x)
+ (optPdfEngine opts)
else case optTo opts of
+ Just f -> return (f, Nothing)
Nothing
- | outputFile == "-" -> return ("html", Nothing)
- | otherwise ->
- case formatFromFilePaths [outputFile] of
+ | outputFile == "-" -> return ("html", Nothing)
+ | otherwise ->
+ case formatFromFilePaths [outputFile] of
Nothing -> do
report $ CouldNotDeduceFormat
[takeExtension outputFile] "html"
return ("html", Nothing)
Just f -> return (f, Nothing)
- Just f -> return (f, Nothing)
let format = if ".lua" `isSuffixOf` writerName
then writerName
@@ -244,13 +249,10 @@ baseWriterName = takeWhile (\c -> c /= '+' && c /= '-')
pdfWriterAndProg :: Maybe String -- ^ user-specified writer name
-> Maybe String -- ^ user-specified pdf-engine
-> IO (String, Maybe String) -- ^ IO (writerName, maybePdfEngineProg)
-pdfWriterAndProg mWriter mEngine = do
- let panErr msg = liftIO $ E.throwIO $ PandocAppError msg
+pdfWriterAndProg mWriter mEngine =
case go mWriter mEngine of
Right (writ, prog) -> return (writ, Just prog)
- Left "pdf writer" -> liftIO $ E.throwIO $
- PandocUnknownWriterError "pdf"
- Left err -> panErr err
+ Left err -> liftIO $ E.throwIO $ PandocAppError err
where
go Nothing Nothing = Right ("latex", "pdflatex")
go (Just writer) Nothing = (writer,) <$> engineForWriter writer
@@ -273,4 +275,5 @@ pdfWriterAndProg mWriter mEngine = do
"cannot produce pdf output from " ++ w
isTextFormat :: String -> Bool
-isTextFormat s = s `notElem` ["odt","docx","epub2","epub3","epub","pptx"]
+isTextFormat s =
+ s `notElem` ["odt","docx","epub2","epub3","epub","pptx","pdf"]