diff options
-rw-r--r-- | README | 84 | ||||
-rw-r--r-- | changelog | 7 | ||||
m--------- | data/templates | 14 | ||||
-rw-r--r-- | pandoc.cabal | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 16 | ||||
-rw-r--r-- | tests/Tests/Readers/Markdown.hs | 3 | ||||
-rw-r--r-- | tests/lhs-test.latex | 6 | ||||
-rw-r--r-- | tests/lhs-test.latex+lhs | 6 | ||||
-rw-r--r-- | tests/writer.latex | 8 |
12 files changed, 107 insertions, 51 deletions
@@ -5,7 +5,7 @@ Synopsis ======== -pandoc [*options*] [*input-file*]... +`pandoc` [*options*] [*input-file*]... Description =========== @@ -127,7 +127,8 @@ 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`, `longtable`, `booktabs`, `url`, -`graphicx`, `hyperref`, `ulem`, `babel` (if the `lang` variable is set), +`graphicx` and `grffile` (if the document contains images), + `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). @@ -332,7 +333,7 @@ Reader options provided. If you want to run a script in the working directory, preface the filename with `./`. -`-M` *KEY[=VAL]*, `--metadata=`*KEY[:VAL]* +`-M` *KEY*[`=`*VAL*], `--metadata=`*KEY*[`:`*VAL*] : Set the metadata field *KEY* to the value *VAL*. A value specified on the command line overrides a value specified in the document. @@ -358,15 +359,15 @@ Reader options : Specify the number of spaces per tab (default is 4). -`--track-changes=`*accept|reject|all* +`--track-changes=accept`|`reject`|`all` : Specifies what to do with insertions and deletions produced by the MS - Word "track-changes" feature. *accept* (the default), inserts all - insertions, and ignores all deletions. *reject* inserts all - deletions and ignores insertions. *all* puts in both insertions + Word "track-changes" feature. `accept` (the default), inserts all + insertions, and ignores all deletions. `reject` inserts all + deletions and ignores insertions. `all` puts in both insertions and deletions, wrapped in spans with `insertion` and `deletion` classes, respectively. The author and time of change is - included. *all* is useful for scripting: only accepting changes + included. `all` is useful for scripting: only accepting changes from a certain reviewer, say, or before a certain date. This option only affects the docx reader. @@ -399,7 +400,7 @@ General writer options template appropriate for the output format will be used (see `-D/--print-default-template`). -`-V` *KEY[=VAL]*, `--variable=`*KEY[:VAL]* +`-V` *KEY*[`=`*VAL*], `--variable=`*KEY*[`:`*VAL*] : Set the template variable *KEY* to the value *VAL* when rendering the document in standalone mode. This is generally only useful when the @@ -422,7 +423,7 @@ General writer options : Disable text wrapping in output. By default, text is wrapped appropriately for the output format. -`--columns`=*NUMBER* +`--columns=`*NUMBER* : Specify length of lines in characters (for text wrapping). @@ -444,7 +445,7 @@ General writer options : Disables syntax highlighting for code blocks and inlines, even when a language attribute is given. -`--highlight-style`=*STYLE* +`--highlight-style=`*STYLE* : Specifies the coloring style to be used in highlighted source code. Options are `pygments` (the default), `kate`, `monochrome`, @@ -535,7 +536,7 @@ Options affecting specific writers `unnumbered` will never be numbered, even if `--number-sections` is specified. -`--number-offset`=*NUMBER[,NUMBER,...]*, +`--number-offset=`*NUMBER*[`,`*NUMBER*`,`*...*] : Offset for section headings in HTML output (ignored in other output formats). The first number is added to the section number for @@ -567,7 +568,7 @@ Options affecting specific writers : Make list items in slide shows display incrementally (one by one). The default is for lists to be displayed all at once. -`--slide-level`=*NUMBER* +`--slide-level=`*NUMBER* : Specifies that headers with the specified level create slides (for `beamer`, `s5`, `slidy`, `slideous`, `dzslides`). Headers @@ -584,14 +585,14 @@ Options affecting specific writers rather than the header itself. See [Section identifiers](#header-identifiers-in-html-latex-and-context), below. -`--email-obfuscation=`*none|javascript|references* +`--email-obfuscation=none`|`javascript`|`references` : Specify a method for obfuscating `mailto:` links in HTML documents. - *none* leaves `mailto:` links as they are. *javascript* obfuscates - them using javascript. *references* obfuscates them by printing their + `none` leaves `mailto:` links as they are. `javascript` obfuscates + them using javascript. `references` obfuscates them by printing their letters as decimal or hexadecimal character references. -`--id-prefix`=*STRING* +`--id-prefix=`*STRING* : Specify a prefix to be added to all automatically generated identifiers in HTML and DocBook output, and to footnote numbers in markdown output. @@ -721,7 +722,7 @@ Options affecting specific writers documents with few level 1 headers, one might want to use a chapter level of 2 or 3. -`--latex-engine=`*pdflatex|lualatex|xelatex* +`--latex-engine=pdflatex`|`lualatex`|`xelatex` : Use the specified LaTeX engine when producing PDF output. The default is `pdflatex`. If the engine is not in your PATH, @@ -772,7 +773,7 @@ Citation rendering Math rendering in HTML ---------------------- -`-m` [*URL*], `--latexmathml`[=*URL*] +`-m` [*URL*], `--latexmathml`[`=`*URL*] : Use the [LaTeXMathML] script to display embedded TeX math in HTML output. To insert a link to a local copy of the `LaTeXMathML.js` script, @@ -782,14 +783,14 @@ Math rendering in HTML several pages, it is much better to link to a copy of the script, so it can be cached. -`--mathml`[=*URL*] +`--mathml`[`=`*URL*] : Convert TeX math to MathML (in `docbook` as well as `html` and `html5`). In standalone `html` output, a small javascript (or a link to such a script if a *URL* is supplied) will be inserted that allows the MathML to be viewed on some browsers. -`--jsmath`[=*URL*] +`--jsmath`[`=`*URL*] : Use [jsMath] to display embedded TeX math in HTML output. The *URL* should point to the jsMath load script (e.g. @@ -798,7 +799,7 @@ Math rendering in HTML no link to the jsMath load script will be inserted; it is then up to the author to provide such a link in the HTML template. -`--mathjax`[=*URL*] +`--mathjax`[`=`*URL*] : Use [MathJax] to display embedded TeX math in HTML output. The *URL* should point to the `MathJax.js` load script. @@ -811,28 +812,28 @@ Math rendering in HTML be processed by [gladTeX] to produce links to images of the typeset formulas. -`--mimetex`[=*URL*] +`--mimetex`[`=`*URL*] : Render TeX math using the [mimeTeX] CGI script. If *URL* is not specified, it is assumed that the script is at `/cgi-bin/mimetex.cgi`. -`--webtex`[=*URL*] +`--webtex`[`=`*URL*] : Render TeX formulas using an external script that converts TeX formulas to images. The formula will be concatenated with the URL provided. If *URL* is not specified, the Google Chart API will be used. -`--katex`[=*URL*] +`--katex`[`=`*URL*] -: Use [KaTeX] to display embedded TeX math in HTML output. - The *URL* should point to the `katex.js` load script. If a *URL* is - not provided, a link to the KaTeX CDN will be inserted. +: Use [KaTeX] to display embedded TeX math in HTML output. + The *URL* should point to the `katex.js` load script. If a *URL* is + not provided, a link to the KaTeX CDN will be inserted. -`--katex-stylesheet=*URL*` +`--katex-stylesheet=`*URL* -: The *URL* should point to the `katex.css` stylesheet. If this option is - not specified, a link to the KaTeX CDN will be inserted. Note that this - option does not imply `--katex`. +: The *URL* should point to the `katex.css` stylesheet. If this option is + not specified, a link to the KaTeX CDN will be inserted. Note that this + option does not imply `--katex`. Options for wrapper scripts --------------------------- @@ -992,6 +993,9 @@ as `title`, `author`, and `date`) as well as the following: `toc-depth` : level of section to include in table of contents in LaTeX documents +`toc-title` +: title of table of contents (works only with EPUB and docx) + `lof` : include list of figures in LaTeX documents @@ -2666,20 +2670,24 @@ The bibliography may have any of these formats: Format File extension ------------ -------------- - MODS .mods BibLaTeX .bib BibTeX .bibtex - RIS .ris + Copac .copac + CSL JSON .json + CSL YAML .yaml EndNote .enl EndNote XML .xml ISI .wos MEDLINE .medline - Copac .copac - CSL JSON .json + MODS .mods + RIS .ris Note that `.bib` can generally be used with both BibTeX and BibLaTeX files, but you can use `.bibtex` to force BibTeX. +Note that `pandoc-citeproc --bib2json` and `pandoc-citeproc --bib2yaml` +can produce `.json` and `.yaml` files from any of the supported formats. + As an alternative to specifying a bibliography file, you can include the citation data directly in the `references` field of the document's YAML metadata. The field should contain an array of @@ -2699,8 +2707,8 @@ YAML-encoded references, for example: - - 1953 - 4 - 25 - title: 'Molecular structure of nucleic acids: a structure for deoxyribose nucleic - acid' + title: 'Molecular structure of nucleic acids: a structure for deoxyribose + nucleic acid' title-short: Molecular structure of nucleic acids container-title: Nature volume: 171 @@ -1,3 +1,10 @@ +pandoc (1.13.2.1) + + * Updated to build with ghc 7.10.1. + + * Bumped package upper bounds for filepath, blaze-html, + blaze-markup. + pandoc (1.13.2) * TWiki Reader: add new new twiki reader (API chaneg, Alexander Sulfrian). diff --git a/data/templates b/data/templates -Subproject 09767991b2a8945f5739d47c44d171e37e65e0d +Subproject e8aec53fad6b4d587a44af5ca76c4b809569f15 diff --git a/pandoc.cabal b/pandoc.cabal index 7328a07db..2e04f6bc7 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -254,7 +254,7 @@ Library text >= 0.11 && < 1.3, zip-archive >= 0.2.3.4 && < 0.3, HTTP >= 4000.0.5 && < 4000.3, - texmath >= 0.8.0.2 && < 0.9, + texmath >= 0.8.1 && < 0.9, xml >= 1.3.12 && < 1.4, random >= 1 && < 1.2, extensible-exceptions >= 0.1 && < 0.2, diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index c18aa331f..d30c74230 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -161,7 +161,8 @@ module Text.Pandoc.Parsing ( anyLine, setSourceColumn, setSourceLine, newPos, - addWarning + addWarning, + (<+?>) ) where @@ -1245,3 +1246,7 @@ addWarning mbpos msg = generalize :: (Monad m) => Parser s st a -> ParserT s st m a generalize m = mkPT (\ s -> (return $ (return . runIdentity) <$> runIdentity (runParsecT m s))) + +infixr 5 <+?> +(<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a +a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>) diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 59f71589e..52358e51e 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -887,7 +887,7 @@ htmlTag :: Monad m => (Tag String -> Bool) -> ParserT [Char] st m (Tag String, String) htmlTag f = try $ do - lookAhead $ char '<' >> (oneOf "/!?" <|> letter) + lookAhead $ char '<' >> ((oneOf "/!?" >> nonspaceChar) <|> letter) (next : _) <- getInput >>= return . canonicalizeTags . parseTags guard $ f next -- advance the parser diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index ccda83576..5e0cef4f8 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1487,7 +1487,8 @@ code = try $ do math :: MarkdownParser Inlines math = (B.displayMath <$> (mathDisplay >>= applyMacros')) - <|> (B.math <$> (mathInline >>= applyMacros')) + <|> ((B.math <$> (mathInline >>= applyMacros')) <+?> + ((getOption readerSmart >>= guard) *> apostrophe <* notFollowedBy space)) -- Parses material enclosed in *s, **s, _s, or __s. -- Designed to avoid backtracking. diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index b32be06ae..4809d2a14 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -110,6 +110,7 @@ data WriterState = WriterState{ , stPrintWidth :: Integer , stStyleMaps :: StyleMaps , stFirstPara :: Bool + , stTocTitle :: [Inline] } defaultWriterState :: WriterState @@ -131,6 +132,7 @@ defaultWriterState = WriterState{ , stPrintWidth = 1 , stStyleMaps = defaultStyleMaps , stFirstPara = False + , stTocTitle = normalizeInlines [Str "Table of Contents"] } type WS a = StateT WriterState IO a @@ -193,6 +195,13 @@ isValidChar (ord -> c) | 0x10000 <= c && c <= 0x10FFFF = True | otherwise = False +metaValueToInlines :: MetaValue -> [Inline] +metaValueToInlines (MetaString s) = normalizeInlines [Str s] +metaValueToInlines (MetaInlines ils) = ils +metaValueToInlines (MetaBlocks bs) = query return bs +metaValueToInlines (MetaBool b) = [Str $ show b] +metaValueToInlines _ = [] + -- | Produce an Docx file from a Pandoc document. writeDocx :: WriterOptions -- ^ Writer options -> Pandoc -- ^ Document to convert @@ -235,11 +244,15 @@ writeDocx opts doc@(Pandoc meta _) = do -- parse styledoc for heading styles let styleMaps = getStyleMaps styledoc + let tocTitle = fromMaybe (stTocTitle defaultWriterState) $ + metaValueToInlines <$> lookupMeta "toc-title" meta + ((contents, footnotes), st) <- runStateT (writeOpenXML opts{writerWrapText = False} doc') defaultWriterState{ stChangesAuthor = fromMaybe "unknown" username , stChangesDate = formatTime defaultTimeLocale "%FT%XZ" utctime , stPrintWidth = (maybe 420 (\x -> quot x 20) pgContentWidth) , stStyleMaps = styleMaps + , stTocTitle = tocTitle } let epochtime = floor $ utcTimeToPOSIXSeconds utctime let imgs = M.elems $ stImages st @@ -626,7 +639,8 @@ makeTOC :: WriterOptions -> WS [Element] makeTOC opts | writerTableOfContents opts = do let depth = "1-"++(show (writerTOCDepth opts)) let tocCmd = "TOC \\o \""++depth++"\" \\h \\z \\u" - title <- withParaPropM (pStyleM "TOC Heading") (blocksToOpenXML opts [Para [Str "Table of Contents"]]) + tocTitle <- gets stTocTitle + title <- withParaPropM (pStyleM "TOC Heading") (blocksToOpenXML opts [Para tocTitle]) return $ [mknode "w:sdt" [] ([ mknode "w:sdtPr" [] ( diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index 03884a8e5..6c8e9f306 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -208,6 +208,9 @@ tests = [ testGroup "inline code" , test markdownSmart "apostrophe in French" ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»" =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»") + , test markdownSmart "apostrophe after math" $ -- issue #1909 + "The value of the $x$'s and the systems' condition." =?> + para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.") ] , testGroup "footnotes" [ "indent followed by newline and flush-left text" =: diff --git a/tests/lhs-test.latex b/tests/lhs-test.latex index 6f2fdfb77..cf993af9b 100644 --- a/tests/lhs-test.latex +++ b/tests/lhs-test.latex @@ -68,6 +68,12 @@ \date{} +% Redefines (sub)paragraphs to behave more like sections +\let\oldparagraph\paragraph +\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}} +\let\oldsubparagraph\subparagraph +\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}} + \begin{document} \section{lhs test}\label{lhs-test} diff --git a/tests/lhs-test.latex+lhs b/tests/lhs-test.latex+lhs index 77f0e08ff..746744cc8 100644 --- a/tests/lhs-test.latex+lhs +++ b/tests/lhs-test.latex+lhs @@ -49,6 +49,12 @@ \date{} +% Redefines (sub)paragraphs to behave more like sections +\let\oldparagraph\paragraph +\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}} +\let\oldsubparagraph\subparagraph +\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}} + \begin{document} \section{lhs test}\label{lhs-test} diff --git a/tests/writer.latex b/tests/writer.latex index f7123be98..fab5c9325 100644 --- a/tests/writer.latex +++ b/tests/writer.latex @@ -25,7 +25,7 @@ }{} \usepackage{fancyvrb} \VerbatimFootnotes -\usepackage{graphicx} +\usepackage{graphicx,grffile} \makeatletter \def\maxwidth{\ifdim\Gin@nat@width>\linewidth\linewidth\else\Gin@nat@width\fi} \def\maxheight{\ifdim\Gin@nat@height>\textheight\textheight\else\Gin@nat@height\fi} @@ -64,6 +64,12 @@ \author{John MacFarlane \and Anonymous} \date{July 17, 2006} +% Redefines (sub)paragraphs to behave more like sections +\let\oldparagraph\paragraph +\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}} +\let\oldsubparagraph\subparagraph +\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}} + \begin{document} \maketitle |