aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt5
-rw-r--r--data/templates/article.jats_publishing (renamed from data/templates/default.jats)9
-rw-r--r--data/templates/default.jats_archiving7
-rw-r--r--data/templates/default.jats_articleauthoring90
-rw-r--r--data/templates/default.jats_publishing7
-rw-r--r--pandoc.cabal13
-rw-r--r--src/Text/Pandoc/Templates.hs1
-rw-r--r--src/Text/Pandoc/Writers.hs8
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs140
-rw-r--r--test/Tests/Old.hs9
-rw-r--r--test/Tests/Writers/JATS.hs16
-rw-r--r--test/tables.jats_archiving (renamed from test/tables.jats)0
-rw-r--r--test/tables.jats_articleauthoring226
-rw-r--r--test/tables.jats_publishing226
-rw-r--r--test/writer.jats_archiving (renamed from test/writer.jats)0
-rw-r--r--test/writer.jats_articleauthoring874
-rw-r--r--test/writer.jats_publishing898
17 files changed, 2474 insertions, 55 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index c90ac7b01..4fb744085 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -294,7 +294,10 @@ header when requesting a document from a URL:
- `html4` ([XHTML] 1.0 Transitional)
- `icml` ([InDesign ICML])
- `ipynb` ([Jupyter notebook])
- - `jats` ([JATS] XML)
+ - `jats_archiving` ([JATS] XML, Archiving and Interchange Tag Set)
+ - `jats_articleauthoring` ([JATS] XML, Article Authoring Tag Set)
+ - `jats_publishing` ([JATS] XML, Journal Publishing Tag Set)
+ - `jats` (alias for `jats_archiving`)
- `jira` ([Jira] wiki markup)
- `json` (JSON version of native AST)
- `latex` ([LaTeX])
diff --git a/data/templates/default.jats b/data/templates/article.jats_publishing
index 20560cdc5..ce184c0ed 100644
--- a/data/templates/default.jats
+++ b/data/templates/article.jats_publishing
@@ -1,9 +1,3 @@
-<?xml version="1.0" encoding="utf-8" ?>
-$if(xml-stylesheet)$
-<?xml-stylesheet type="text/xsl" href="$xml-stylesheet$"?>
-$endif$
-<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Archiving and Interchange DTD v1.2 20190208//EN"
- "JATS-archivearticle1.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.2" article-type="$article.type$">
$else$
@@ -164,8 +158,8 @@ $if(copyright.text)$
<license license-type="$copyright.type$" xlink:href="$copyright.link$">
<license-p>$copyright.text$</license-p>
</license>
-</permissions>
$endif$
+</permissions>
$endif$
$if(abstract)$
<abstract>
@@ -198,3 +192,4 @@ $back$
$endif$
</back>
</article>
+
diff --git a/data/templates/default.jats_archiving b/data/templates/default.jats_archiving
new file mode 100644
index 000000000..9b99aab12
--- /dev/null
+++ b/data/templates/default.jats_archiving
@@ -0,0 +1,7 @@
+<?xml version="1.0" encoding="utf-8" ?>
+$if(xml-stylesheet)$
+<?xml-stylesheet type="text/xsl" href="$xml-stylesheet$"?>
+$endif$
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Archiving and Interchange DTD v1.2 20190208//EN"
+ "JATS-archivearticle1.dtd">
+${ article.jats_publishing() }
diff --git a/data/templates/default.jats_articleauthoring b/data/templates/default.jats_articleauthoring
new file mode 100644
index 000000000..f86bb2d3b
--- /dev/null
+++ b/data/templates/default.jats_articleauthoring
@@ -0,0 +1,90 @@
+<?xml version="1.0" encoding="utf-8" ?>
+$if(xml-stylesheet)$
+<?xml-stylesheet type="text/xsl" href="$xml-stylesheet$"?>
+$endif$
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Article Authoring DTD v1.2 20190208//EN"
+ "JATS-articleauthoring1.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.2" 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.2" article-type="other">
+$endif$
+<front>
+<article-meta>
+$if(title)$
+<title-group>
+<article-title>$title$</article-title>
+</title-group>
+$endif$
+$if(author)$
+<contrib-group>
+$for(author)$
+<contrib contrib-type="author">
+$if(author.orcid)$
+<contrib-id contrib-id-type="orcid">$author.orcid$</contrib-id>
+$endif$
+$if(author.surname)$
+<name>
+<surname>$author.surname$</surname>
+<given-names>$author.given-names$</given-names>
+</name>
+$else$
+<string-name>$author$</string-name>
+$endif$
+$if(author.email)$
+<email>$author.email$</email>
+$endif$
+$if(author.aff-id)$
+<xref ref-type="aff" rid="aff-$contrib.aff-id$"/>
+$endif$
+$if(author.cor-id)$
+<xref ref-type="corresp" rid="cor-$author.cor-id$"><sup>*</sup></xref>
+$endif$
+</contrib>
+$endfor$
+</contrib-group>
+$endif$
+$if(copyright)$
+<permissions>
+$if(copyright.statement)$
+<copyright-statement>$copyright.statement$</copyright-statement>
+$endif$
+$if(copyright.year)$
+<copyright-year>$copyright.year$</copyright-year>
+$endif$
+$if(copyright.holder)$
+<copyright-holder>$copyright.holder$</copyright-holder>
+$endif$
+$if(copyright.text)$
+<license license-type="$copyright.type$" xlink:href="$copyright.link$">
+<license-p>$copyright.text$</license-p>
+</license>
+$endif$
+</permissions>
+$endif$
+<abstract>
+$abstract$
+</abstract>
+$if(tags)$
+<kwd-group kwd-group-type="author">
+$for(tags)$
+<kwd>$tags$</kwd>
+$endfor$
+</kwd-group>
+$endif$
+$if(article.funding-statement)$
+<funding-group>
+<funding-statement>$article.funding-statement$</funding-statement>
+</funding-group>
+$endif$
+</article-meta>
+</front>
+<body>
+$body$
+</body>
+<back>
+$if(back)$
+$back$
+$endif$
+</back>
+</article>
diff --git a/data/templates/default.jats_publishing b/data/templates/default.jats_publishing
new file mode 100644
index 000000000..79e9b00d8
--- /dev/null
+++ b/data/templates/default.jats_publishing
@@ -0,0 +1,7 @@
+<?xml version="1.0" encoding="utf-8" ?>
+$if(xml-stylesheet)$
+<?xml-stylesheet type="text/xsl" href="$xml-stylesheet$"?>
+$endif$
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.2 20190208//EN"
+ "JATS-publishing1.dtd">
+${ article.jats_publishing() }
diff --git a/pandoc.cabal b/pandoc.cabal
index 3b8e84634..95c85bf75 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -46,7 +46,9 @@ data-files:
data/templates/default.html5
data/templates/default.docbook4
data/templates/default.docbook5
- data/templates/default.jats
+ data/templates/default.jats_archiving
+ data/templates/default.jats_articleauthoring
+ data/templates/default.jats_publishing
data/templates/default.tei
data/templates/default.opendocument
data/templates/default.icml
@@ -79,6 +81,7 @@ data-files:
data/templates/default.org
data/templates/default.epub2
data/templates/default.epub3
+ data/templates/article.jats_publishing
-- translations
data/translations/*.yaml
-- source files for reference.docx
@@ -254,7 +257,9 @@ extra-source-files:
test/tables.context
test/tables.docbook4
test/tables.docbook5
- test/tables.jats
+ test/tables.jats_archiving
+ test/tables.jats_articleauthoring
+ test/tables.jats_publishing
test/tables.jira
test/tables.dokuwiki
test/tables.zimwiki
@@ -286,7 +291,9 @@ extra-source-files:
test/writer.context
test/writer.docbook4
test/writer.docbook5
- test/writer.jats
+ test/writer.jats_archiving
+ test/writer.jats_articleauthoring
+ test/writer.jats_publishing
test/writer.jira
test/writer.html4
test/writer.html5
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index f04a73b58..6444728ae 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -90,6 +90,7 @@ getDefaultTemplate writer = do
"docbook" -> getDefaultTemplate "docbook5"
"epub" -> getDefaultTemplate "epub3"
"beamer" -> getDefaultTemplate "latex"
+ "jats" -> getDefaultTemplate "jats_archiving"
"markdown_strict" -> getDefaultTemplate "markdown"
"multimarkdown" -> getDefaultTemplate "markdown"
"markdown_github" -> getDefaultTemplate "markdown"
diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs
index 753972855..cdf3ca1c8 100644
--- a/src/Text/Pandoc/Writers.hs
+++ b/src/Text/Pandoc/Writers.hs
@@ -41,6 +41,9 @@ module Text.Pandoc.Writers
, writeHtml5String
, writeICML
, writeJATS
+ , writeJatsArchiving
+ , writeJatsArticleAuthoring
+ , writeJatsPublishing
, writeJSON
, writeJira
, writeLaTeX
@@ -146,7 +149,10 @@ writers = [
,("docbook" , TextWriter writeDocbook5)
,("docbook4" , TextWriter writeDocbook4)
,("docbook5" , TextWriter writeDocbook5)
- ,("jats" , TextWriter writeJATS)
+ ,("jats" , TextWriter writeJatsArchiving)
+ ,("jats_articleauthoring", TextWriter writeJatsArticleAuthoring)
+ ,("jats_publishing" , TextWriter writeJatsPublishing)
+ ,("jats_archiving" , TextWriter writeJatsArchiving)
,("jira" , TextWriter writeJira)
,("opml" , TextWriter writeOPML)
,("opendocument" , TextWriter writeOpenDocument)
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index ab95110bf..49ace4636 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.JATS
- Copyright : Copyright (C) 2017-2019 John MacFarlane
+ Copyright : Copyright (C) 2017-2020 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -15,7 +15,12 @@ Conversion of 'Pandoc' documents to JATS XML.
Reference:
https://jats.nlm.nih.gov/publishing/tag-library
-}
-module Text.Pandoc.Writers.JATS ( writeJATS ) where
+module Text.Pandoc.Writers.JATS
+ ( writeJATS
+ , writeJatsArchiving
+ , writeJatsPublishing
+ , writeJatsArticleAuthoring
+ ) where
import Prelude
import Control.Monad.Reader
import Control.Monad.State
@@ -43,19 +48,46 @@ import Text.Pandoc.XML
import Text.TeXMath
import qualified Text.XML.Light as Xml
-data JATSVersion = JATS1_1
- deriving (Eq, Show)
+-- | JATS tag set variant
+data JATSTagSet
+ = TagSetArchiving -- ^ Archiving and Interchange Tag Set
+ | TagSetPublishing -- ^ Journal Publishing Tag Set
+ | TagSetArticleAuthoring -- ^ Article Authoring Tag Set
+ deriving (Eq)
-data JATSState = JATSState
+-- | Internal state used by the writer.
+newtype JATSState = JATSState
{ jatsNotes :: [(Int, Doc Text)] }
-type JATS a = StateT JATSState (ReaderT JATSVersion a)
+-- | JATS writer type
+type JATS a = StateT JATSState (ReaderT JATSTagSet a)
+-- | Convert a @'Pandoc'@ document to JATS (Archiving and Interchange
+-- Tag Set.)
+writeJatsArchiving :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeJatsArchiving = writeJats TagSetArchiving
+
+-- | Convert a @'Pandoc'@ document to JATS (Journal Publishing Tag Set.)
+writeJatsPublishing :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeJatsPublishing = writeJats TagSetPublishing
+
+-- | Convert a @'Pandoc'@ document to JATS (Archiving and Interchange
+-- Tag Set.)
+writeJatsArticleAuthoring :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeJatsArticleAuthoring = writeJats TagSetArticleAuthoring
+
+-- | Alias for @'writeJatsArchiving'@. This function exists for backwards
+-- compatibility, but will be deprecated in the future. Use
+-- @'writeJatsArchiving'@ instead.
writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m Text
-writeJATS opts d =
+writeJATS = writeJatsArchiving
+
+-- | Convert a @'Pandoc'@ document to JATS.
+writeJats :: PandocMonad m => JATSTagSet -> WriterOptions -> Pandoc -> m Text
+writeJats tagSet opts d =
runReaderT (evalStateT (docToJATS opts d)
- (JATSState{ jatsNotes = [] }))
- JATS1_1
+ (JATSState{ jatsNotes = [] }))
+ tagSet
-- | Convert Pandoc document to string in JATS format.
docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> JATS m Text
@@ -80,7 +112,10 @@ docToJATS opts (Pandoc meta blocks) = do
main <- fromBlocks bodyblocks
notes <- reverse . map snd <$> gets jatsNotes
backs <- fromBlocks backblocks
- let fns = if null notes
+ tagSet <- ask
+ -- In the "Article Authoring" tag set, occurrence of fn-group elements
+ -- is restricted to table footers. Footnotes have to be placed inline.
+ let fns = if null notes || tagSet == TagSetArticleAuthoring
then mempty
else inTagsIndented "fn-group" $ vcat notes
let back = backs $$ fns
@@ -116,6 +151,8 @@ docToJATS opts (Pandoc meta blocks) = do
blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> JATS m (Doc Text)
blocksToJATS = wrappedBlocksToJATS (const False)
+-- | Like @'blocksToJATS'@, but wraps top-level blocks into a @<p>@
+-- element if the @needsWrap@ predicate evaluates to @True@.
wrappedBlocksToJATS :: PandocMonad m
=> (Block -> Bool)
-> WriterOptions
@@ -275,8 +312,12 @@ blockToJATS opts (Para lst) =
inTagsSimple "p" <$> inlinesToJATS opts lst
blockToJATS opts (LineBlock lns) =
blockToJATS opts $ linesToPara lns
-blockToJATS opts (BlockQuote blocks) =
- inTagsIndented "disp-quote" <$> blocksToJATS opts blocks
+blockToJATS opts (BlockQuote blocks) = do
+ tagSet <- ask
+ let blocksToJats' = if tagSet == TagSetArticleAuthoring
+ then wrappedBlocksToJATS (not . isPara)
+ else blocksToJATS
+ inTagsIndented "disp-quote" <$> blocksToJats' opts blocks
blockToJATS _ (CodeBlock a str) = return $
inTags False tag attr (flush (text (T.unpack $ escapeStringForXML str)))
where (lang, attr) = codeAttr a
@@ -287,14 +328,20 @@ blockToJATS opts (BulletList lst) =
listItemsToJATS opts Nothing lst
blockToJATS _ (OrderedList _ []) = return empty
blockToJATS opts (OrderedList (start, numstyle, delimstyle) items) = do
- let listType = case numstyle of
- DefaultStyle -> "order"
- Decimal -> "order"
- Example -> "order"
- UpperAlpha -> "alpha-upper"
- LowerAlpha -> "alpha-lower"
- UpperRoman -> "roman-upper"
- LowerRoman -> "roman-lower"
+ tagSet <- ask
+ let listType =
+ -- The Article Authoring tag set doesn't allow a more specific
+ -- @list-type@ attribute than "order".
+ if tagSet == TagSetArticleAuthoring
+ then "order"
+ else case numstyle of
+ DefaultStyle -> "order"
+ Decimal -> "order"
+ Example -> "order"
+ UpperAlpha -> "alpha-upper"
+ LowerAlpha -> "alpha-lower"
+ UpperRoman -> "roman-upper"
+ LowerRoman -> "roman-lower"
let simpleList = start == 1 && (delimstyle == DefaultDelim ||
delimstyle == Period)
let markers = if simpleList
@@ -407,17 +454,22 @@ inlineToJATS opts SoftBreak
| writerWrapText opts == WrapPreserve = return cr
| otherwise = return space
inlineToJATS opts (Note contents) = do
- notes <- gets jatsNotes
- let notenum = case notes of
- (n, _):_ -> n + 1
- [] -> 1
- thenote <- inTags True "fn" [("id","fn" <> tshow notenum)]
- <$> wrappedBlocksToJATS (not . isPara) opts
- (walk demoteHeaderAndRefs contents)
- modify $ \st -> st{ jatsNotes = (notenum, thenote) : notes }
- return $ inTags False "xref" [("ref-type", "fn"),
- ("rid", "fn" <> tshow notenum)]
- $ text (show notenum)
+ tagSet <- ask
+ -- Footnotes must occur inline when using the Article Authoring tag set.
+ if tagSet == TagSetArticleAuthoring
+ then inTagsIndented "fn" <$> wrappedBlocksToJATS (not . isPara) opts contents
+ else do
+ notes <- gets jatsNotes
+ let notenum = case notes of
+ (n, _):_ -> n + 1
+ [] -> 1
+ thenote <- inTags True "fn" [("id","fn" <> tshow notenum)]
+ <$> wrappedBlocksToJATS (not . isPara) opts
+ (walk demoteHeaderAndRefs contents)
+ modify $ \st -> st{ jatsNotes = (notenum, thenote) : notes }
+ return $ inTags False "xref" [("ref-type", "fn"),
+ ("rid", "fn" <> tshow notenum)]
+ $ text (show notenum)
inlineToJATS opts (Cite _ lst) =
-- TODO revisit this after examining the jats.csl pipeline
inlinesToJATS opts lst
@@ -444,16 +496,22 @@ inlineToJATS _ (Math t str) = do
let tagtype = case t of
DisplayMath -> "disp-formula"
InlineMath -> "inline-formula"
- let rawtex = inTagsSimple "tex-math"
- $ text "<![CDATA[" <>
- literal str <>
- text "]]>"
- return $ inTagsSimple tagtype $
- case res of
- Right r -> inTagsSimple "alternatives" $
- cr <> rawtex $$
- text (Xml.ppcElement conf $ fixNS r)
- Left _ -> rawtex
+
+ let rawtex = text "<![CDATA[" <> literal str <> text "]]>"
+ let texMath = inTagsSimple "tex-math" rawtex
+
+ tagSet <- ask
+ return . inTagsSimple tagtype $
+ case res of
+ Right r -> let mathMl = text (Xml.ppcElement conf $ fixNS r)
+ -- tex-math is unsupported in Article Authoring tag set
+ in if tagSet == TagSetArticleAuthoring
+ then mathMl
+ else inTagsSimple "alternatives" $
+ cr <> texMath $$ mathMl
+ Left _ -> if tagSet /= TagSetArticleAuthoring
+ then texMath
+ else rawtex
inlineToJATS _ (Link _attr [Str t] (T.stripPrefix "mailto:" -> Just email, _))
| escapeURI t == email =
return $ inTagsSimple "email" $ literal (escapeStringForXML email)
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 3543cdbb3..2851db5d4 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -94,7 +94,14 @@ tests pandocPath =
[ testGroup "writer" $ writerTests' "docbook5"
]
, testGroup "jats"
- [ testGroup "writer" $ writerTests' "jats"
+ [ testGroup "writer"
+ [ testGroup "jats_archiving" $
+ writerTests' "jats_archiving"
+ , testGroup "jats_articleauthoring" $
+ writerTests' "jats_articleauthoring"
+ , testGroup "jats_publishing" $
+ writerTests' "jats_publishing"
+ ]
, test' "reader" ["-r", "jats", "-w", "native", "-s"]
"jats-reader.xml" "jats-reader.native"
]
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
index 6de058701..7d98f979b 100644
--- a/test/Tests/Writers/JATS.hs
+++ b/test/Tests/Writers/JATS.hs
@@ -11,7 +11,14 @@ import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
jats :: (ToPandoc a) => a -> String
-jats = unpack . purely (writeJATS def{ writerWrapText = WrapNone }) . toPandoc
+jats = unpack
+ . purely (writeJATS def{ writerWrapText = WrapNone })
+ . toPandoc
+
+jatsArticleAuthoring :: (ToPandoc a) => a -> String
+jatsArticleAuthoring = unpack
+ . purely (writeJatsArticleAuthoring def{ writerWrapText = WrapNone })
+ . toPandoc
{-
"my test" =: X =?> Y
@@ -47,6 +54,13 @@ tests = [ testGroup "inline code"
, testGroup "inlines"
[ "Emphasis" =: emph "emphasized"
=?> "<p><italic>emphasized</italic></p>"
+
+ , test jatsArticleAuthoring "footnote in articleauthoring tag set"
+ ("test" <> note (para "footnote") =?>
+ unlines [ "<p>test<fn>"
+ , " <p>footnote</p>"
+ , "</fn></p>"
+ ])
]
, "bullet list" =: bulletList [ plain $ text "first"
, plain $ text "second"
diff --git a/test/tables.jats b/test/tables.jats_archiving
index 70f71e384..70f71e384 100644
--- a/test/tables.jats
+++ b/test/tables.jats_archiving
diff --git a/test/tables.jats_articleauthoring b/test/tables.jats_articleauthoring
new file mode 100644
index 000000000..70f71e384
--- /dev/null
+++ b/test/tables.jats_articleauthoring
@@ -0,0 +1,226 @@
+<p>Simple table with caption:</p>
+<table-wrap>
+ <caption>
+ <p>Demonstration of simple table syntax.</p>
+ </caption>
+ <table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>Right</th>
+ <th>Left</th>
+ <th>Center</th>
+ <th>Default</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+ </table>
+</table-wrap>
+<p>Simple table without caption:</p>
+<table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>Right</th>
+ <th>Left</th>
+ <th>Center</th>
+ <th>Default</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+</table>
+<p>Simple table indented two spaces:</p>
+<table-wrap>
+ <caption>
+ <p>Demonstration of simple table syntax.</p>
+ </caption>
+ <table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>Right</th>
+ <th>Left</th>
+ <th>Center</th>
+ <th>Default</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+ </table>
+</table-wrap>
+<p>Multiline table with caption:</p>
+<table-wrap>
+ <caption>
+ <p>Here’s the caption. It may span multiple lines.</p>
+ </caption>
+ <table>
+ <col width="15*" align="center" />
+ <col width="13*" align="left" />
+ <col width="16*" align="right" />
+ <col width="35*" align="left" />
+ <thead>
+ <tr>
+ <th>Centered Header</th>
+ <th>Left Aligned</th>
+ <th>Right Aligned</th>
+ <th>Default aligned</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>First</td>
+ <td>row</td>
+ <td>12.0</td>
+ <td>Example of a row that spans multiple lines.</td>
+ </tr>
+ <tr>
+ <td>Second</td>
+ <td>row</td>
+ <td>5.0</td>
+ <td>Here’s another one. Note the blank line between rows.</td>
+ </tr>
+ </tbody>
+ </table>
+</table-wrap>
+<p>Multiline table without caption:</p>
+<table>
+ <col width="15*" align="center" />
+ <col width="13*" align="left" />
+ <col width="16*" align="right" />
+ <col width="35*" align="left" />
+ <thead>
+ <tr>
+ <th>Centered Header</th>
+ <th>Left Aligned</th>
+ <th>Right Aligned</th>
+ <th>Default aligned</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>First</td>
+ <td>row</td>
+ <td>12.0</td>
+ <td>Example of a row that spans multiple lines.</td>
+ </tr>
+ <tr>
+ <td>Second</td>
+ <td>row</td>
+ <td>5.0</td>
+ <td>Here’s another one. Note the blank line between rows.</td>
+ </tr>
+ </tbody>
+</table>
+<p>Table without column headers:</p>
+<table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="right" />
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+</table>
+<p>Multiline table without column headers:</p>
+<table>
+ <col width="15*" align="center" />
+ <col width="13*" align="left" />
+ <col width="16*" align="right" />
+ <col width="35*" align="left" />
+ <tbody>
+ <tr>
+ <td>First</td>
+ <td>row</td>
+ <td>12.0</td>
+ <td>Example of a row that spans multiple lines.</td>
+ </tr>
+ <tr>
+ <td>Second</td>
+ <td>row</td>
+ <td>5.0</td>
+ <td>Here’s another one. Note the blank line between rows.</td>
+ </tr>
+ </tbody>
+</table>
diff --git a/test/tables.jats_publishing b/test/tables.jats_publishing
new file mode 100644
index 000000000..70f71e384
--- /dev/null
+++ b/test/tables.jats_publishing
@@ -0,0 +1,226 @@
+<p>Simple table with caption:</p>
+<table-wrap>
+ <caption>
+ <p>Demonstration of simple table syntax.</p>
+ </caption>
+ <table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>Right</th>
+ <th>Left</th>
+ <th>Center</th>
+ <th>Default</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+ </table>
+</table-wrap>
+<p>Simple table without caption:</p>
+<table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>Right</th>
+ <th>Left</th>
+ <th>Center</th>
+ <th>Default</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+</table>
+<p>Simple table indented two spaces:</p>
+<table-wrap>
+ <caption>
+ <p>Demonstration of simple table syntax.</p>
+ </caption>
+ <table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>Right</th>
+ <th>Left</th>
+ <th>Center</th>
+ <th>Default</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+ </table>
+</table-wrap>
+<p>Multiline table with caption:</p>
+<table-wrap>
+ <caption>
+ <p>Here’s the caption. It may span multiple lines.</p>
+ </caption>
+ <table>
+ <col width="15*" align="center" />
+ <col width="13*" align="left" />
+ <col width="16*" align="right" />
+ <col width="35*" align="left" />
+ <thead>
+ <tr>
+ <th>Centered Header</th>
+ <th>Left Aligned</th>
+ <th>Right Aligned</th>
+ <th>Default aligned</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>First</td>
+ <td>row</td>
+ <td>12.0</td>
+ <td>Example of a row that spans multiple lines.</td>
+ </tr>
+ <tr>
+ <td>Second</td>
+ <td>row</td>
+ <td>5.0</td>
+ <td>Here’s another one. Note the blank line between rows.</td>
+ </tr>
+ </tbody>
+ </table>
+</table-wrap>
+<p>Multiline table without caption:</p>
+<table>
+ <col width="15*" align="center" />
+ <col width="13*" align="left" />
+ <col width="16*" align="right" />
+ <col width="35*" align="left" />
+ <thead>
+ <tr>
+ <th>Centered Header</th>
+ <th>Left Aligned</th>
+ <th>Right Aligned</th>
+ <th>Default aligned</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>First</td>
+ <td>row</td>
+ <td>12.0</td>
+ <td>Example of a row that spans multiple lines.</td>
+ </tr>
+ <tr>
+ <td>Second</td>
+ <td>row</td>
+ <td>5.0</td>
+ <td>Here’s another one. Note the blank line between rows.</td>
+ </tr>
+ </tbody>
+</table>
+<p>Table without column headers:</p>
+<table>
+ <col align="right" />
+ <col align="left" />
+ <col align="center" />
+ <col align="right" />
+ <tbody>
+ <tr>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ <td>12</td>
+ </tr>
+ <tr>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ <td>123</td>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ <td>1</td>
+ </tr>
+ </tbody>
+</table>
+<p>Multiline table without column headers:</p>
+<table>
+ <col width="15*" align="center" />
+ <col width="13*" align="left" />
+ <col width="16*" align="right" />
+ <col width="35*" align="left" />
+ <tbody>
+ <tr>
+ <td>First</td>
+ <td>row</td>
+ <td>12.0</td>
+ <td>Example of a row that spans multiple lines.</td>
+ </tr>
+ <tr>
+ <td>Second</td>
+ <td>row</td>
+ <td>5.0</td>
+ <td>Here’s another one. Note the blank line between rows.</td>
+ </tr>
+ </tbody>
+</table>
diff --git a/test/writer.jats b/test/writer.jats_archiving
index b7274b0f1..b7274b0f1 100644
--- a/test/writer.jats
+++ b/test/writer.jats_archiving
diff --git a/test/writer.jats_articleauthoring b/test/writer.jats_articleauthoring
new file mode 100644
index 000000000..90437992e
--- /dev/null
+++ b/test/writer.jats_articleauthoring
@@ -0,0 +1,874 @@
+<?xml version="1.0" encoding="utf-8" ?>
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Article Authoring DTD v1.2 20190208//EN"
+ "JATS-articleauthoring1.dtd">
+<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.2" article-type="other">
+<front>
+<article-meta>
+<title-group>
+<article-title>Pandoc Test Suite</article-title>
+</title-group>
+<contrib-group>
+<contrib contrib-type="author">
+<string-name>John MacFarlane</string-name>
+</contrib>
+<contrib contrib-type="author">
+<string-name>Anonymous</string-name>
+</contrib>
+</contrib-group>
+<abstract>
+
+</abstract>
+</article-meta>
+</front>
+<body>
+<p>This is a set of tests for pandoc. Most of them are adapted from John
+Gruber’s markdown test suite.</p>
+<sec id="headers">
+ <title>Headers</title>
+ <sec id="level-2-with-an-embedded-link">
+ <title>Level 2 with an
+ <ext-link ext-link-type="uri" xlink:href="/url">embedded
+ link</ext-link></title>
+ <sec id="level-3-with-emphasis">
+ <title>Level 3 with <italic>emphasis</italic></title>
+ <sec id="level-4">
+ <title>Level 4</title>
+ <sec id="level-5">
+ <title>Level 5</title>
+ </sec>
+ </sec>
+ </sec>
+ </sec>
+</sec>
+<sec id="level-1">
+ <title>Level 1</title>
+ <sec id="level-2-with-emphasis">
+ <title>Level 2 with <italic>emphasis</italic></title>
+ <sec id="level-3">
+ <title>Level 3</title>
+ <p>with no blank line</p>
+ </sec>
+ </sec>
+ <sec id="level-2">
+ <title>Level 2</title>
+ <p>with no blank line</p>
+ </sec>
+</sec>
+<sec id="paragraphs">
+ <title>Paragraphs</title>
+ <p>Here’s a regular paragraph.</p>
+ <p>In Markdown 1.0.0 and earlier. Version 8. This line turns into a list
+ item. Because a hard-wrapped line in the middle of a paragraph looked like a
+ list item.</p>
+ <p>Here’s one with a bullet. * criminey.</p>
+ <p>There should be a hard line break
+ here.</p>
+</sec>
+<sec id="block-quotes">
+ <title>Block Quotes</title>
+ <p>E-mail style:</p>
+ <disp-quote>
+ <p>This is a block quote. It is pretty short.</p>
+ </disp-quote>
+ <disp-quote>
+ <p>Code in a block quote:</p>
+ <p specific-use="wrapper">
+ <preformat>sub status {
+ print &quot;working&quot;;
+}</preformat>
+ </p>
+ <p>A list:</p>
+ <p specific-use="wrapper">
+ <list list-type="order">
+ <list-item>
+ <p>item one</p>
+ </list-item>
+ <list-item>
+ <p>item two</p>
+ </list-item>
+ </list>
+ </p>
+ <p>Nested block quotes:</p>
+ <p specific-use="wrapper">
+ <disp-quote>
+ <p>nested</p>
+ </disp-quote>
+ </p>
+ <p specific-use="wrapper">
+ <disp-quote>
+ <p>nested</p>
+ </disp-quote>
+ </p>
+ </disp-quote>
+ <p>This should not be a block quote: 2 &gt; 1.</p>
+ <p>And a following paragraph.</p>
+</sec>
+<sec id="code-blocks">
+ <title>Code Blocks</title>
+ <p>Code:</p>
+ <preformat>---- (should be four hyphens)
+
+sub status {
+ print &quot;working&quot;;
+}
+
+this code block is indented by one tab</preformat>
+ <p>And:</p>
+ <preformat> this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \&gt; \[ \{</preformat>
+</sec>
+<sec id="lists">
+ <title>Lists</title>
+ <sec id="unordered">
+ <title>Unordered</title>
+ <p>Asterisks tight:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>asterisk 1</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 2</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 3</p>
+ </list-item>
+ </list>
+ <p>Asterisks loose:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>asterisk 1</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 2</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 3</p>
+ </list-item>
+ </list>
+ <p>Pluses tight:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Plus 1</p>
+ </list-item>
+ <list-item>
+ <p>Plus 2</p>
+ </list-item>
+ <list-item>
+ <p>Plus 3</p>
+ </list-item>
+ </list>
+ <p>Pluses loose:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Plus 1</p>
+ </list-item>
+ <list-item>
+ <p>Plus 2</p>
+ </list-item>
+ <list-item>
+ <p>Plus 3</p>
+ </list-item>
+ </list>
+ <p>Minuses tight:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Minus 1</p>
+ </list-item>
+ <list-item>
+ <p>Minus 2</p>
+ </list-item>
+ <list-item>
+ <p>Minus 3</p>
+ </list-item>
+ </list>
+ <p>Minuses loose:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Minus 1</p>
+ </list-item>
+ <list-item>
+ <p>Minus 2</p>
+ </list-item>
+ <list-item>
+ <p>Minus 3</p>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="ordered">
+ <title>Ordered</title>
+ <p>Tight:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second</p>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ <p>and:</p>
+ <list list-type="order">
+ <list-item>
+ <p>One</p>
+ </list-item>
+ <list-item>
+ <p>Two</p>
+ </list-item>
+ <list-item>
+ <p>Three</p>
+ </list-item>
+ </list>
+ <p>Loose using tabs:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second</p>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ <p>and using spaces:</p>
+ <list list-type="order">
+ <list-item>
+ <p>One</p>
+ </list-item>
+ <list-item>
+ <p>Two</p>
+ </list-item>
+ <list-item>
+ <p>Three</p>
+ </list-item>
+ </list>
+ <p>Multiple paragraphs:</p>
+ <list list-type="order">
+ <list-item>
+ <p>Item 1, graf one.</p>
+ <p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s
+ back.</p>
+ </list-item>
+ <list-item>
+ <p>Item 2.</p>
+ </list-item>
+ <list-item>
+ <p>Item 3.</p>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="nested">
+ <title>Nested</title>
+ <list list-type="bullet">
+ <list-item>
+ <p>Tab</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Tab</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Tab</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Here’s another:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Fee</p>
+ </list-item>
+ <list-item>
+ <p>Fie</p>
+ </list-item>
+ <list-item>
+ <p>Foe</p>
+ </list-item>
+ </list>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ <p>Same thing but with paragraphs:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Fee</p>
+ </list-item>
+ <list-item>
+ <p>Fie</p>
+ </list-item>
+ <list-item>
+ <p>Foe</p>
+ </list-item>
+ </list>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="tabs-and-spaces">
+ <title>Tabs and spaces</title>
+ <list list-type="bullet">
+ <list-item>
+ <p>this is a list item indented with tabs</p>
+ </list-item>
+ <list-item>
+ <p>this is a list item indented with spaces</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>this is an example list item indented with tabs</p>
+ </list-item>
+ <list-item>
+ <p>this is an example list item indented with spaces</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="fancy-list-markers">
+ <title>Fancy list markers</title>
+ <list list-type="order">
+ <list-item>
+ <label>(2)</label>
+ <p>begins with 2</p>
+ </list-item>
+ <list-item>
+ <label>(3)</label>
+ <p>and now 3</p>
+ <p>with a continuation</p>
+ <list list-type="order">
+ <list-item>
+ <label>iv.</label>
+ <p>sublist with roman numerals, starting with 4</p>
+ </list-item>
+ <list-item>
+ <label>v.</label>
+ <p>more items</p>
+ <list list-type="order">
+ <list-item>
+ <label>(A)</label>
+ <p>a subsublist</p>
+ </list-item>
+ <list-item>
+ <label>(B)</label>
+ <p>a subsublist</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Nesting:</p>
+ <list list-type="order">
+ <list-item>
+ <p>Upper Alpha</p>
+ <list list-type="order">
+ <list-item>
+ <p>Upper Roman.</p>
+ <list list-type="order">
+ <list-item>
+ <label>(6)</label>
+ <p>Decimal start with 6</p>
+ <list list-type="order">
+ <list-item>
+ <label>c)</label>
+ <p>Lower alpha with paren</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Autonumbering:</p>
+ <list list-type="order">
+ <list-item>
+ <p>Autonumber.</p>
+ </list-item>
+ <list-item>
+ <p>More.</p>
+ <list list-type="order">
+ <list-item>
+ <p>Nested.</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Should not be a list item:</p>
+ <p>M.A. 2007</p>
+ <p>B. Williams</p>
+ </sec>
+</sec>
+<sec id="definition-lists">
+ <title>Definition Lists</title>
+ <p>Tight using spaces:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>banana</term>
+ <def>
+ <p>yellow fruit</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Tight using tabs:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>banana</term>
+ <def>
+ <p>yellow fruit</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Loose:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>banana</term>
+ <def>
+ <p>yellow fruit</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Multiple blocks with italics:</p>
+ <def-list>
+ <def-item>
+ <term><italic>apple</italic></term>
+ <def>
+ <p>red fruit</p>
+ <p>contains seeds, crisp, pleasant to taste</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term><italic>orange</italic></term>
+ <def>
+ <p>orange fruit</p>
+ <p specific-use="wrapper">
+ <preformat>{ orange code block }</preformat>
+ </p>
+ <p specific-use="wrapper">
+ <disp-quote>
+ <p>orange block quote</p>
+ </disp-quote>
+ </p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Multiple definitions, tight:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ <p>computer</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ <p>bank</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Multiple definitions, loose:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ <p>computer</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ <p>bank</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Blank line after term, indented marker, alternate markers:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ <p>computer</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ <p specific-use="wrapper">
+ <list list-type="order">
+ <list-item>
+ <p>sublist</p>
+ </list-item>
+ <list-item>
+ <p>sublist</p>
+ </list-item>
+ </list>
+ </p>
+ </def>
+ </def-item>
+ </def-list>
+</sec>
+<sec id="html-blocks">
+ <title>HTML Blocks</title>
+ <p>Simple block on one line:</p>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ <p>And nested without indentation:</p>
+ <boxed-text>
+ <boxed-text>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ </boxed-text>
+ <boxed-text>
+ <p>bar</p>
+ </boxed-text>
+ </boxed-text>
+ <p>Interpreted markdown in a table:</p>
+ <p>This is <italic>emphasized</italic></p>
+ <p>And this is <bold>strong</bold></p>
+ <p>Here’s a simple block:</p>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ <p>This should be a code block, though:</p>
+ <preformat>&lt;div&gt;
+ foo
+&lt;/div&gt;</preformat>
+ <p>As should this:</p>
+ <preformat>&lt;div&gt;foo&lt;/div&gt;</preformat>
+ <p>Now, nested:</p>
+ <boxed-text>
+ <boxed-text>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ </boxed-text>
+ </boxed-text>
+ <p>This should just be an HTML comment:</p>
+ <p>Multiline:</p>
+ <p>Code block:</p>
+ <preformat>&lt;!-- Comment --&gt;</preformat>
+ <p>Just plain comment, with trailing spaces on the line:</p>
+ <p>Code:</p>
+ <preformat>&lt;hr /&gt;</preformat>
+ <p>Hr’s:</p>
+</sec>
+<sec id="inline-markup">
+ <title>Inline Markup</title>
+ <p>This is <italic>emphasized</italic>, and so <italic>is this</italic>.</p>
+ <p>This is <bold>strong</bold>, and so <bold>is this</bold>.</p>
+ <p>An <italic><ext-link ext-link-type="uri" xlink:href="/url">emphasized
+ link</ext-link></italic>.</p>
+ <p><bold><italic>This is strong and em.</italic></bold></p>
+ <p>So is <bold><italic>this</italic></bold> word.</p>
+ <p><bold><italic>This is strong and em.</italic></bold></p>
+ <p>So is <bold><italic>this</italic></bold> word.</p>
+ <p>This is code: <monospace>&gt;</monospace>, <monospace>$</monospace>,
+ <monospace>\</monospace>, <monospace>\$</monospace>,
+ <monospace>&lt;html&gt;</monospace>.</p>
+ <p><strike>This is <italic>strikeout</italic>.</strike></p>
+ <p>Superscripts: a<sup>bc</sup>d a<sup><italic>hello</italic></sup>
+ a<sup>hello there</sup>.</p>
+ <p>Subscripts: H<sub>2</sub>O, H<sub>23</sub>O,
+ H<sub>many of them</sub>O.</p>
+ <p>These should not be superscripts or subscripts, because of the unescaped
+ spaces: a^b c^d, a~b c~d.</p>
+</sec>
+<sec id="smart-quotes-ellipses-dashes">
+ <title>Smart quotes, ellipses, dashes</title>
+ <p>“Hello,” said the spider. “‘Shelob’ is my name.”</p>
+ <p>‘A’, ‘B’, and ‘C’ are letters.</p>
+ <p>‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p>
+ <p>‘He said, “I want to go.”’ Were you alive in the 70’s?</p>
+ <p>Here is some quoted ‘<monospace>code</monospace>’ and a
+ “<ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">quoted
+ link</ext-link>”.</p>
+ <p>Some dashes: one—two — three—four — five.</p>
+ <p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p>
+ <p>Ellipses…and…and….</p>
+</sec>
+<sec id="latex">
+ <title>LaTeX</title>
+ <list list-type="bullet">
+ <list-item>
+ <p></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mn>2</mml:mn><mml:mo>+</mml:mo><mml:mn>2</mml:mn><mml:mo>=</mml:mo><mml:mn>4</mml:mn></mml:mrow></mml:math></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>x</mml:mi><mml:mo>∈</mml:mo><mml:mi>y</mml:mi></mml:mrow></mml:math></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>α</mml:mi><mml:mo>∧</mml:mo><mml:mi>ω</mml:mi></mml:mrow></mml:math></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mn>223</mml:mn></mml:math></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mi>p</mml:mi></mml:math></inline-formula>-Tree</p>
+ </list-item>
+ <list-item>
+ <p>Here’s some display math:
+ <disp-formula><mml:math display="block" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mfrac><mml:mi>d</mml:mi><mml:mrow><mml:mi>d</mml:mi><mml:mi>x</mml:mi></mml:mrow></mml:mfrac><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo><mml:mo>=</mml:mo><mml:munder><mml:mo>lim</mml:mo><mml:mrow><mml:mi>h</mml:mi><mml:mo>→</mml:mo><mml:mn>0</mml:mn></mml:mrow></mml:munder><mml:mfrac><mml:mrow><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo>+</mml:mo><mml:mi>h</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo><mml:mo>−</mml:mo><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo></mml:mrow><mml:mi>h</mml:mi></mml:mfrac></mml:mrow></mml:math></disp-formula></p>
+ </list-item>
+ <list-item>
+ <p>Here’s one that has a line break in it:
+ <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>α</mml:mi><mml:mo>+</mml:mo><mml:mi>ω</mml:mi><mml:mo>×</mml:mo><mml:msup><mml:mi>x</mml:mi><mml:mn>2</mml:mn></mml:msup></mml:mrow></mml:math></inline-formula>.</p>
+ </list-item>
+ </list>
+ <p>These shouldn’t be math:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>To get the famous equation, write
+ <monospace>$e = mc^2$</monospace>.</p>
+ </list-item>
+ <list-item>
+ <p>$22,000 is a <italic>lot</italic> of money. So is $34,000. (It worked
+ if “lot” is emphasized.)</p>
+ </list-item>
+ <list-item>
+ <p>Shoes ($20) and socks ($5).</p>
+ </list-item>
+ <list-item>
+ <p>Escaped <monospace>$</monospace>: $73 <italic>this should be
+ emphasized</italic> 23$.</p>
+ </list-item>
+ </list>
+ <p>Here’s a LaTeX table:</p>
+</sec>
+<sec id="special-characters">
+ <title>Special Characters</title>
+ <p>Here is some unicode:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>I hat: Î</p>
+ </list-item>
+ <list-item>
+ <p>o umlaut: ö</p>
+ </list-item>
+ <list-item>
+ <p>section: §</p>
+ </list-item>
+ <list-item>
+ <p>set membership: ∈</p>
+ </list-item>
+ <list-item>
+ <p>copyright: ©</p>
+ </list-item>
+ </list>
+ <p>AT&amp;T has an ampersand in their name.</p>
+ <p>AT&amp;T is another way to write it.</p>
+ <p>This &amp; that.</p>
+ <p>4 &lt; 5.</p>
+ <p>6 &gt; 5.</p>
+ <p>Backslash: \</p>
+ <p>Backtick: `</p>
+ <p>Asterisk: *</p>
+ <p>Underscore: _</p>
+ <p>Left brace: {</p>
+ <p>Right brace: }</p>
+ <p>Left bracket: [</p>
+ <p>Right bracket: ]</p>
+ <p>Left paren: (</p>
+ <p>Right paren: )</p>
+ <p>Greater-than: &gt;</p>
+ <p>Hash: #</p>
+ <p>Period: .</p>
+ <p>Bang: !</p>
+ <p>Plus: +</p>
+ <p>Minus: -</p>
+</sec>
+<sec id="links">
+ <title>Links</title>
+ <sec id="explicit">
+ <title>Explicit</title>
+ <p>Just a
+ <ext-link ext-link-type="uri" xlink:href="/url/">URL</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title">URL
+ and title</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title preceded by two spaces">URL
+ and title</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title preceded by a tab">URL
+ and title</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title with &quot;quotes&quot; in it">URL
+ and title</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title with single quotes">URL
+ and title</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/with_underscore">with_underscore</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="mailto:nobody@nowhere.net">Email
+ link</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="">Empty</ext-link>.</p>
+ </sec>
+ <sec id="reference">
+ <title>Reference</title>
+ <p>Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>.</p>
+ <p>With <ext-link ext-link-type="uri" xlink:href="/url/">embedded
+ [brackets]</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/">b</ext-link> by itself
+ should be a link.</p>
+ <p>Indented
+ <ext-link ext-link-type="uri" xlink:href="/url">once</ext-link>.</p>
+ <p>Indented
+ <ext-link ext-link-type="uri" xlink:href="/url">twice</ext-link>.</p>
+ <p>Indented
+ <ext-link ext-link-type="uri" xlink:href="/url">thrice</ext-link>.</p>
+ <p>This should [not][] be a link.</p>
+ <preformat>[not]: /url</preformat>
+ <p>Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="Title with &quot;quotes&quot; inside">bar</ext-link>.</p>
+ <p>Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="Title with &quot;quote&quot; inside">biz</ext-link>.</p>
+ </sec>
+ <sec id="with-ampersands">
+ <title>With ampersands</title>
+ <p>Here’s a
+ <ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">link
+ with an ampersand in the URL</ext-link>.</p>
+ <p>Here’s a link with an amersand in the link text:
+ <ext-link ext-link-type="uri" xlink:href="http://att.com/" xlink:title="AT&amp;T">AT&amp;T</ext-link>.</p>
+ <p>Here’s an
+ <ext-link ext-link-type="uri" xlink:href="/script?foo=1&amp;bar=2">inline
+ link</ext-link>.</p>
+ <p>Here’s an
+ <ext-link ext-link-type="uri" xlink:href="/script?foo=1&amp;bar=2">inline
+ link in pointy braces</ext-link>.</p>
+ </sec>
+ <sec id="autolinks">
+ <title>Autolinks</title>
+ <p>With an ampersand:
+ <ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">http://example.com/?foo=1&amp;bar=2</ext-link></p>
+ <list list-type="bullet">
+ <list-item>
+ <p>In a list?</p>
+ </list-item>
+ <list-item>
+ <p><ext-link ext-link-type="uri" xlink:href="http://example.com/">http://example.com/</ext-link></p>
+ </list-item>
+ <list-item>
+ <p>It should.</p>
+ </list-item>
+ </list>
+ <p>An e-mail address: <email>nobody@nowhere.net</email></p>
+ <disp-quote>
+ <p>Blockquoted:
+ <ext-link ext-link-type="uri" xlink:href="http://example.com/">http://example.com/</ext-link></p>
+ </disp-quote>
+ <p>Auto-links should not occur here:
+ <monospace>&lt;http://example.com/&gt;</monospace></p>
+ <preformat>or here: &lt;http://example.com/&gt;</preformat>
+ </sec>
+</sec>
+<sec id="images">
+ <title>Images</title>
+ <p>From “Voyage dans la Lune” by Georges Melies (1902):</p>
+ <fig>
+ <caption><p>lalune</p></caption>
+ <graphic mimetype="image" mime-subtype="jpeg" xlink:href="lalune.jpg" xlink:title="Voyage dans la Lune" />
+ </fig>
+ <p>Here is a movie
+ <inline-graphic mimetype="image" mime-subtype="jpeg" xlink:href="movie.jpg" />
+ icon.</p>
+</sec>
+<sec id="footnotes">
+ <title>Footnotes</title>
+ <p>Here is a footnote reference,<fn>
+ <p>Here is the footnote. It can go anywhere after the footnote reference.
+ It need not be placed at the end of the document.</p>
+ </fn> and another.<fn>
+ <p>Here’s the long note. This one contains multiple blocks.</p>
+ <p>Subsequent blocks are indented to show that they belong to the footnote
+ (as with list items).</p>
+ <p specific-use="wrapper">
+ <preformat> { &lt;code&gt; }</preformat>
+ </p>
+ <p>If you want, you can indent every line, but you can also be lazy and
+ just indent the first line of each block.</p>
+ </fn> This should <italic>not</italic> be a footnote reference, because it
+ contains a space.[^my note] Here is an inline note.<fn>
+ <p>This is <italic>easier</italic> to type. Inline notes may contain
+ <ext-link ext-link-type="uri" xlink:href="http://google.com">links</ext-link>
+ and <monospace>]</monospace> verbatim characters, as well as [bracketed
+ text].</p>
+ </fn></p>
+ <disp-quote>
+ <p>Notes can go in quotes.<fn>
+ <p>In quote.</p>
+ </fn></p>
+ </disp-quote>
+ <list list-type="order">
+ <list-item>
+ <p>And in list items.<fn>
+ <p>In list.</p>
+ </fn></p>
+ </list-item>
+ </list>
+ <p>This paragraph should not be part of the note, as it is not indented.</p>
+</sec>
+</body>
+<back>
+</back>
+</article>
diff --git a/test/writer.jats_publishing b/test/writer.jats_publishing
new file mode 100644
index 000000000..6384a5939
--- /dev/null
+++ b/test/writer.jats_publishing
@@ -0,0 +1,898 @@
+<?xml version="1.0" encoding="utf-8" ?>
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.2 20190208//EN"
+ "JATS-publishing1.dtd">
+<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.2" article-type="other">
+<front>
+<journal-meta>
+<journal-title-group>
+</journal-title-group>
+<publisher>
+<publisher-name></publisher-name>
+</publisher>
+</journal-meta>
+<article-meta>
+<title-group>
+<article-title>Pandoc Test Suite</article-title>
+</title-group>
+<contrib-group>
+<contrib contrib-type="author">
+<string-name>John MacFarlane</string-name>
+</contrib>
+<contrib contrib-type="author">
+<string-name>Anonymous</string-name>
+</contrib>
+</contrib-group>
+<pub-date pub-type="epub" iso-8601-date="2006-07-17">
+<day>17</day>
+<month>7</month>
+<year>2006</year>
+</pub-date>
+</article-meta>
+</front>
+<body>
+<p>This is a set of tests for pandoc. Most of them are adapted from John
+Gruber’s markdown test suite.</p>
+<sec id="headers">
+ <title>Headers</title>
+ <sec id="level-2-with-an-embedded-link">
+ <title>Level 2 with an
+ <ext-link ext-link-type="uri" xlink:href="/url">embedded
+ link</ext-link></title>
+ <sec id="level-3-with-emphasis">
+ <title>Level 3 with <italic>emphasis</italic></title>
+ <sec id="level-4">
+ <title>Level 4</title>
+ <sec id="level-5">
+ <title>Level 5</title>
+ </sec>
+ </sec>
+ </sec>
+ </sec>
+</sec>
+<sec id="level-1">
+ <title>Level 1</title>
+ <sec id="level-2-with-emphasis">
+ <title>Level 2 with <italic>emphasis</italic></title>
+ <sec id="level-3">
+ <title>Level 3</title>
+ <p>with no blank line</p>
+ </sec>
+ </sec>
+ <sec id="level-2">
+ <title>Level 2</title>
+ <p>with no blank line</p>
+ </sec>
+</sec>
+<sec id="paragraphs">
+ <title>Paragraphs</title>
+ <p>Here’s a regular paragraph.</p>
+ <p>In Markdown 1.0.0 and earlier. Version 8. This line turns into a list
+ item. Because a hard-wrapped line in the middle of a paragraph looked like a
+ list item.</p>
+ <p>Here’s one with a bullet. * criminey.</p>
+ <p>There should be a hard line break
+ here.</p>
+</sec>
+<sec id="block-quotes">
+ <title>Block Quotes</title>
+ <p>E-mail style:</p>
+ <disp-quote>
+ <p>This is a block quote. It is pretty short.</p>
+ </disp-quote>
+ <disp-quote>
+ <p>Code in a block quote:</p>
+ <preformat>sub status {
+ print &quot;working&quot;;
+}</preformat>
+ <p>A list:</p>
+ <list list-type="order">
+ <list-item>
+ <p>item one</p>
+ </list-item>
+ <list-item>
+ <p>item two</p>
+ </list-item>
+ </list>
+ <p>Nested block quotes:</p>
+ <disp-quote>
+ <p>nested</p>
+ </disp-quote>
+ <disp-quote>
+ <p>nested</p>
+ </disp-quote>
+ </disp-quote>
+ <p>This should not be a block quote: 2 &gt; 1.</p>
+ <p>And a following paragraph.</p>
+</sec>
+<sec id="code-blocks">
+ <title>Code Blocks</title>
+ <p>Code:</p>
+ <preformat>---- (should be four hyphens)
+
+sub status {
+ print &quot;working&quot;;
+}
+
+this code block is indented by one tab</preformat>
+ <p>And:</p>
+ <preformat> this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \&gt; \[ \{</preformat>
+</sec>
+<sec id="lists">
+ <title>Lists</title>
+ <sec id="unordered">
+ <title>Unordered</title>
+ <p>Asterisks tight:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>asterisk 1</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 2</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 3</p>
+ </list-item>
+ </list>
+ <p>Asterisks loose:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>asterisk 1</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 2</p>
+ </list-item>
+ <list-item>
+ <p>asterisk 3</p>
+ </list-item>
+ </list>
+ <p>Pluses tight:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Plus 1</p>
+ </list-item>
+ <list-item>
+ <p>Plus 2</p>
+ </list-item>
+ <list-item>
+ <p>Plus 3</p>
+ </list-item>
+ </list>
+ <p>Pluses loose:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Plus 1</p>
+ </list-item>
+ <list-item>
+ <p>Plus 2</p>
+ </list-item>
+ <list-item>
+ <p>Plus 3</p>
+ </list-item>
+ </list>
+ <p>Minuses tight:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Minus 1</p>
+ </list-item>
+ <list-item>
+ <p>Minus 2</p>
+ </list-item>
+ <list-item>
+ <p>Minus 3</p>
+ </list-item>
+ </list>
+ <p>Minuses loose:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Minus 1</p>
+ </list-item>
+ <list-item>
+ <p>Minus 2</p>
+ </list-item>
+ <list-item>
+ <p>Minus 3</p>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="ordered">
+ <title>Ordered</title>
+ <p>Tight:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second</p>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ <p>and:</p>
+ <list list-type="order">
+ <list-item>
+ <p>One</p>
+ </list-item>
+ <list-item>
+ <p>Two</p>
+ </list-item>
+ <list-item>
+ <p>Three</p>
+ </list-item>
+ </list>
+ <p>Loose using tabs:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second</p>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ <p>and using spaces:</p>
+ <list list-type="order">
+ <list-item>
+ <p>One</p>
+ </list-item>
+ <list-item>
+ <p>Two</p>
+ </list-item>
+ <list-item>
+ <p>Three</p>
+ </list-item>
+ </list>
+ <p>Multiple paragraphs:</p>
+ <list list-type="order">
+ <list-item>
+ <p>Item 1, graf one.</p>
+ <p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s
+ back.</p>
+ </list-item>
+ <list-item>
+ <p>Item 2.</p>
+ </list-item>
+ <list-item>
+ <p>Item 3.</p>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="nested">
+ <title>Nested</title>
+ <list list-type="bullet">
+ <list-item>
+ <p>Tab</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Tab</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Tab</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Here’s another:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Fee</p>
+ </list-item>
+ <list-item>
+ <p>Fie</p>
+ </list-item>
+ <list-item>
+ <p>Foe</p>
+ </list-item>
+ </list>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ <p>Same thing but with paragraphs:</p>
+ <list list-type="order">
+ <list-item>
+ <p>First</p>
+ </list-item>
+ <list-item>
+ <p>Second:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>Fee</p>
+ </list-item>
+ <list-item>
+ <p>Fie</p>
+ </list-item>
+ <list-item>
+ <p>Foe</p>
+ </list-item>
+ </list>
+ </list-item>
+ <list-item>
+ <p>Third</p>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="tabs-and-spaces">
+ <title>Tabs and spaces</title>
+ <list list-type="bullet">
+ <list-item>
+ <p>this is a list item indented with tabs</p>
+ </list-item>
+ <list-item>
+ <p>this is a list item indented with spaces</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>this is an example list item indented with tabs</p>
+ </list-item>
+ <list-item>
+ <p>this is an example list item indented with spaces</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </sec>
+ <sec id="fancy-list-markers">
+ <title>Fancy list markers</title>
+ <list list-type="order">
+ <list-item>
+ <label>(2)</label>
+ <p>begins with 2</p>
+ </list-item>
+ <list-item>
+ <label>(3)</label>
+ <p>and now 3</p>
+ <p>with a continuation</p>
+ <list list-type="roman-lower">
+ <list-item>
+ <label>iv.</label>
+ <p>sublist with roman numerals, starting with 4</p>
+ </list-item>
+ <list-item>
+ <label>v.</label>
+ <p>more items</p>
+ <list list-type="alpha-upper">
+ <list-item>
+ <label>(A)</label>
+ <p>a subsublist</p>
+ </list-item>
+ <list-item>
+ <label>(B)</label>
+ <p>a subsublist</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Nesting:</p>
+ <list list-type="alpha-upper">
+ <list-item>
+ <p>Upper Alpha</p>
+ <list list-type="roman-upper">
+ <list-item>
+ <p>Upper Roman.</p>
+ <list list-type="order">
+ <list-item>
+ <label>(6)</label>
+ <p>Decimal start with 6</p>
+ <list list-type="alpha-lower">
+ <list-item>
+ <label>c)</label>
+ <p>Lower alpha with paren</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Autonumbering:</p>
+ <list list-type="order">
+ <list-item>
+ <p>Autonumber.</p>
+ </list-item>
+ <list-item>
+ <p>More.</p>
+ <list list-type="order">
+ <list-item>
+ <p>Nested.</p>
+ </list-item>
+ </list>
+ </list-item>
+ </list>
+ <p>Should not be a list item:</p>
+ <p>M.A. 2007</p>
+ <p>B. Williams</p>
+ </sec>
+</sec>
+<sec id="definition-lists">
+ <title>Definition Lists</title>
+ <p>Tight using spaces:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>banana</term>
+ <def>
+ <p>yellow fruit</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Tight using tabs:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>banana</term>
+ <def>
+ <p>yellow fruit</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Loose:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>banana</term>
+ <def>
+ <p>yellow fruit</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Multiple blocks with italics:</p>
+ <def-list>
+ <def-item>
+ <term><italic>apple</italic></term>
+ <def>
+ <p>red fruit</p>
+ <p>contains seeds, crisp, pleasant to taste</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term><italic>orange</italic></term>
+ <def>
+ <p>orange fruit</p>
+ <p specific-use="wrapper">
+ <preformat>{ orange code block }</preformat>
+ </p>
+ <p specific-use="wrapper">
+ <disp-quote>
+ <p>orange block quote</p>
+ </disp-quote>
+ </p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Multiple definitions, tight:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ <p>computer</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ <p>bank</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Multiple definitions, loose:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ <p>computer</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ <p>bank</p>
+ </def>
+ </def-item>
+ </def-list>
+ <p>Blank line after term, indented marker, alternate markers:</p>
+ <def-list>
+ <def-item>
+ <term>apple</term>
+ <def>
+ <p>red fruit</p>
+ <p>computer</p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>orange</term>
+ <def>
+ <p>orange fruit</p>
+ <p specific-use="wrapper">
+ <list list-type="order">
+ <list-item>
+ <p>sublist</p>
+ </list-item>
+ <list-item>
+ <p>sublist</p>
+ </list-item>
+ </list>
+ </p>
+ </def>
+ </def-item>
+ </def-list>
+</sec>
+<sec id="html-blocks">
+ <title>HTML Blocks</title>
+ <p>Simple block on one line:</p>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ <p>And nested without indentation:</p>
+ <boxed-text>
+ <boxed-text>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ </boxed-text>
+ <boxed-text>
+ <p>bar</p>
+ </boxed-text>
+ </boxed-text>
+ <p>Interpreted markdown in a table:</p>
+ <p>This is <italic>emphasized</italic></p>
+ <p>And this is <bold>strong</bold></p>
+ <p>Here’s a simple block:</p>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ <p>This should be a code block, though:</p>
+ <preformat>&lt;div&gt;
+ foo
+&lt;/div&gt;</preformat>
+ <p>As should this:</p>
+ <preformat>&lt;div&gt;foo&lt;/div&gt;</preformat>
+ <p>Now, nested:</p>
+ <boxed-text>
+ <boxed-text>
+ <boxed-text>
+ <p>foo</p>
+ </boxed-text>
+ </boxed-text>
+ </boxed-text>
+ <p>This should just be an HTML comment:</p>
+ <p>Multiline:</p>
+ <p>Code block:</p>
+ <preformat>&lt;!-- Comment --&gt;</preformat>
+ <p>Just plain comment, with trailing spaces on the line:</p>
+ <p>Code:</p>
+ <preformat>&lt;hr /&gt;</preformat>
+ <p>Hr’s:</p>
+</sec>
+<sec id="inline-markup">
+ <title>Inline Markup</title>
+ <p>This is <italic>emphasized</italic>, and so <italic>is this</italic>.</p>
+ <p>This is <bold>strong</bold>, and so <bold>is this</bold>.</p>
+ <p>An <italic><ext-link ext-link-type="uri" xlink:href="/url">emphasized
+ link</ext-link></italic>.</p>
+ <p><bold><italic>This is strong and em.</italic></bold></p>
+ <p>So is <bold><italic>this</italic></bold> word.</p>
+ <p><bold><italic>This is strong and em.</italic></bold></p>
+ <p>So is <bold><italic>this</italic></bold> word.</p>
+ <p>This is code: <monospace>&gt;</monospace>, <monospace>$</monospace>,
+ <monospace>\</monospace>, <monospace>\$</monospace>,
+ <monospace>&lt;html&gt;</monospace>.</p>
+ <p><strike>This is <italic>strikeout</italic>.</strike></p>
+ <p>Superscripts: a<sup>bc</sup>d a<sup><italic>hello</italic></sup>
+ a<sup>hello there</sup>.</p>
+ <p>Subscripts: H<sub>2</sub>O, H<sub>23</sub>O,
+ H<sub>many of them</sub>O.</p>
+ <p>These should not be superscripts or subscripts, because of the unescaped
+ spaces: a^b c^d, a~b c~d.</p>
+</sec>
+<sec id="smart-quotes-ellipses-dashes">
+ <title>Smart quotes, ellipses, dashes</title>
+ <p>“Hello,” said the spider. “‘Shelob’ is my name.”</p>
+ <p>‘A’, ‘B’, and ‘C’ are letters.</p>
+ <p>‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p>
+ <p>‘He said, “I want to go.”’ Were you alive in the 70’s?</p>
+ <p>Here is some quoted ‘<monospace>code</monospace>’ and a
+ “<ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">quoted
+ link</ext-link>”.</p>
+ <p>Some dashes: one—two — three—four — five.</p>
+ <p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p>
+ <p>Ellipses…and…and….</p>
+</sec>
+<sec id="latex">
+ <title>LaTeX</title>
+ <list list-type="bullet">
+ <list-item>
+ <p></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><alternatives>
+ <tex-math><![CDATA[2+2=4]]></tex-math>
+ <mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mn>2</mml:mn><mml:mo>+</mml:mo><mml:mn>2</mml:mn><mml:mo>=</mml:mo><mml:mn>4</mml:mn></mml:mrow></mml:math></alternatives></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><alternatives>
+ <tex-math><![CDATA[x \in y]]></tex-math>
+ <mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>x</mml:mi><mml:mo>∈</mml:mo><mml:mi>y</mml:mi></mml:mrow></mml:math></alternatives></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><alternatives>
+ <tex-math><![CDATA[\alpha \wedge \omega]]></tex-math>
+ <mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>α</mml:mi><mml:mo>∧</mml:mo><mml:mi>ω</mml:mi></mml:mrow></mml:math></alternatives></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><alternatives>
+ <tex-math><![CDATA[223]]></tex-math>
+ <mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mn>223</mml:mn></mml:math></alternatives></inline-formula></p>
+ </list-item>
+ <list-item>
+ <p><inline-formula><alternatives>
+ <tex-math><![CDATA[p]]></tex-math>
+ <mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mi>p</mml:mi></mml:math></alternatives></inline-formula>-Tree</p>
+ </list-item>
+ <list-item>
+ <p>Here’s some display math: <disp-formula><alternatives>
+ <tex-math><![CDATA[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}]]></tex-math>
+ <mml:math display="block" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mfrac><mml:mi>d</mml:mi><mml:mrow><mml:mi>d</mml:mi><mml:mi>x</mml:mi></mml:mrow></mml:mfrac><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo><mml:mo>=</mml:mo><mml:munder><mml:mo>lim</mml:mo><mml:mrow><mml:mi>h</mml:mi><mml:mo>→</mml:mo><mml:mn>0</mml:mn></mml:mrow></mml:munder><mml:mfrac><mml:mrow><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo>+</mml:mo><mml:mi>h</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo><mml:mo>−</mml:mo><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo></mml:mrow><mml:mi>h</mml:mi></mml:mfrac></mml:mrow></mml:math></alternatives></disp-formula></p>
+ </list-item>
+ <list-item>
+ <p>Here’s one that has a line break in it:
+ <inline-formula><alternatives>
+ <tex-math><![CDATA[\alpha + \omega \times x^2]]></tex-math>
+ <mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>α</mml:mi><mml:mo>+</mml:mo><mml:mi>ω</mml:mi><mml:mo>×</mml:mo><mml:msup><mml:mi>x</mml:mi><mml:mn>2</mml:mn></mml:msup></mml:mrow></mml:math></alternatives></inline-formula>.</p>
+ </list-item>
+ </list>
+ <p>These shouldn’t be math:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>To get the famous equation, write
+ <monospace>$e = mc^2$</monospace>.</p>
+ </list-item>
+ <list-item>
+ <p>$22,000 is a <italic>lot</italic> of money. So is $34,000. (It worked
+ if “lot” is emphasized.)</p>
+ </list-item>
+ <list-item>
+ <p>Shoes ($20) and socks ($5).</p>
+ </list-item>
+ <list-item>
+ <p>Escaped <monospace>$</monospace>: $73 <italic>this should be
+ emphasized</italic> 23$.</p>
+ </list-item>
+ </list>
+ <p>Here’s a LaTeX table:</p>
+</sec>
+<sec id="special-characters">
+ <title>Special Characters</title>
+ <p>Here is some unicode:</p>
+ <list list-type="bullet">
+ <list-item>
+ <p>I hat: Î</p>
+ </list-item>
+ <list-item>
+ <p>o umlaut: ö</p>
+ </list-item>
+ <list-item>
+ <p>section: §</p>
+ </list-item>
+ <list-item>
+ <p>set membership: ∈</p>
+ </list-item>
+ <list-item>
+ <p>copyright: ©</p>
+ </list-item>
+ </list>
+ <p>AT&amp;T has an ampersand in their name.</p>
+ <p>AT&amp;T is another way to write it.</p>
+ <p>This &amp; that.</p>
+ <p>4 &lt; 5.</p>
+ <p>6 &gt; 5.</p>
+ <p>Backslash: \</p>
+ <p>Backtick: `</p>
+ <p>Asterisk: *</p>
+ <p>Underscore: _</p>
+ <p>Left brace: {</p>
+ <p>Right brace: }</p>
+ <p>Left bracket: [</p>
+ <p>Right bracket: ]</p>
+ <p>Left paren: (</p>
+ <p>Right paren: )</p>
+ <p>Greater-than: &gt;</p>
+ <p>Hash: #</p>
+ <p>Period: .</p>
+ <p>Bang: !</p>
+ <p>Plus: +</p>
+ <p>Minus: -</p>
+</sec>
+<sec id="links">
+ <title>Links</title>
+ <sec id="explicit">
+ <title>Explicit</title>
+ <p>Just a
+ <ext-link ext-link-type="uri" xlink:href="/url/">URL</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title">URL
+ and title</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title preceded by two spaces">URL
+ and title</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title preceded by a tab">URL
+ and title</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title with &quot;quotes&quot; in it">URL
+ and title</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title with single quotes">URL
+ and title</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/with_underscore">with_underscore</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="mailto:nobody@nowhere.net">Email
+ link</ext-link></p>
+ <p><ext-link ext-link-type="uri" xlink:href="">Empty</ext-link>.</p>
+ </sec>
+ <sec id="reference">
+ <title>Reference</title>
+ <p>Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>.</p>
+ <p>With <ext-link ext-link-type="uri" xlink:href="/url/">embedded
+ [brackets]</ext-link>.</p>
+ <p><ext-link ext-link-type="uri" xlink:href="/url/">b</ext-link> by itself
+ should be a link.</p>
+ <p>Indented
+ <ext-link ext-link-type="uri" xlink:href="/url">once</ext-link>.</p>
+ <p>Indented
+ <ext-link ext-link-type="uri" xlink:href="/url">twice</ext-link>.</p>
+ <p>Indented
+ <ext-link ext-link-type="uri" xlink:href="/url">thrice</ext-link>.</p>
+ <p>This should [not][] be a link.</p>
+ <preformat>[not]: /url</preformat>
+ <p>Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="Title with &quot;quotes&quot; inside">bar</ext-link>.</p>
+ <p>Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="Title with &quot;quote&quot; inside">biz</ext-link>.</p>
+ </sec>
+ <sec id="with-ampersands">
+ <title>With ampersands</title>
+ <p>Here’s a
+ <ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">link
+ with an ampersand in the URL</ext-link>.</p>
+ <p>Here’s a link with an amersand in the link text:
+ <ext-link ext-link-type="uri" xlink:href="http://att.com/" xlink:title="AT&amp;T">AT&amp;T</ext-link>.</p>
+ <p>Here’s an
+ <ext-link ext-link-type="uri" xlink:href="/script?foo=1&amp;bar=2">inline
+ link</ext-link>.</p>
+ <p>Here’s an
+ <ext-link ext-link-type="uri" xlink:href="/script?foo=1&amp;bar=2">inline
+ link in pointy braces</ext-link>.</p>
+ </sec>
+ <sec id="autolinks">
+ <title>Autolinks</title>
+ <p>With an ampersand:
+ <ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">http://example.com/?foo=1&amp;bar=2</ext-link></p>
+ <list list-type="bullet">
+ <list-item>
+ <p>In a list?</p>
+ </list-item>
+ <list-item>
+ <p><ext-link ext-link-type="uri" xlink:href="http://example.com/">http://example.com/</ext-link></p>
+ </list-item>
+ <list-item>
+ <p>It should.</p>
+ </list-item>
+ </list>
+ <p>An e-mail address: <email>nobody@nowhere.net</email></p>
+ <disp-quote>
+ <p>Blockquoted:
+ <ext-link ext-link-type="uri" xlink:href="http://example.com/">http://example.com/</ext-link></p>
+ </disp-quote>
+ <p>Auto-links should not occur here:
+ <monospace>&lt;http://example.com/&gt;</monospace></p>
+ <preformat>or here: &lt;http://example.com/&gt;</preformat>
+ </sec>
+</sec>
+<sec id="images">
+ <title>Images</title>
+ <p>From “Voyage dans la Lune” by Georges Melies (1902):</p>
+ <fig>
+ <caption><p>lalune</p></caption>
+ <graphic mimetype="image" mime-subtype="jpeg" xlink:href="lalune.jpg" xlink:title="Voyage dans la Lune" />
+ </fig>
+ <p>Here is a movie
+ <inline-graphic mimetype="image" mime-subtype="jpeg" xlink:href="movie.jpg" />
+ icon.</p>
+</sec>
+<sec id="footnotes">
+ <title>Footnotes</title>
+ <p>Here is a footnote reference,<xref ref-type="fn" rid="fn1">1</xref> and
+ another.<xref ref-type="fn" rid="fn2">2</xref> This should
+ <italic>not</italic> be a footnote reference, because it contains a
+ space.[^my note] Here is an inline
+ note.<xref ref-type="fn" rid="fn3">3</xref></p>
+ <disp-quote>
+ <p>Notes can go in quotes.<xref ref-type="fn" rid="fn4">4</xref></p>
+ </disp-quote>
+ <list list-type="order">
+ <list-item>
+ <p>And in list items.<xref ref-type="fn" rid="fn5">5</xref></p>
+ </list-item>
+ </list>
+ <p>This paragraph should not be part of the note, as it is not indented.</p>
+</sec>
+</body>
+<back>
+<fn-group>
+ <fn id="fn1">
+ <p>Here is the footnote. It can go anywhere after the footnote reference.
+ It need not be placed at the end of the document.</p>
+ </fn>
+ <fn id="fn2">
+ <p>Here’s the long note. This one contains multiple blocks.</p>
+ <p>Subsequent blocks are indented to show that they belong to the footnote
+ (as with list items).</p>
+ <p specific-use="wrapper">
+ <preformat> { &lt;code&gt; }</preformat>
+ </p>
+ <p>If you want, you can indent every line, but you can also be lazy and
+ just indent the first line of each block.</p>
+ </fn>
+ <fn id="fn3">
+ <p>This is <italic>easier</italic> to type. Inline notes may contain
+ <ext-link ext-link-type="uri" xlink:href="http://google.com">links</ext-link>
+ and <monospace>]</monospace> verbatim characters, as well as [bracketed
+ text].</p>
+ </fn>
+ <fn id="fn4">
+ <p>In quote.</p>
+ </fn>
+ <fn id="fn5">
+ <p>In list.</p>
+ </fn>
+</fn-group>
+</back>
+</article>