Made beamer an output format, removed pdf as output format.

Removed `--beamer` option; instead, use `beamer` as output format.
There is no longer a `pdf` output format; instead, pandoc tries
to produce a pdf if the output file has a `.pdf` extension.
(The output format can be latex -- the default for pdf output,
latex+lhs, or beamer.)

This seems more consistent with the way pandoc currently works
(e.g. we have an `html5` output format, not an `--html5` option).
This commit is contained in:
John MacFarlane 2012-01-28 11:41:26 -08:00
parent 513af8dd1b
commit 8abe08d6d4
4 changed files with 74 additions and 78 deletions

88
README
View file

@ -14,11 +14,11 @@ Pandoc is a [Haskell] library for converting from one markup format to
another, and a command-line tool that uses this library. It can read
[markdown] and (subsets of) [Textile], [reStructuredText], [HTML],
and [LaTeX]; and it can write plain text, [markdown], [reStructuredText],
[XHTML], [HTML 5], [LaTeX], [ConTeXt], [RTF], [DocBook XML],
[OpenDocument XML], [ODT], [Word docx], [GNU Texinfo], [MediaWiki markup], [EPUB],
[Textile], [groff man] pages, [Emacs Org-Mode], [AsciiDoc], and [Slidy],
[DZSlides], or [S5] HTML slide shows. It can also produce [PDF] output
on systems where LaTeX is installed.
[XHTML], [HTML 5], [LaTeX] (including [beamer] slide shows),
[ConTeXt], [RTF], [DocBook XML], [OpenDocument XML], [ODT], [Word docx], [GNU
Texinfo], [MediaWiki markup], [EPUB], [Textile], [groff man] pages, [Emacs
Org-Mode], [AsciiDoc], and [Slidy], [DZSlides], or [S5] HTML slide shows. It
can also produce [PDF] output on systems where LaTeX is installed.
Pandoc's enhanced version of markdown includes syntax for footnotes,
tables, flexible ordered lists, definition lists, delimited code blocks,
@ -42,7 +42,7 @@ If no *input-file* is specified, input is read from *stdin*.
Otherwise, the *input-files* are concatenated (with a blank
line between each) and used as input. Output goes to *stdout* by
default (though output to *stdout* is disabled for the `odt`, `docx`,
`pdf`, and `epub` output formats). For output to a file, use the
and `epub` output formats). For output to a file, use the
`-o` option:
pandoc -o output.html input.txt
@ -91,23 +91,25 @@ should pipe input and output through `iconv`:
iconv -t utf-8 input.txt | pandoc | iconv -f utf-8
`markdown2pdf`
Creating a PDF
--------------
Earlier versions of pandoc came with a program, `markdown2pdf`, that
used pandoc and pdflatex to produce a PDF. This is no longer needed,
since `pandoc` now has a `pdf` output format, and there is no reason
to limit input to markdown. Note that whereas `markdown2pdf` would
create an ouput file based on the input file name, `pandoc` requires
that you specify the output filename explicitly. So,
since `pandoc` can now produce `pdf` output itself. To produce a PDF, simply
specify an output file with a `.pdf` extension. Pandoc will create a latex
file and use pdflatex (or another engine, see `--latex-engine`) to convert it
to PDF:
pandoc input.txt -o input.pdf --latex-engine=xelatex
pandoc test.txt -o test.pdf
does the same thing
markdown2pdf --xetex input.txt
used to do.
Production of a PDF requires that a LaTeX engine be installed (see
`--latex-engine`, below), and assumes that the following LaTeX packages are
available: `amssymb`, `amsmath`, `ifxetex`, `ifluatex`, `listings` (if the
`--listings` option is used), `fancyvrb`, `enumerate`, `ctable`, `url`,
`graphicx`, `hyperref`, `ulem`, `babel` (if the `lang` variable is set),
`fontspec` (if `xelatex` or `lualatex` is used as the LaTeX engine), `xltxtra`
and `xunicode` (if `xelatex` is used).
`hsmarkdown`
------------
@ -144,32 +146,24 @@ General options
: Specify output format. *FORMAT* can be `native` (native Haskell),
`json` (JSON version of native AST), `plain` (plain text),
`markdown` (markdown), `rst` (reStructuredText), `html` (XHTML 1),
`html5` (HTML 5), `latex` (LaTeX), `context` (ConTeXt),
`man` (groff man), `mediawiki` (MediaWiki markup), `textile`
(Textile), `org` (Emacs Org-Mode), `texinfo` (GNU Texinfo), `docbook`
(DocBook XML), `opendocument` (OpenDocument XML), `odt` (OpenOffice text
document), `docx` (Word docx), `epub` (EPUB book), `asciidoc` (AsciiDoc),
`slidy` (Slidy HTML and javascript slide show), `dzslides` (HTML5 +
javascript slide show), `s5` (S5 HTML and javascript slide show),
`rtf` (rich text format), or `pdf` (PDF). Note that `odt` and `epub` output
will not be directed to *stdout*; an output filename must be specified
using the `-o/--output` option. If `+lhs` is appended to `markdown`, `rst`,
`latex`, `html`, or `html5`, the output will be rendered as literate Haskell
source: see [Literate Haskell support](#literate-haskell-support), below.
Production of `pdf` output requires that a LaTeX engine be installed
(see `--latex-engine`, below), and assumes that the following LaTeX
packages are available: `amssymb`, `amsmath`, `ifxetex`, `ifluatex`,
`listings` (if the `--listings` option is used), `fancyvrb`,
`enumerate`, `ctable`, `url`, `graphicx`, `hyperref`, `ulem`,
`babel` (if the `lang` variable is set), `fontspec` (if `xelatex`
or `lualatex` is used as the LaTeX engine), `xltxtra` and
`xunicode` (if `xelatex` is used).
`html5` (HTML 5), `latex` (LaTeX), `beamer` (LaTeX beamer slide show),
`context` (ConTeXt), `man` (groff man), `mediawiki` (MediaWiki markup),
`textile` (Textile), `org` (Emacs Org-Mode), `texinfo` (GNU Texinfo),
`docbook` (DocBook XML), `opendocument` (OpenDocument XML), `odt`
(OpenOffice text document), `docx` (Word docx), `epub` (EPUB book),
`asciidoc` (AsciiDoc), `slidy` (Slidy HTML and javascript slide show),
`dzslides` (HTML5 + javascript slide show), `s5` (S5 HTML and javascript
slide show), or `rtf` (rich text format). Note that `odt` and `epub`
output will not be directed to *stdout*; an output filename must
be specified using the `-o/--output` option. If `+lhs` is appended
to `markdown`, `rst`, `latex`, `html`, or `html5`, the output will
be rendered as literate Haskell source: see [Literate Haskell
support](#literate-haskell-support), below.
`-o` *FILE*, `--output=`*FILE*
: Write output to *FILE* instead of *stdout*. If *FILE* is
`-`, output will go to *stdout*. (Exception: if the output
format is `odt`, `docx`, `pdf`, or `epub`, output to stdout is disabled.)
format is `odt`, `docx`, or `epub`, output to stdout is disabled.)
`--data-dir=`*DIRECTORY*
: Specify the user data directory to search for pandoc data files.
@ -248,7 +242,8 @@ General writer options
`-s`, `--standalone`
: Produce output with an appropriate header and footer (e.g. a
standalone HTML, LaTeX, or RTF file, not a fragment).
standalone HTML, LaTeX, or RTF file, not a fragment). This option
is set automatically for `pdf`, `epub`, `docx`, and `odt` output.
`--template=`*FILE*
: Use *FILE* as a custom template for the generated document. Implies
@ -359,10 +354,6 @@ Options affecting specific writers
`--listings`
: Use listings package for LaTeX code blocks
`--beamer`
: Produce LaTeX output for the `beamer` document class.
This has an effect only for `latex` or `pdf` output.
`-i`, `--incremental`
: Make list items in slide shows display incrementally (one by one).
The default is for lists to be displayed all at once.
@ -1979,8 +1970,7 @@ Producing slide shows with Pandoc
You can use Pandoc to produce an HTML + javascript slide presentation
that can be viewed via a web browser. There are three ways to do this,
using [S5], [DZSlides], or [Slidy]. You can also produce a PDF slide
show using [LaTeX beamer]: just use the `--beamer` option with `pdf`
output.
show using LaTeX [beamer].
Here's the markdown source for a simple slide show, `habits.txt`:
@ -2030,7 +2020,7 @@ for Slidy,
for DZSlides, or
pandoc --beamer habits.txt -o habits.pdf
pandoc -t beamer habits.txt -o habits.pdf
for beamer.
@ -2110,7 +2100,7 @@ be modified there.
To style beamer slides, you can specify a beamer "theme" or "colortheme"
using the `-V` option:
pandoc --beamer habits.txt -V theme:Warsaw -o habits.pdf
pandoc -t beamer habits.txt -V theme:Warsaw -o habits.pdf
Literate Haskell support
========================
@ -2177,7 +2167,7 @@ Christopher Sawicki, Kelsey Hightower.
[HTML 5]: http://www.w3.org/TR/html5/
[XHTML]: http://www.w3.org/TR/xhtml1/
[LaTeX]: http://www.latex-project.org/
[LaTeX beamer]: http://www.tex.ac.uk/CTAN/macros/latex/contrib/beamer
[beamer]: http://www.tex.ac.uk/CTAN/macros/latex/contrib/beamer
[ConTeXt]: http://www.pragma-ade.nl/
[RTF]: http://en.wikipedia.org/wiki/Rich_Text_Format
[DocBook XML]: http://www.docbook.org/

