aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt9
-rw-r--r--data/jats.csl4
-rw-r--r--data/templates/default.epub28
-rw-r--r--data/templates/default.epub38
-rw-r--r--data/templates/default.jats6
-rw-r--r--data/templates/default.man2
-rw-r--r--data/templates/default.ms2
-rw-r--r--linux/Dockerfile2
-rw-r--r--man/pandoc.17
-rw-r--r--src/Text/Pandoc/Extensions.hs2
-rw-r--r--src/Text/Pandoc/Lua/Filter.hs2
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs2
-rw-r--r--src/Text/Pandoc/Lua/Module/System.hs4
-rw-r--r--src/Text/Pandoc/Parsing.hs14
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Readers/Ipynb.hs2
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs61
-rw-r--r--src/Text/Pandoc/Readers/Man.hs3
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs12
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs2
-rw-r--r--src/Text/Pandoc/Readers/RST.hs2
-rw-r--r--src/Text/Pandoc/Readers/TikiWiki.hs4
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs14
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs1
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs4
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs6
-rw-r--r--test/Tests/Lua.hs2
-rw-r--r--test/command/3523.md31
-rw-r--r--test/command/5619.md10
-rw-r--r--test/command/5627.md83
-rw-r--r--test/command/5635.md23
-rw-r--r--test/command/5642.md8
-rw-r--r--test/writer.jats4
-rwxr-xr-xtools/diff-zip.sh26
34 files changed, 304 insertions, 70 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 879bef5a9..cc329b972 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -3967,10 +3967,11 @@ Attributes can be set on links and images:
(This syntax is compatible with [PHP Markdown Extra] when only `#id`
and `.class` are used.)
-For HTML and EPUB, all attributes except `width` and `height` (but
-including `srcset` and `sizes`) are passed through as is. The other
-writers ignore attributes that are not supported by their output
-format.
+For HTML and EPUB, all known HTML5 attributes except `width` and
+`height` (but including `srcset` and `sizes`) are passed through
+as is. Unknown attributes are passed through as custom
+attributes, with `data-` prepended. The other writers ignore
+attributes that are not specifically supported by their output format.
The `width` and `height` attributes on images are treated specially. When
used without a unit, the unit is assumed to be pixels. However, any of
diff --git a/data/jats.csl b/data/jats.csl
index 8f3f643d5..6972cb3f8 100644
--- a/data/jats.csl
+++ b/data/jats.csl
@@ -37,9 +37,9 @@
</names>
</macro>
- <macro name="editor">
+ <macro name="editor" delimiter=" ">
<names variable="editor" prefix="{{jats}}&lt;person-group person-group-type=&quot;editor&quot;&gt;{{/jats}}" suffix="{{jats}}&lt;/person-group&gt;{{/jats}}">
- <name prefix="{{jats}}&lt;name&gt;{{/jats}}" suffix="{{jats}}&lt;/name&gt;{{/jats}}" name-as-sort-order="all" sort-separator="">
+ <name prefix="{{jats}}&lt;name&gt;{{/jats}}" suffix="{{jats}}&lt;/name&gt;{{/jats}}" name-as-sort-order="all" sort-separator=" ">
<name-part name="family" text-case="capitalize-first" prefix="{{jats}}&lt;surname&gt;{{/jats}}" suffix="{{jats}}&lt;/surname&gt;{{/jats}}"/>
<name-part name="given" text-case="capitalize-first" prefix="{{jats}}&lt;given-names&gt;{{/jats}}" suffix="{{jats}}&lt;/given-names&gt;{{/jats}}"/>
</name>
diff --git a/data/templates/default.epub2 b/data/templates/default.epub2
index afcf96a3e..f440134df 100644
--- a/data/templates/default.epub2
+++ b/data/templates/default.epub2
@@ -46,6 +46,13 @@ $if(rights)$
<div class="rights">$rights$</div>
$endif$
$else$
+$if(coverpage)$
+<div id="cover-image">
+<svg xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" version="1.1" width="100%" height="100%" viewBox="0 0 $cover-image-width$ $cover-image-height$" preserveAspectRatio="none">
+<image width="$cover-image-width$" height="$cover-image-height$" xlink:href="../media/$cover-image$" />
+</svg>
+</div>
+$else$
$for(include-before)$
$include-before$
$endfor$
@@ -54,6 +61,7 @@ $for(include-after)$
$include-after$
$endfor$
$endif$
+$endif$
</body>
</html>
diff --git a/data/templates/default.epub3 b/data/templates/default.epub3
index f0feb147a..4f5bd6641 100644
--- a/data/templates/default.epub3
+++ b/data/templates/default.epub3
@@ -47,6 +47,13 @@ $if(rights)$
$endif$
</section>
$else$
+$if(coverpage)$
+<div id="cover-image">
+<svg xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" version="1.1" width="100%" height="100%" viewBox="0 0 $cover-image-width$ $cover-image-height$" preserveAspectRatio="none">
+<image width="$cover-image-width$" height="$cover-image-height$" xlink:href="../media/$cover-image$" />
+</svg>
+</div>
+$else$
$for(include-before)$
$include-before$
$endfor$
@@ -55,6 +62,7 @@ $for(include-after)$
$include-after$
$endfor$
$endif$
+$endif$
</body>
</html>
diff --git a/data/templates/default.jats b/data/templates/default.jats
index 5fd3590a5..6fce5337c 100644
--- a/data/templates/default.jats
+++ b/data/templates/default.jats
@@ -2,12 +2,12 @@
$if(xml-stylesheet)$
<?xml-stylesheet type="text/xsl" href="$xml-stylesheet$"?>
$endif$
-<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.0 20120330//EN"
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.1 20151215//EN"
"JATS-journalpublishing1.dtd">
$if(article.type)$
-<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.0" article-type="$article.type$">
+<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.1" article-type="$article.type$">
$else$
-<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.0" article-type="other">
+<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.1" article-type="other">
$endif$
<front>
<journal-meta>
diff --git a/data/templates/default.man b/data/templates/default.man
index 44b59198b..f257ec3a7 100644
--- a/data/templates/default.man
+++ b/data/templates/default.man
@@ -12,7 +12,7 @@ $endif$
$if(hyphenate)$
.hy
$else$
-.nh \" Turn off hyphenation by default.
+.nh
$endif$
$for(header-includes)$
$header-includes$
diff --git a/data/templates/default.ms b/data/templates/default.ms
index 02bbc626a..d3a0bf7dc 100644
--- a/data/templates/default.ms
+++ b/data/templates/default.ms
@@ -71,7 +71,7 @@ $endif$
$if(hyphenate)$
.hy
$else$
-.nh \" Turn off hyphenation by default.
+.nh
$endif$
$if(has-inline-math)$
.EQ
diff --git a/linux/Dockerfile b/linux/Dockerfile
index c039c0ec4..a669891ac 100644
--- a/linux/Dockerfile
+++ b/linux/Dockerfile
@@ -15,7 +15,7 @@ CMD cabal --version && \
git checkout -b work $TREE && \
cabal new-update && \
cabal new-clean && \
- cabal new-configure --enable-tests -f-export-dynamic -fstatic -fembed_data_files -fbibutils --ghc-options '-optc-Os -optl=-pthread -optl=-static -fPIC' . pandoc-citeproc && \
+ cabal new-configure --enable-tests -f-export-dynamic -fstatic -fembed_data_files -fbibutils --ghc-options '-optc-Os -optl=-pthread -optl=-static -fPIC -split-sections' . pandoc-citeproc && \
cabal new-build . pandoc-citeproc && \
cabal new-test -j1 . pandoc-citeproc && \
for f in $(find dist-newstyle -name 'pandoc*' -type f -perm +400); do cp $f /artifacts/; done && \
diff --git a/man/pandoc.1 b/man/pandoc.1
index d77ea45cb..eaae7707d 100644
--- a/man/pandoc.1
+++ b/man/pandoc.1
@@ -1660,6 +1660,13 @@ options for LaTeX beamer themes (a list).
.TP
.B \f[C]titlegraphic\f[R]
image for title slide
+.SS Variables for PowerPoint slide shows
+.PP
+These variables control the visual aspects of a slide show that are not
+easily controled via templates.
+.TP
+.B \f[C]monofont\f[R]
+font to use for code.
.SS Variables for LaTeX
.PP
Pandoc uses these variables when creating a PDF with a LaTeX engine.
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index f85b23abd..6cb87eef6 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -227,7 +227,7 @@ plainExtensions = extensionsFromList
, Ext_strikeout
]
--- | Extensions to be used with github-flavored markdown.
+-- | Extensions to be used with PHP Markdown Extra.
phpMarkdownExtraExtensions :: Extensions
phpMarkdownExtraExtensions = extensionsFromList
[ Ext_footnotes
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs
index 553dda8de..e8958347d 100644
--- a/src/Text/Pandoc/Lua/Filter.hs
+++ b/src/Text/Pandoc/Lua/Filter.hs
@@ -129,7 +129,7 @@ walkMWithLuaFilter :: LuaFilter -> Pandoc -> Lua Pandoc
walkMWithLuaFilter f =
walkInlines f >=> walkBlocks f >=> walkMeta f >=> walkPandoc f
-mconcatMapM :: (Monad m, Functor m) => (a -> m [a]) -> [a] -> m [a]
+mconcatMapM :: (Monad m) => (a -> m [a]) -> [a] -> m [a]
mconcatMapM f = fmap mconcat . mapM f
hasOneOf :: LuaFilter -> [String] -> Bool
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 8f7653550..09892db49 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -46,7 +46,7 @@ pushModule datadir = do
LuaUtil.addFunction "walk_inline" walkInline
return 1
-walkElement :: (Pushable a, Walkable [Inline] a, Walkable [Block] a)
+walkElement :: (Walkable [Inline] a, Walkable [Block] a)
=> a -> LuaFilter -> Lua a
walkElement x f = walkInlines f x >>= walkBlocks f
diff --git a/src/Text/Pandoc/Lua/Module/System.hs b/src/Text/Pandoc/Lua/Module/System.hs
index 5149c2112..50db21244 100644
--- a/src/Text/Pandoc/Lua/Module/System.hs
+++ b/src/Text/Pandoc/Lua/Module/System.hs
@@ -27,8 +27,8 @@ pushModule = do
addField "arch" arch
addField "os" os
addFunction "environment" env
- addFunction "get_current_directory" getwd
+ addFunction "get_working_directory" getwd
addFunction "with_environment" with_env
- addFunction "with_temp_directory" with_tmpdir
+ addFunction "with_temporary_directory" with_tmpdir
addFunction "with_working_directory" with_wd
return 1
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 15349314f..49249bec8 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -313,8 +313,7 @@ many1Till p end = do
return (first:rest)
-- | Like @manyTill@, but also returns the result of end parser.
-manyUntil :: (Stream s m t)
- => ParserT s u m a
+manyUntil :: ParserT s u m a
-> ParserT s u m b
-> ParserT s u m ([a], b)
manyUntil p end = scan
@@ -328,8 +327,7 @@ manyUntil p end = scan
-- | Like @sepBy1@ from Parsec,
-- but does not fail if it @sep@ succeeds and @p@ fails.
-sepBy1' :: (Stream s m t)
- => ParsecT s u m a
+sepBy1' :: ParsecT s u m a
-> ParsecT s u m sep
-> ParsecT s u m [a]
sepBy1' p sep = (:) <$> p <*> many (try $ sep >> p)
@@ -440,7 +438,7 @@ stringAnyCase (x:xs) = do
return (firstChar:rest)
-- | Parse contents of 'str' using 'parser' and return result.
-parseFromString :: (Monad m, Stream s m Char, IsString s)
+parseFromString :: (Stream s m Char, IsString s)
=> ParserT s st m r
-> String
-> ParserT s st m r
@@ -458,7 +456,7 @@ parseFromString parser str = do
-- | Like 'parseFromString' but specialized for 'ParserState'.
-- This resets 'stateLastStrPos', which is almost always what we want.
-parseFromString' :: (Monad m, Stream s m Char, IsString s)
+parseFromString' :: (Stream s m Char, IsString s)
=> ParserT s ParserState m a
-> String
-> ParserT s ParserState m a
@@ -1019,7 +1017,7 @@ gridTableFooter = blanklines
---
-- | Removes the ParsecT layer from the monad transformer stack
-readWithM :: (Monad m, Stream s m Char, ToString s)
+readWithM :: (Stream s m Char, ToString s)
=> ParserT s st m a -- ^ parser
-> st -- ^ initial state
-> s -- ^ input
@@ -1410,7 +1408,7 @@ extractIdClass (ident, cls, kvs) = (ident', cls', kvs')
Nothing -> cls
kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs
-insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st, Monad mf)
+insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st)
=> ParserT [a] st m (mf Blocks)
-> (String -> [a])
-> [FilePath] -> FilePath
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 78b377993..392530609 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -435,7 +435,7 @@ eSection = try $ do
TagOpen tag _ <- lookAhead $ pSatisfy sectTag
setInChapter (pInTags tag block)
-headerLevel :: PandocMonad m => Text -> TagParser m Int
+headerLevel :: Text -> TagParser m Int
headerLevel tagtype =
case safeRead (T.unpack (T.drop 1 tagtype)) of
Just level ->
@@ -1129,7 +1129,7 @@ _ `closes` _ = False
--- parsers for use in markdown, textile readers
-- | Matches a stretch of HTML in balanced tags.
-htmlInBalanced :: (HasReaderOptions st, Monad m)
+htmlInBalanced :: Monad m
=> (Tag String -> Bool)
-> ParserT String st m String
htmlInBalanced f = try $ do
diff --git a/src/Text/Pandoc/Readers/Ipynb.hs b/src/Text/Pandoc/Readers/Ipynb.hs
index 04e0b1595..dbca5a59f 100644
--- a/src/Text/Pandoc/Readers/Ipynb.hs
+++ b/src/Text/Pandoc/Readers/Ipynb.hs
@@ -53,7 +53,7 @@ readIpynb opts t = do
Right (notebook3 :: Notebook NbV3) -> notebookToPandoc opts notebook3
Left err -> throwError $ PandocIpynbDecodingError err
-notebookToPandoc :: (PandocMonad m, FromJSON (Notebook a))
+notebookToPandoc :: PandocMonad m
=> ReaderOptions -> Notebook a -> m Pandoc
notebookToPandoc opts notebook = do
let cells = notebookCells notebook
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 6734bc32d..0202c1fc4 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1379,7 +1379,7 @@ doref cls = do
""
(inBrackets $ str refstr)
-lookupListDefault :: (Show k, Ord k) => v -> [k] -> M.Map k v -> v
+lookupListDefault :: (Ord k) => v -> [k] -> M.Map k v -> v
lookupListDefault d = (fromMaybe d .) . lookupList
where lookupList l m = msum $ map (`M.lookup` m) l
@@ -1502,12 +1502,15 @@ macroDef =
guardDisabled Ext_latex_macros <|>
updateState (\s -> s{ sMacros = M.insert name macro' (sMacros s) })
environmentDef = do
- (name, macro1, macro2) <- newenvironment
- guardDisabled Ext_latex_macros <|>
- do updateState $ \s -> s{ sMacros =
- M.insert name macro1 (sMacros s) }
- updateState $ \s -> s{ sMacros =
- M.insert ("end" <> name) macro2 (sMacros s) }
+ mbenv <- newenvironment
+ case mbenv of
+ Nothing -> return ()
+ Just (name, macro1, macro2) -> do
+ guardDisabled Ext_latex_macros <|>
+ do updateState $ \s -> s{ sMacros =
+ M.insert name macro1 (sMacros s) }
+ updateState $ \s -> s{ sMacros =
+ M.insert ("end" <> name) macro2 (sMacros s) }
-- @\newenvironment{envname}[n-args][default]{begin}{end}@
-- is equivalent to
-- @\newcommand{\envname}[n-args][default]{begin}@
@@ -1580,14 +1583,16 @@ newcommand = do
: (contents' ++
[ Tok pos Symbol "}", Tok pos Symbol "}" ])
_ -> contents'
- when (mtype == "newcommand") $ do
- macros <- sMacros <$> getState
- case M.lookup name macros of
- Just _ -> report $ MacroAlreadyDefined (T.unpack txt) pos
- Nothing -> return ()
- return (name, Macro ExpandWhenUsed argspecs optarg contents)
-
-newenvironment :: PandocMonad m => LP m (Text, Macro, Macro)
+ macros <- sMacros <$> getState
+ case M.lookup name macros of
+ Just macro
+ | mtype == "newcommand" -> do
+ report $ MacroAlreadyDefined (T.unpack txt) pos
+ return (name, macro)
+ | mtype == "providecommand" -> return (name, macro)
+ _ -> return (name, Macro ExpandWhenUsed argspecs optarg contents)
+
+newenvironment :: PandocMonad m => LP m (Maybe (Text, Macro, Macro))
newenvironment = do
pos <- getPosition
Tok _ (CtrlSeq mtype) _ <- controlSeq "newenvironment" <|>
@@ -1604,13 +1609,17 @@ newenvironment = do
let argspecs = map (\i -> ArgNum i) [1..numargs]
startcontents <- spaces >> bracedOrToken
endcontents <- spaces >> bracedOrToken
- when (mtype == "newenvironment") $ do
- macros <- sMacros <$> getState
- case M.lookup name macros of
- Just _ -> report $ MacroAlreadyDefined (T.unpack name) pos
- Nothing -> return ()
- return (name, Macro ExpandWhenUsed argspecs optarg startcontents,
- Macro ExpandWhenUsed [] Nothing endcontents)
+ macros <- sMacros <$> getState
+ case M.lookup name macros of
+ Just _
+ | mtype == "newenvironment" -> do
+ report $ MacroAlreadyDefined (T.unpack name) pos
+ return Nothing
+ | mtype == "provideenvironment" -> do
+ return Nothing
+ _ -> return $ Just (name,
+ Macro ExpandWhenUsed argspecs optarg startcontents,
+ Macro ExpandWhenUsed [] Nothing endcontents)
bracketedNum :: PandocMonad m => LP m Int
bracketedNum = do
@@ -1640,6 +1649,12 @@ looseItem = do
skipopts
return mempty
+epigraph :: PandocMonad m => LP m Blocks
+epigraph = do
+ p1 <- grouped blocks
+ p2 <- grouped blocks
+ return $ divWith ("", ["epigraph"], []) (p1 <> p2)
+
resetCaption :: PandocMonad m => LP m ()
resetCaption = updateState $ \st -> st{ sCaption = (Nothing, Nothing) }
@@ -1795,6 +1810,8 @@ blockCommands = M.fromList
, ("usepackage", include "usepackage")
-- preamble
, ("PackageError", mempty <$ (braced >> braced >> braced))
+ -- epigraph package
+ , ("epigraph", epigraph)
]
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index a9676c960..c21fd00c3 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -323,8 +323,7 @@ parseItalic [] = do
parseItalic args = return $
emph $ mconcat $ intersperse B.space $ map linePartsToInlines args
-parseAlternatingFonts :: PandocMonad m
- => [Inlines -> Inlines]
+parseAlternatingFonts :: [Inlines -> Inlines]
-> [Arg]
-> ManParser m Inlines
parseAlternatingFonts constructors args = return $ mconcat $
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index ab5aa6b05..3d2ba490d 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -857,7 +857,8 @@ listLine continuationIndent = try $ do
listLineCommon :: PandocMonad m => MarkdownParser m String
listLineCommon = concat <$> manyTill
- ( many1 (satisfy $ \c -> c /= '\n' && c /= '<')
+ ( many1 (satisfy $ \c -> c `notElem` ['\n', '<', '`'])
+ <|> fmap snd (withRaw code)
<|> fmap snd (htmlTag isCommentTag)
<|> count 1 anyChar
) newline
@@ -932,14 +933,14 @@ listItem :: PandocMonad m
-> MarkdownParser m a
-> MarkdownParser m (F Blocks)
listItem fourSpaceRule start = try $ do
- (first, continuationIndent) <- rawListItem fourSpaceRule start
- continuations <- many (listContinuation continuationIndent)
-- parsing with ListItemState forces markers at beginning of lines to
-- count as list item markers, even if not separated by blank space.
-- see definition of "endline"
state <- getState
let oldContext = stateParserContext state
setState $ state {stateParserContext = ListItemState}
+ (first, continuationIndent) <- rawListItem fourSpaceRule start
+ continuations <- many (listContinuation continuationIndent)
-- parse the extracted block, which may contain various block elements:
let raw = concat (first:continuations)
contents <- parseFromString' parseBlocks raw
@@ -1583,8 +1584,9 @@ code = try $ do
starts <- many1 (char '`')
skipSpaces
result <- (trim . concat) <$>
- manyTill (many1 (noneOf "`\n") <|> many1 (char '`') <|>
- (char '\n' >> notFollowedBy' blankline >> return " "))
+ manyTill (notFollowedBy (inList >> listStart) >>
+ (many1 (noneOf "`\n") <|> many1 (char '`') <|>
+ (char '\n' >> notFollowedBy' blankline >> return " ")))
(try (skipSpaces >> count (length starts) (char '`') >>
notFollowedBy (char '`')))
rawattr <-
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 9c409510f..46ddc4257 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -772,7 +772,7 @@ bulletList = try $ do
fmap (B.bulletList . compactify) . sequence
<$> many1 (listItem (bulletListStart `indented` indent))
-indented :: Monad m => OrgParser m Int -> Int -> OrgParser m Int
+indented :: OrgParser m Int -> Int -> OrgParser m Int
indented indentedMarker minIndent = try $ do
n <- indentedMarker
guard (minIndent <= n)
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index b54f5ccbf..105d27088 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -645,7 +645,7 @@ directive' = do
name = trim $ fromMaybe "" (lookup "name" fields)
classes = words $ maybe "" trim (lookup "class" fields)
keyvals = [(k, trim v) | (k, v) <- fields, k /= "name", k /= "class"]
- imgAttr cl = ("", classes ++ alignClasses, widthAttr ++ heightAttr)
+ imgAttr cl = (name, classes ++ alignClasses, widthAttr ++ heightAttr)
where
alignClasses = words $ maybe "" trim (lookup cl fields) ++
maybe "" (\x -> "align-" ++ trim x)
diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs
index 8e01a80f8..5daf6b0bb 100644
--- a/src/Text/Pandoc/Readers/TikiWiki.hs
+++ b/src/Text/Pandoc/Readers/TikiWiki.hs
@@ -54,10 +54,10 @@ type TikiWikiParser = ParserT [Char] ParserState
-- utility functions
--
-tryMsg :: PandocMonad m => String -> TikiWikiParser m a -> TikiWikiParser m a
+tryMsg :: String -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg msg p = try p <?> msg
-skip :: PandocMonad m => TikiWikiParser m a -> TikiWikiParser m ()
+skip :: TikiWikiParser m a -> TikiWikiParser m ()
skip parser = Control.Monad.void parser
nested :: PandocMonad m => TikiWikiParser m a -> TikiWikiParser m a
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 82b6e8221..fdcab1442 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -41,6 +41,7 @@ import qualified Text.Pandoc.Class as P
import Data.Time
import Text.Pandoc.Definition
import Text.Pandoc.Error
+import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.MIME (MimeType, extensionFromMimeType, getMimeType)
import Text.Pandoc.Options (EPUBVersion (..), HTMLMathMethod (..),
@@ -450,14 +451,23 @@ pandocToEPUB version opts doc = do
Nothing -> return ([],[])
Just img -> do
let coverImage = takeFileName img
+ imgContent <- lift $ P.readFileLazy img
+ (coverImageWidth, coverImageHeight) <-
+ case imageSize opts' (B.toStrict imgContent) of
+ Right sz -> return $ sizeInPixels sz
+ Left err' -> (0, 0) <$ report
+ (CouldNotDetermineImageSize img err')
cpContent <- lift $ writeHtml
opts'{ writerVariables =
("coverpage","true"):
("pagetitle",
escapeStringForXML plainTitle):
+ ("cover-image", coverImage):
+ ("cover-image-width", show coverImageWidth):
+ ("cover-image-height",
+ show coverImageHeight):
cssvars True ++ vars }
- (Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"../media/" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"])
- imgContent <- lift $ P.readFileLazy img
+ (Pandoc meta [])
coverEntry <- mkEntry "text/cover.xhtml" cpContent
coverImageEntry <- mkEntry ("media/" ++ coverImage)
imgContent
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index ca44583ab..241479157 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -621,6 +621,7 @@ toAttrs kvs = do
if x `Set.member` (html5Attributes <> rdfaAttributes)
|| ':' `elem` x -- e.g. epub: namespace
|| "data-" `isPrefixOf` x
+ || "aria-" `isPrefixOf` x
then Just $ customAttribute (fromString x) (toValue y)
else Just $ customAttribute (fromString ("data-" ++ x))
(toValue y)
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index 145d37bee..61a68d543 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -88,7 +88,9 @@ docToJATS opts (Pandoc meta blocks) = do
mapM (elementToJATS opts' startLvl) elements
notes <- reverse . map snd <$> gets jatsNotes
backs <- mapM (elementToJATS opts' startLvl) backElements
- let fns = inTagsIndented "fn-group" $ vcat notes
+ let fns = if null notes
+ then mempty
+ else inTagsIndented "fn-group" $ vcat notes
let back = render' $ vcat backs $$ fns
let date = case getField "date" metadata -- an object
`mplus`
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index 1f55be797..a9163b3b9 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -63,7 +63,7 @@ import Text.Pandoc.XML (escapeStringForXML)
-- Variables overwrite metadata fields with the same names.
-- If multiple variables are set with the same name, a list is
-- assigned. Does nothing if 'writerTemplate' is Nothing.
-metaToJSON :: (Functor m, Monad m, ToJSON a)
+metaToJSON :: (Monad m, ToJSON a)
=> WriterOptions
-> ([Block] -> m a)
-> ([Inline] -> m a)
@@ -76,7 +76,7 @@ metaToJSON opts blockWriter inlineWriter meta
-- | Like 'metaToJSON', but does not include variables and is
-- not sensitive to 'writerTemplate'.
-metaToJSON' :: (Functor m, Monad m, ToJSON a)
+metaToJSON' :: (Monad m, ToJSON a)
=> ([Block] -> m a)
-> ([Inline] -> m a)
-> Meta
@@ -99,7 +99,7 @@ addVariablesToJSON opts metadata =
where combineMetadata (Object o1) (Object o2) = Object $ H.union o1 o2
combineMetadata x _ = x
-metaValueToJSON :: (Functor m, Monad m, ToJSON a)
+metaValueToJSON :: (Monad m, ToJSON a)
=> ([Block] -> m a)
-> ([Inline] -> m a)
-> MetaValue
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 7a1261eb2..49d54c9c8 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -192,7 +192,7 @@ assertFilterConversion msg filterPath docIn expectedDoc = do
roundtripEqual :: (Eq a, Lua.Peekable a, Lua.Pushable a) => a -> IO Bool
roundtripEqual x = (x ==) <$> roundtripped
where
- roundtripped :: (Lua.Peekable a, Lua.Pushable a) => IO a
+ roundtripped :: Lua.Peekable a => IO a
roundtripped = runLuaTest $ do
oldSize <- Lua.gettop
Lua.push x
diff --git a/test/command/3523.md b/test/command/3523.md
new file mode 100644
index 000000000..cb0089489
--- /dev/null
+++ b/test/command/3523.md
@@ -0,0 +1,31 @@
+```
+% pandoc -f latex -t html
+\documentclass{article}
+\usepackage{epigraph}
+\begin{document}
+
+\epigraph{
+ Das Recht hat kein Dasein f{\"u}r sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.
+
+ Das Recht hat kein Dasein f{\"u}r sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.
+
+ \begin{itemize}
+ \item hey
+ \item hey
+ \item hey
+ \end{itemize}
+
+ }{ Friedrich Carl von Savigny }
+\end{document}
+^D
+<div class="epigraph">
+<p>Das Recht hat kein Dasein f<span>ü</span>r sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.</p>
+<p>Das Recht hat kein Dasein f<span>ü</span>r sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.</p>
+<ul>
+<li><p>hey</p></li>
+<li><p>hey</p></li>
+<li><p>hey</p></li>
+</ul>
+<p>Friedrich Carl von Savigny</p>
+</div>
+```
diff --git a/test/command/5619.md b/test/command/5619.md
new file mode 100644
index 000000000..776d57acc
--- /dev/null
+++ b/test/command/5619.md
@@ -0,0 +1,10 @@
+```
+% pandoc -f rst -t native
+.. figure:: img1.jpg
+ :width: 1in
+ :name: test
+
+ The caption. Here's what piggybacking on caption would look like {#fig:1}
+^D
+[Para [Image ("test",[],[("width","1in")]) [Str "The",Space,Str "caption.",Space,Str "Here's",Space,Str "what",Space,Str "piggybacking",Space,Str "on",Space,Str "caption",Space,Str "would",Space,Str "look",Space,Str "like",Space,Str "{#fig:1}"] ("img1.jpg","fig:")]]
+```
diff --git a/test/command/5627.md b/test/command/5627.md
new file mode 100644
index 000000000..0f67a083f
--- /dev/null
+++ b/test/command/5627.md
@@ -0,0 +1,83 @@
+```
+% pandoc -t html
+## Example
+
+1. One
+2. Two `-->something<!--`
+3. Three
+
+~~~html
+--><!--<script>alert('Escaped!')</script>
+~~~
+
+~~~html
+Something
+~~~
+^D
+<h2 id="example">Example</h2>
+<ol type="1">
+<li>One</li>
+<li>Two <code>--&gt;something&lt;!--</code></li>
+<li>Three</li>
+</ol>
+<div class="sourceCode" id="cb1"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb1-1"><a href="#cb1-1"></a>--&gt;<span class="co">&lt;!--&lt;script&gt;alert(&#39;Escaped!&#39;)&lt;/script&gt;</span></span></code></pre></div>
+<div class="sourceCode" id="cb2"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb2-1"><a href="#cb2-1"></a>Something</span></code></pre></div>
+```
+
+```
+% pandoc -t html
+## Example 2
+
+- `-->something<!--`
+- `-->something<!--`
+- bye `-->something else<!--`
+
+~~~html
+--><!--<script>alert('Escaped!')</script>
+~~~
+
+~~~html
+Something
+~~~
+^D
+<h2 id="example-2">Example 2</h2>
+<ul>
+<li><code>--&gt;something&lt;!--</code></li>
+<li><code>--&gt;something&lt;!--</code></li>
+<li>bye <code>--&gt;something else&lt;!--</code></li>
+</ul>
+<div class="sourceCode" id="cb1"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb1-1"><a href="#cb1-1"></a>--&gt;<span class="co">&lt;!--&lt;script&gt;alert(&#39;Escaped!&#39;)&lt;/script&gt;</span></span></code></pre></div>
+<div class="sourceCode" id="cb2"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb2-1"><a href="#cb2-1"></a>Something</span></code></pre></div>
+```
+
+```
+% pandoc -t html
+## Example 3
+
+1. `-->one<!--`
+5. bye `-->two <!--`
+3. ` three, not in block
+1. four, not in block `
+2. five
+5. six
+6. seven `
+- separate unordered list `
+42. forty-two, separate ordered list
+^D
+<h2 id="example-3">Example 3</h2>
+<ol type="1">
+<li><code>--&gt;one&lt;!--</code></li>
+<li>bye <code>--&gt;two &lt;!--</code></li>
+<li>` three, not in block</li>
+<li>four, not in block `</li>
+<li>five</li>
+<li>six</li>
+<li>seven `</li>
+</ol>
+<ul>
+<li>separate unordered list `</li>
+</ul>
+<ol start="42" type="1">
+<li>forty-two, separate ordered list</li>
+</ol>
+```
diff --git a/test/command/5635.md b/test/command/5635.md
new file mode 100644
index 000000000..72440616f
--- /dev/null
+++ b/test/command/5635.md
@@ -0,0 +1,23 @@
+```
+% pandoc -f latex -t plain
+\providecommand{\test}{foo}
+\providecommand{\test}{bar}
+
+The value is: \test
+^D
+The value is: foo
+```
+
+```
+% pandoc -f latex -t plain
+\provideenvironment{test}{startfoo}{stopfoo}
+\provideenvironment{test}{startbar}{stopbar}
+
+\begin{test}
+Hi
+\end{test}
+^D
+startfoo Hi stopfoo
+```
+
+
diff --git a/test/command/5642.md b/test/command/5642.md
new file mode 100644
index 000000000..7fe8f5a5f
--- /dev/null
+++ b/test/command/5642.md
@@ -0,0 +1,8 @@
+```
+% pandoc -t html5 -f markdown
+![test](foo){aria-describedby="barbaz"}
+^D
+<figure>
+<img src="foo" aria-describedby="barbaz" alt="" /><figcaption>test</figcaption>
+</figure>
+```
diff --git a/test/writer.jats b/test/writer.jats
index 7bbf8304d..8df981cc3 100644
--- a/test/writer.jats
+++ b/test/writer.jats
@@ -1,7 +1,7 @@
<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.0 20120330//EN"
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.1 20151215//EN"
"JATS-journalpublishing1.dtd">
-<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.0" article-type="other">
+<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.1" article-type="other">
<front>
<journal-meta>
<journal-title-group>
diff --git a/tools/diff-zip.sh b/tools/diff-zip.sh
new file mode 100755
index 000000000..fa88035f6
--- /dev/null
+++ b/tools/diff-zip.sh
@@ -0,0 +1,26 @@
+#!/bin/sh
+
+# This script allows you to compare two epub, odt, or docx
+# containers, ignoring insignificant formatting differences
+# in the XML contents.
+
+f1="$1"
+f2="$2"
+test -f "$f1" -a -f "$f2" || {
+ echo "Usage: diff-zip firstfile secondfile" && exit 1
+}
+WORKDIR=$(mktemp -d -t diff-zip.XXX)
+trap "{ rm -r $WORKDIR; }" EXIT
+unzip -q -d "$WORKDIR/a" "$f1"
+unzip -q -d "$WORKDIR/b" "$f2"
+cd "$WORKDIR"
+mkdir tidy
+for x in a b; do
+ cp -r $x tidy/
+ find $x -regextype posix-extended -iregex '.*\.(xhtml|xml|rdf|rels)' -exec sh -c 'mkdir -p "$(dirname tidy/$1)" && tidy -q -xml -utf8 -i "$1" > "tidy/$1"' _ {} \;
+done
+cd tidy
+mkdir c
+cp -r a/* c/
+cp -r b/* c/
+find c -type f -exec sh -c 'echo -e "\033[1m=== ${1#*/} ===\033[0m" ; diff -u "a/${1#*/}" "b/${1#*/}" 2>&1' _ {} \;