diff options
| -rw-r--r-- | changelog | 242 | ||||
| -rw-r--r-- | pandoc.cabal | 2 | ||||
| -rw-r--r-- | pandoc.hs | 53 | ||||
| -rw-r--r-- | src/Text/Pandoc.hs | 35 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 9 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 6 | ||||
| -rw-r--r-- | tests/latex-reader.native | 2 |
7 files changed, 299 insertions, 50 deletions
@@ -1,3 +1,245 @@ +pandoc (1.12.4) + + * Made it possible to run filters that aren't executable (#1096). + Pandoc first tries to find the executable (searching the path + if path isn't given). If it fails, but the file exists and has + a `.py`, `.pl`, `.rb`, `.hs`, or `.php` extension, pandoc runs the filter + using the appropriate interpreter. This should make it easier to + use filters on Windows, and make it more convenient for everyone. + + * Added Emacs org-mode reader (Albert Krewinkel). + + * Added InDesign ICML Writer (mb21). + + * MediaWiki reader: + + + Accept image links in more languages (Jaime Marquínez Ferrándiz). + + Fixed bug in certain nested lists (#1213). If a level 2 list was + followed by a level 1 list, the first item of the level 1 list + would be lost. + + Handle table rows containing just an HTML comment (#1230). + + * LaTeX reader: + + + LaTeX reader: Better handling of `table` environment (#1204). + Positioning options no longer rendered verbatim. + + Better handling of figure and table with caption (#1204). + + Handle `@{}` and `p{length}` in tabular. The length is not actually + recorded, but at least we get a table (#1180). + + * Markdown reader: + + + Ensure that whole numbers in YAML metadata are rendered without + decimal points. (This became necessary with changes to aeson + and yaml libraries. aeson >= 0.7 and yaml >= 0.8.8.2 are now required.) + + Fixed regression on line breaks in strict mode (#1203). + + Small efficiency improvements. + + Improved parsing of nested `div`s. Formerly a closing `div` tag + would be missed if it came right after other block-level tags. + + Avoid backtracking when closing `</div>` not found. + + Fixed bug in reference link parsing in `markdown_mmd`. + + * Textile reader: + + + Better support for attributes. Instead of being ignored, attributes + are now parsed and included in Span inlines. The output will be a bit + different from stock textile: e.g. for `*(foo)hi*`, we'll get + `<em><span class="foo">hi</span></em>` instead of + `<em class="foo">hi</em>`. But at least the data is not lost. + + Improved treatment of HTML spans (%) (#1115). + + Improved link parsing. In particular we now pick up on attributes. + Since pandoc links can't have attributes, we enclose the whole link in + a span if there are attributes (#1008). + + Implemented correct parsing rules for inline markup (#1175, Matthew + Pickering). + + Use Builder (Matthew Pickering). + + * DocBook reader: + + + Better treatment of `formalpara`. We now emit the title (if present) + as a separate paragraph with boldface text (#1215). + + Set metadata `author` not `authors`. + + Added recognition of `authorgroup` and `releaseinfo` elements (#1214, + Matthew Pickering). + + Converted current meta information parsing in DocBook to a more + extensible version which is aware of the more recent meta + representation (Matthew Pickering). + + * HTML reader: + + + Require tagsoup 0.13.1, to fix a bug with parsing of script tags + (#1248). + + Treat processing instructions & declarations as block. Previously + these were treated as inline, and included in paragraph tags in HTML + or DocBook output, which is generally not what is wanted (#1233). + + Updated `closes` with rules from HTML5 spec. + + Use Builder (Matthew Pickering, #1162). + + * RST reader: + + + Remove duplicate `http` in PEP links (Albert Krewinkel). + + Make rst figures true figures (#1168, CasperVector) + + Enhanced Pandoc's support for rST roles (Merijn Verstaaten). + rST parser now supports: all built-in rST roles, new role definition, + role inheritance, though with some limitations. + + * LaTeX writer: + + + Mark span contents with label if span has an ID (Albert Krewinkel). + + Made `--toc-depth` work well with books in latex/pdf output (#1210). + + Handle line breaks in simple table cells (#1217). + + Workaround for level 4-5 headers in quotes. These previously produced + invalid LaTeX: `\paragraph` or `\subparagraph` in a `quote` environment. + This adds an `mbox{}` in these contexts to work around the problem. + See <http://tex.stackexchange.com/a/169833/22451> (#1221). + + Use `\/` to avoid en-dash ligature instead of `-{}-` (Vaclav Zeman). + This is to fix LuaLaTeX output. The `-{}-` sequence does not avoid the + ligature with LuaLaTeX but `\/` does. + + * DocBook writer: + + + Improve handling of hard line breaks in Docbook writer + (Neil Mayhew). Use a `<literallayout>` for the entire paragraph, not + just for the newline character. + + Don't let line breaks inside footnotes influence the enclosing + paragraph (Neil Mayhew). + + * EPUB writer: + + + Include extension in epub ids. This fixes a problem with duplicate + extensions for fonts and images with the same base name but different + extensions (#1254). + + Handle files linked in raw `img` tags (#1170). + + Handle media in `audio` source tags (#1170). + Note that we now use a `media` directory rather than `images`. + + Incorporate files linked in `video` tags (#1170). `src` and `poster` + will both be incorporated into `content.opf` and the epub container. + + * HTML writer: + + + Add colgroup around col tags (#877). Also affects EPUB writer. + + Fixed bug with unnumbered section headings. Unnumbered section + headings (with class `unnumbered`) were getting numbers. + + * Man writer: Ensure that terms in definition lists aren't line wrapped + (#1195). + + * Markdown writer: + + + Use proper escapes to avoid unwanted lists (#980). Previously we used + 0-width spaces, an ugly hack. + + Use longer backtick fences if needed (#1206). If the content contains a + backtick fence and there are attributes, make sure longer fences are + used to delimit the code. Note: This works well in pandoc, but github + markdown is more limited, and will interpret the first string of three + or more backticks as ending the code block. + + * RST writer: Avoid stack overflow with certain tables (#1197). + + * RTF writer: Fixed table cells containing paragraphs. + + * Custom writer: Correctly handle UTF-8 in custom lua scripts (#1189). + + * `Text.Pandoc.Options`: Added `readerTrace` to `ReaderOptions` + + * `Text.Pandoc.Shared`: + + + Added `compactify'DL` (formerly in markdown reader) (Albert Krewinkel). + + Fixed bug in `toRomanNumeral`: numbers ending with '9' would + be rendered as Roman numerals ending with 'IXIV' (#1249). Thanks to + Jesse Rosenthal. + + `openURL`: set proxy with value of http_proxy env variable (#1211). + Note: proxies with non-root paths are not supported, due to + limitations in `http-conduit`. + + * `Text.Pandoc.PDF`: + + + Ensure that temp directories deleted on Windows (#1192). The PDF is + now read as a strict bytestring, ensuring that process ownership will + be terminated, so the temp directory can be deleted. + + Use `/` as path separators in a few places, even on Windows. + This seems to be necessary for texlive (#1151, thanks to Tim Lin). + + Use `;` for `TEXINPUTS` separator on Windows (#1151). + + Changes to error reporting, to handle non-UTF8 error output. + + * `Text.Pandoc.Templates`: + + + Removed unneeded datatype context (Merijn Verstraaten). + + + YAML objects resolve to "true" in conditionals (#1133). + Note: If `address` is a YAML object and you just have `$address$` + in your template, the word `true` will appear, which may be + unexpected. (Previously nothing would appear.) + + * `Text.Pandoc.SelfContained`: Handle `poster` attribute in `video` + tags (#1188). + + * `Text.Pandoc.Parsing`: + + + Made `F` an instance of Applicative (#1138). + + Added `stateCaption`. + + Added `HasMacros`, simplified other typeclasses. + Removed `updateHeaderMap`, `setHeaderMap`, `getHeaderMap`, + `updateIdentifierList`, `setIdentifierList`, `getIdentifierList`. + + Changed the smart punctuation parser to return `Inlines` + rather than `Inline` (Matthew Pickering). + + Changed `HasReaderOptions`, `HasHeaderMap`, `HasIdentifierList` + from typeclasses of monads to typeclasses of states. This simplifies + the instance definitions and provides more flexibility. Generalized + type of `getOption` and added a default definition. Removed + `askReaderOption`. Added `extractReaderOption`. Added + `extractHeaderMap` and `updateHeaderMap` in `HasHeaderMap`. + Gave default definitions for `getHeaderMap`, `putHeaderMap`, + `modifyHeaderMap`. Added `extractIdentifierList` and + `updateIdentifierList` in `HasIdentifierList`. Gave defaults + for `getIdentifierList`, `putIdentifierList`, and + `modifyIdentifierList`. The ultimate goal here is to allow different + parsers to use their own, tailored parser states (instead of + `ParserState`) while still using shared functions. + + * Template changes: + + + LaTeX template: use `fontenc` package only with `pdflatex` (#1164). + + Beamer template: Consistent styles for figure and table captions + (aaronwolen). + + Beamer template: Adjust widths correctly for oversized images + (Garrick Aden-Buie). + + Beamer template: Added caption package (#1200). + + Beamer template: changes for better unicode handling (KarolS). + + DocBook template: use `authorgroup` if there are authors. + + revealjs template: Move `include-after` to end (certainlyakey). + + revealjs template: Fixed PDF print function (#1220, kevinkenan). + + * Bumped version bounds of dependencies. + + * Added a `--trace` command line option, for debugging backtracking + bugs. So far this only works with the markdown reader. + + * MathMLinHTML: Fixed deprecation warning (#362, gwern, Albert Krewinkel). + + * Updated travis script to test with multiple GHC versions. + + * Force failure of a Travis build if GHC produces warnings (Albert + Krewinkel). + + * Add `.editorconfig` (Albert Krewinkel). + See <http://editorconfig.org/> for details. + + * Give more useful error message if '-t pdf' is specified (#1155). + + * README: + + + Added an explanation of how to use YAML metadata to + force items to appear in the bibliography without citations in + the text (like LaTeX `\nocite`). + + Added note to `--bibtex/--natbib`: not for use in making PDF + (#1194, thanks to nahoj). + + * Moved some doc files from `data-files` to `extra-source-files` (#1123). + They aren't needed at runtime. We keep README and COPYRIGHT in data + to ensure that they'll be available on all systems on which pandoc + is installed. + pandoc (1.12.3.3) * To changes to source; recompiled tarball with latest alex and diff --git a/pandoc.cabal b/pandoc.cabal index e455c82a4..732b7cf50 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -1,5 +1,5 @@ Name: pandoc -Version: 1.12.3.3 +Version: 1.12.4 Cabal-Version: >= 1.10 Build-Type: Custom License: GPL @@ -47,7 +47,7 @@ import System.Exit ( exitWith, ExitCode (..) ) import System.FilePath import System.Console.GetOpt import Data.Char ( toLower ) -import Data.List ( intercalate, isPrefixOf, sort ) +import Data.List ( intercalate, isPrefixOf, isSuffixOf, sort ) import System.Directory ( getAppUserDataDirectory, findExecutable, doesFileExist ) import System.IO ( stdout, stderr ) @@ -243,13 +243,13 @@ options :: [OptDescr (Opt -> IO Opt)] options = [ Option "fr" ["from","read"] (ReqArg - (\arg opt -> return opt { optReader = map toLower arg }) + (\arg opt -> return opt { optReader = arg }) "FORMAT") "" , Option "tw" ["to","write"] (ReqArg - (\arg opt -> return opt { optWriter = map toLower arg }) + (\arg opt -> return opt { optWriter = arg }) "FORMAT") "" @@ -1003,34 +1003,37 @@ main = do Just _ -> return mbDataDir -- assign reader and writer based on options and filenames - let readerName' = if null readerName - then let fallback = if any isURI sources - then "html" - else "markdown" - in defaultReaderName fallback sources - else readerName - - let writerName' = if null writerName - then defaultWriterName outputFile - else case writerName of - "epub2" -> "epub" - "html4" -> "html" - x -> x + let readerName' = case map toLower readerName of + [] -> defaultReaderName + (if any isURI sources + then "html" + else "markdown") sources + "html4" -> "html" + x -> x + + let writerName' = case map toLower writerName of + [] -> defaultWriterName outputFile + "epub2" -> "epub" + "html4" -> "html" + x -> x let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" let laTeXOutput = "latex" `isPrefixOf` writerName' || "beamer" `isPrefixOf` writerName' - writer <- case getWriter writerName' of - Left e -> err 9 $ - if writerName' == "pdf" - then e ++ "\nTo create a pdf with pandoc, use the " ++ - "latex or beamer writer and specify\n" ++ - "an output file with .pdf extension " ++ - "(pandoc -t latex -o filename.pdf)." - else e - Right w -> return w + writer <- if ".lua" `isSuffixOf` writerName' + -- note: use non-lowercased version writerName + then return $ IOStringWriter $ writeCustom writerName + else case getWriter writerName' of + Left e -> err 9 $ + if writerName' == "pdf" + then e ++ "\nTo create a pdf with pandoc, use " ++ + "the latex or beamer writer and specify\n" ++ + "an output file with .pdf extension " ++ + "(pandoc -t latex -o filename.pdf)." + else e + Right w -> return w reader <- case getReader readerName' of Right r -> return r diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 66b0e49c0..a37c98814 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -152,7 +152,7 @@ import Text.Pandoc.Options import Text.Pandoc.Shared (safeRead, warn) import Data.Aeson import qualified Data.ByteString.Lazy as BL -import Data.List (intercalate, isSuffixOf) +import Data.List (intercalate) import Data.Version (showVersion) import Data.Set (Set) import qualified Data.Set as Set @@ -292,24 +292,21 @@ getReader s = -- | Retrieve writer based on formatSpec (format+extensions). getWriter :: String -> Either String Writer -getWriter s = - case parseFormatSpec s of - Left e -> Left $ intercalate "\n" $ [m | Message m <- errorMessages e] - Right (writerName, setExts) -> - case lookup writerName writers of - Nothing - | ".lua" `isSuffixOf` s -> - Right $ IOStringWriter $ writeCustom s - | otherwise -> Left $ "Unknown writer: " ++ writerName - Just (PureStringWriter r) -> Right $ PureStringWriter $ - \o -> r o{ writerExtensions = setExts $ - getDefaultExtensions writerName } - Just (IOStringWriter r) -> Right $ IOStringWriter $ - \o -> r o{ writerExtensions = setExts $ - getDefaultExtensions writerName } - Just (IOByteStringWriter r) -> Right $ IOByteStringWriter $ - \o -> r o{ writerExtensions = setExts $ - getDefaultExtensions writerName } +getWriter s + = case parseFormatSpec s of + Left e -> Left $ intercalate "\n" $ [m | Message m <- errorMessages e] + Right (writerName, setExts) -> + case lookup writerName writers of + Nothing -> Left $ "Unknown writer: " ++ writerName + Just (PureStringWriter r) -> Right $ PureStringWriter $ + \o -> r o{ writerExtensions = setExts $ + getDefaultExtensions writerName } + Just (IOStringWriter r) -> Right $ IOStringWriter $ + \o -> r o{ writerExtensions = setExts $ + getDefaultExtensions writerName } + Just (IOByteStringWriter r) -> Right $ IOByteStringWriter $ + \o -> r o{ writerExtensions = setExts $ + getDefaultExtensions writerName } {-# DEPRECATED toJsonFilter "Use 'toJSONFilter' from 'Text.Pandoc.JSON' instead" #-} -- | Deprecated. Use @toJSONFilter@ from @Text.Pandoc.JSON@ instead. diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index fd761dbec..b5d529eb9 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -322,7 +322,8 @@ blockCommands = M.fromList $ ] addMeta :: ToMetaValue a => String -> a -> LP () -addMeta field val = updateState $ setMeta field val +addMeta field val = updateState $ \st -> + st{ stateMeta = addMetaField field val $ stateMeta st } setCaption :: Inlines -> LP Blocks setCaption ils = do @@ -341,7 +342,7 @@ authors = try $ do -- skip e.g. \vspace{10pt} auths <- sepBy oneAuthor (controlSeq "and") char '}' - addMeta "authors" (map trimInlines auths) + addMeta "author" (map trimInlines auths) section :: Attr -> Int -> LP Blocks section (ident, classes, kvs) lvl = do @@ -525,10 +526,12 @@ inlineCommands = M.fromList $ , ("citeauthor", (try (tok *> optional sp *> controlSeq "citetext") *> complexNatbibCitation AuthorInText) <|> citation "citeauthor" AuthorInText False) + , ("nocite", mempty <$ (citation "nocite" NormalCitation False >>= + addMeta "nocite")) ] ++ map ignoreInlines -- these commands will be ignored unless --parse-raw is specified, -- in which case they will appear as raw latex blocks: - [ "noindent", "index", "nocite" ] + [ "noindent", "index" ] mkImage :: String -> LP Inlines mkImage src = do diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index e0385af25..1de4345f9 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -40,6 +40,7 @@ import Text.Pandoc.Slides import Text.Pandoc.Highlighting ( highlight, styleToCss, formatHtmlInline, formatHtmlBlock ) import Text.Pandoc.XML (fromEntities, escapeStringForXML) +import Network.URI ( parseURIReference, URI(..) ) import Network.HTTP ( urlEncode ) import Numeric ( showHex ) import Data.Char ( ord, toLower ) @@ -396,7 +397,10 @@ imageExts = [ "art", "bmp", "cdr", "cdt", "cpt", "cr2", "crw", "djvu", "erf", treatAsImage :: FilePath -> Bool treatAsImage fp = - let ext = map toLower $ drop 1 $ takeExtension fp + let path = case uriPath `fmap` parseURIReference fp of + Nothing -> fp + Just up -> up + ext = map toLower $ drop 1 $ takeExtension path in null ext || ext `elem` imageExts -- | Convert Pandoc block element to HTML. diff --git a/tests/latex-reader.native b/tests/latex-reader.native index fcc3153cf..abc4b05a7 100644 --- a/tests/latex-reader.native +++ b/tests/latex-reader.native @@ -1,4 +1,4 @@ -Pandoc (Meta {unMeta = fromList [("authors",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]}) +Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]}) [RawBlock (Format "latex") "\\maketitle" ,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] ,HorizontalRule |