View file

@ -190,6 +190,8 @@ writers = [("native" , writeNative)
,("latex" , writeLaTeX)
,("latex+lhs" , \o ->
writeLaTeX o{ writerLiterateHaskell = True })
,("beamer" , \o ->
writeLaTeX o{ writerBeamer = True })
,("context" , writeConTeXt)
,("texinfo" , writeTexinfo)
,("man" , writeMan)

View file

@ -85,7 +85,7 @@ getDefaultTemplate _ "native" = return $ Right ""
getDefaultTemplate _ "json" = return $ Right ""
getDefaultTemplate _ "docx" = return $ Right ""
getDefaultTemplate user "odt" = getDefaultTemplate user "opendocument"
getDefaultTemplate user "pdf" = getDefaultTemplate user "latex"
getDefaultTemplate user "beamer" = getDefaultTemplate user "latex"
getDefaultTemplate user "epub" = getDefaultTemplate user "html"
getDefaultTemplate user writer = do
let format = takeWhile (/='+') writer -- strip off "+lhs" if present

View file

@ -83,7 +83,7 @@ wrapWords indent c = wrap' (c - indent) (c - indent)
else ", " ++ x ++ wrap' cols (remaining - (length x + 2)) xs
nonTextFormats :: [String]
nonTextFormats = ["odt","docx","epub","pdf"]
nonTextFormats = ["odt","docx","epub"]
-- | Data structure for command line options.
data Opt = Opt
@ -130,7 +130,6 @@ data Opt = Opt
, optAbbrevsFile :: Maybe FilePath
, optListings :: Bool -- ^ Use listings package for code blocks
, optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
, optBeamer :: Bool -- ^ Produce latex output for beamer class
, optSlideLevel :: Maybe Int -- ^ Header level that creates slides
, optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
}
@ -181,7 +180,6 @@ defaultOpts = Opt
, optAbbrevsFile = Nothing
, optListings = False
, optLaTeXEngine = "pdflatex"
, optBeamer = False
, optSlideLevel = Nothing
, optSetextHeaders = True
}
@ -436,11 +434,6 @@ options =
(\opt -> return opt { optListings = True }))
"" -- "Use listings package for LaTeX code blocks"
, Option "" ["beamer"]
(NoArg
(\opt -> return opt { optBeamer = True }))
"" -- "Produce latex output for beamer class"
, Option "i" ["incremental"]
(NoArg
(\opt -> return opt { optIncremental = True }))
@ -732,7 +725,7 @@ defaultWriterName x =
".epub" -> "epub"
".org" -> "org"
".asciidoc" -> "asciidoc"
".pdf" -> "pdf"
".pdf" -> "latex"
['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html"
@ -815,7 +808,6 @@ main = do
, optCiteMethod = citeMethod
, optListings = listings
, optLaTeXEngine = latexEngine
, optBeamer = beamer
, optSlideLevel = slideLevel
, optSetextHeaders = setextHeaders
} = opts
@ -845,7 +837,13 @@ main = do
then defaultWriterName outputFile
else writerName
when (writerName' == "pdf") $ do
let pdfOutput = map toLower (takeExtension outputFile) == ".pdf"
when pdfOutput $ do
-- make sure writer is latex or beamer
unless (writerName' == "latex" || writerName' == "beamer" ||
writerName' == "latex+lhs") $
err 47 $ "cannot produce pdf output with " ++ writerName' ++ " writer"
-- check for latex program
mbLatex <- findExecutable latexEngine
case mbLatex of
@ -858,7 +856,7 @@ main = do
Just r -> return r
Nothing -> err 7 ("Unknown reader: " ++ readerName')
let standalone' = standalone || (`elem` nonTextFormats) writerName'
let standalone' = standalone || writerName' `elem` nonTextFormats || pdfOutput
templ <- case templatePath of
_ | not standalone' -> return ""
@ -925,13 +923,13 @@ main = do
stateStandalone = standalone',
stateCitations = map CSL.refId refs,
stateSmart = smart || writerName' `elem`
["latex", "context", "latex+lhs", "pdf"],
["latex", "context", "latex+lhs", "beamer"],
stateOldDashes = oldDashes,
stateColumns = columns,
stateStrict = strict,
stateIndentedCodeClasses = codeBlockClasses,
stateApplyMacros = writerName' `notElem`
["latex", "latex+lhs", "pdf"] }
["latex", "latex+lhs", "beamer"] }
let writerOptions = defaultWriterOptions
{ writerStandalone = standalone',
@ -965,7 +963,7 @@ main = do
slideVariant == DZSlides,
writerChapters = chapters,
writerListings = listings,
writerBeamer = beamer,
writerBeamer = writerName' == "beamer",
writerSlideLevel = slideLevel,
writerHighlight = highlight,
writerHighlightStyle = highlightStyle,
@ -1013,24 +1011,30 @@ main = do
processBiblio cslfile' cslabbrevs refs doc1
else return doc1
let writeBinary :: B.ByteString -> IO ()
writeBinary = B.writeFile (encodeString outputFile)
let writerFn :: FilePath -> String -> IO ()
writerFn "-" = UTF8.putStr
writerFn f = UTF8.writeFile f
case lookup writerName' writers of
Nothing | writerName' == "epub" ->
writeEPUB epubStylesheet writerOptions doc2 >>= writeBinary
| writerName' == "odt" ->
writeODT referenceODT writerOptions doc2 >>= writeBinary
| writerName' == "docx" ->
writeDocx referenceDocx writerOptions doc2 >>= writeBinary
| writerName' == "pdf" ->
do res <- tex2pdf latexEngine $ writeLaTeX writerOptions doc2
Nothing
| writerName' == "epub" ->
writeEPUB epubStylesheet writerOptions doc2 >>= writeBinary
| writerName' == "odt" ->
writeODT referenceODT writerOptions doc2 >>= writeBinary
| writerName' == "docx" ->
writeDocx referenceDocx writerOptions doc2 >>= writeBinary
| otherwise -> err 9 ("Unknown writer: " ++ writerName')
Just _
| pdfOutput -> do
res <- tex2pdf latexEngine $ writeLaTeX writerOptions doc2
case res of
Right pdf -> writeBinary pdf
Left err' -> err 43 $ toString err'
| otherwise -> err 9 ("Unknown writer: " ++ writerName')
where writeBinary = B.writeFile (encodeString outputFile)
Just r -> writerFn outputFile =<< postProcess result
where writerFn "-" = UTF8.putStr
writerFn f = UTF8.writeFile f
result = r writerOptions doc2 ++ ['\n' | not standalone']
where result = r writerOptions doc2 ++ ['\n' | not standalone']
htmlFormats = ["html","html+lhs","s5","slidy","dzslides"]
postProcess = if selfContained && writerName' `elem` htmlFormats
then makeSelfContained datadir