summaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
authorHamish Mackenzie <Hamish.K.Mackenzie@googlemail.com>2017-12-20 13:54:02 +1300
committerHamish Mackenzie <Hamish.K.Mackenzie@googlemail.com>2017-12-20 13:54:02 +1300
commit5d3c9e56460165be452b672f12fc476e7a5ed3a9 (patch)
tree03c924628d4ba99ab4531db86364ab7576add007 /test
parent1e21cfb251506d42cbdcf3e24661f08633817572 (diff)
Add Basic JATS reader based on DocBook reader
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Old.hs2
-rw-r--r--test/Tests/Readers/JATS.hs111
-rw-r--r--test/jats-reader.native422
-rw-r--r--test/jats-reader.xml1773
-rw-r--r--test/test-pandoc.hs2
5 files changed, 2310 insertions, 0 deletions
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 9c6b9f660..bbd51ee98 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -79,6 +79,8 @@ tests = [ testGroup "markdown"
]
, testGroup "jats"
[ testGroup "writer" $ writerTests "jats"
+ , test "reader" ["-r", "jats", "-w", "native", "-s"]
+ "jats-reader.xml" "jats-reader.native"
]
, testGroup "native"
[ testGroup "writer" $ writerTests "native"
diff --git a/test/Tests/Readers/JATS.hs b/test/Tests/Readers/JATS.hs
new file mode 100644
index 000000000..ed6317c71
--- /dev/null
+++ b/test/Tests/Readers/JATS.hs
@@ -0,0 +1,111 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.JATS (tests) where
+
+import Data.Text (Text)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+jats :: Text -> Pandoc
+jats = purely $ readJATS def
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ test jats "basic" $ "<p>\n <monospace>@&amp;</monospace>\n</p>" =?> para (code "@&")
+ ]
+ , testGroup "images"
+ [ test jats "basic" $ "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
+ =?> para (image "/url" "title" mempty)
+ ]
+ , test jats "bullet list" $
+ "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ first\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ second\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ third\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \</list>"
+ =?> bulletList [ para $ text "first"
+ , para $ text "second"
+ , para $ text "third"
+ ]
+ , testGroup "definition lists"
+ [ test jats "with internal link" $
+ "<def-list>\n\
+ \ <def-item>\n\
+ \ <term>\n\
+ \ <xref alt=\"testing\" rid=\"go\">testing</xref>\n\
+ \ </term>\n\
+ \ <def>\n\
+ \ <p>\n\
+ \ hi there\n\
+ \ </p>\n\
+ \ </def>\n\
+ \ </def-item>\n\
+ \</def-list>"
+ =?> definitionList [(link "#go" "" (str "testing"),
+ [para (text "hi there")])]
+ ]
+ , testGroup "math"
+ [ test jats "escape |" $
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \ <mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula>\n\
+ \</p>"
+ =?> para (math "\\sigma|_{\\{x\\}}")
+ , test jats "tex-math only" $
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \</p>"
+ =?> para (math "\\sigma|_{\\{x\\}}")
+ , test jats "math ml only" $
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula>\n\
+ \</p>"
+ =?> para (math "\\sigma|_{\\{ x\\}}")
+ ]
+ , testGroup "headers"
+-- TODO fix footnotes in headers
+-- [ test jats "unnumbered header" $
+-- "<sec>\n\
+-- \ <title>Header 1<fn>\n\
+-- \ <p>\n\
+-- \ note\n\
+-- \ </p>\n\
+-- \ </fn></title>\n\
+-- \</sec>"
+-- =?> header 1
+-- (text "Header 1" <> note (plain $ text "note"))
+ [ test jats "unnumbered sub header" $
+ "<sec id=\"foo\">\n\
+ \ <title>Header</title>\n\
+ \ <sec id=\"foo2\">\n\
+ \ <title>Sub-Header</title>\n\
+ \ </sec>\n\
+ \</sec>"
+ =?> headerWith ("foo", [], []) 1
+ (text "Header")
+ <> headerWith ("foo2", [], []) 2
+ (text "Sub-Header")
+ , test jats "containing image" $
+ "<sec>\n\
+ \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
+ \</sec>"
+ =?> header 1 (image "imgs/foo.jpg" "" mempty)
+ ]
+ ]
diff --git a/test/jats-reader.native b/test/jats-reader.native
new file mode 100644
index 000000000..2bc8b94ce
--- /dev/null
+++ b/test/jats-reader.native
@@ -0,0 +1,422 @@
+Pandoc (Meta {unMeta = fromList [("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",SoftBreak,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
+,Header 1 ("headers",[],[]) [Str "Headers"]
+,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",SoftBreak,Link ("",[],[]) [Str "embedded",SoftBreak,Str "link"] ("/url","")]
+,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
+,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
+,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
+,Header 1 ("level-1",[],[]) [Str "Level",Space,Str "1"]
+,Header 2 ("level-2-with-emphasis",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Emph [Str "emphasis"]]
+,Header 3 ("level-3",[],[]) [Str "Level",Space,Str "3"]
+,Para [Str "with",Space,Str "no",Space,Str "blank",Space,Str "line"]
+,Header 2 ("level-2",[],[]) [Str "Level",Space,Str "2"]
+,Para [Str "with",Space,Str "no",Space,Str "blank",Space,Str "line"]
+,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"]
+,Para [Str "Here's",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
+,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",Space,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",SoftBreak,Str "list",Space,Str "item.",Space,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",SoftBreak,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
+,Para [Str "Here's",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
+,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "hard",Space,Str "line",Space,Str "break",LineBreak,Str "here."]
+,Header 1 ("block-quotes",[],[]) [Str "Block",Space,Str "Quotes"]
+,Para [Str "E-mail",Space,Str "style:"]
+,BlockQuote
+ [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
+,BlockQuote
+ [Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
+ ,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
+ ,Para [Str "A",Space,Str "list:"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "item",Space,Str "one"]]
+ ,[Para [Str "item",Space,Str "two"]]]
+ ,Para [Str "Nested",Space,Str "block",Space,Str "quotes:"]
+ ,BlockQuote
+ [Para [Str "nested"]]
+ ,BlockQuote
+ [Para [Str "nested"]]]
+,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1."]
+,Para [Str "Box-style:"]
+,BlockQuote
+ [Para [Str "Example:"]
+ ,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"]
+,BlockQuote
+ [OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "do",Space,Str "laundry"]]
+ ,[Para [Str "take",Space,Str "out",Space,Str "the",Space,Str "trash"]]]]
+,Para [Str "Here's",Space,Str "a",Space,Str "nested",Space,Str "one:"]
+,BlockQuote
+ [Para [Str "Joe",Space,Str "said:"]
+ ,BlockQuote
+ [Para [Str "Don't",Space,Str "quote",Space,Str "me."]]]
+,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
+,Header 1 ("code-blocks",[],[]) [Str "Code",Space,Str "Blocks"]
+,Para [Str "Code:"]
+,CodeBlock ("",[],[]) "---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}\n\nthis code block is indented by one tab"
+,Para [Str "And:"]
+,CodeBlock ("",[],[]) " this code block is indented by two tabs\n\nThese should not be escaped: \\$ \\\\ \\> \\[ \\{"
+,Header 1 ("lists",[],[]) [Str "Lists"]
+,Header 2 ("unordered",[],[]) [Str "Unordered"]
+,Para [Str "Asterisks",Space,Str "tight:"]
+,BulletList
+ [[Para [Str "asterisk",Space,Str "1"]]
+ ,[Para [Str "asterisk",Space,Str "2"]]
+ ,[Para [Str "asterisk",Space,Str "3"]]]
+,Para [Str "Asterisks",Space,Str "loose:"]
+,BulletList
+ [[Para [Str "asterisk",Space,Str "1"]]
+ ,[Para [Str "asterisk",Space,Str "2"]]
+ ,[Para [Str "asterisk",Space,Str "3"]]]
+,Para [Str "Pluses",Space,Str "tight:"]
+,BulletList
+ [[Para [Str "Plus",Space,Str "1"]]
+ ,[Para [Str "Plus",Space,Str "2"]]
+ ,[Para [Str "Plus",Space,Str "3"]]]
+,Para [Str "Pluses",Space,Str "loose:"]
+,BulletList
+ [[Para [Str "Plus",Space,Str "1"]]
+ ,[Para [Str "Plus",Space,Str "2"]]
+ ,[Para [Str "Plus",Space,Str "3"]]]
+,Para [Str "Minuses",Space,Str "tight:"]
+,BulletList
+ [[Para [Str "Minus",Space,Str "1"]]
+ ,[Para [Str "Minus",Space,Str "2"]]
+ ,[Para [Str "Minus",Space,Str "3"]]]
+,Para [Str "Minuses",Space,Str "loose:"]
+,BulletList
+ [[Para [Str "Minus",Space,Str "1"]]
+ ,[Para [Str "Minus",Space,Str "2"]]
+ ,[Para [Str "Minus",Space,Str "3"]]]
+,Header 2 ("ordered",[],[]) [Str "Ordered"]
+,Para [Str "Tight:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "First"]]
+ ,[Para [Str "Second"]]
+ ,[Para [Str "Third"]]]
+,Para [Str "and:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "One"]]
+ ,[Para [Str "Two"]]
+ ,[Para [Str "Three"]]]
+,Para [Str "Loose",Space,Str "using",Space,Str "tabs:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "First"]]
+ ,[Para [Str "Second"]]
+ ,[Para [Str "Third"]]]
+,Para [Str "and",Space,Str "using",Space,Str "spaces:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "One"]]
+ ,[Para [Str "Two"]]
+ ,[Para [Str "Three"]]]
+,Para [Str "Multiple",Space,Str "paragraphs:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one."]
+ ,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",SoftBreak,Str "dog's",Space,Str "back."]]
+ ,[Para [Str "Item",Space,Str "2."]]
+ ,[Para [Str "Item",Space,Str "3."]]]
+,Para [Str "List",Space,Str "styles:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ []
+,OrderedList (1,LowerRoman,DefaultDelim)
+ []
+,Header 2 ("nested",[],[]) [Str "Nested"]
+,BulletList
+ [[Para [Str "Tab"]
+ ,BulletList
+ [[Para [Str "Tab"]
+ ,BulletList
+ [[Para [Str "Tab"]]]]]]]
+,Para [Str "Here's",Space,Str "another:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "First"]]
+ ,[Para [Str "Second:"]
+ ,BulletList
+ [[Para [Str "Fee"]]
+ ,[Para [Str "Fie"]]
+ ,[Para [Str "Foe"]]]]
+ ,[Para [Str "Third"]]]
+,Para [Str "Same",Space,Str "thing",Space,Str "but",Space,Str "with",Space,Str "paragraphs:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "First"]]
+ ,[Para [Str "Second:"]
+ ,BulletList
+ [[Para [Str "Fee"]]
+ ,[Para [Str "Fie"]]
+ ,[Para [Str "Foe"]]]]
+ ,[Para [Str "Third"]]]
+,Header 2 ("tabs-and-spaces",[],[]) [Str "Tabs",Space,Str "and",Space,Str "spaces"]
+,BulletList
+ [[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
+ ,[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]
+ ,BulletList
+ [[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
+ ,[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]]]]]
+,Header 2 ("fancy-list-markers",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
+,Para [Str "Autonumbering:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Autonumber."]]
+ ,[Para [Str "More."]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Nested."]]]]]
+,Header 2 ("definition",[],[]) [Str "Definition"]
+,DefinitionList
+ [([Str "Violin"],
+ [[Para [Str "Stringed",Space,Str "musical",Space,Str "instrument."]
+ ,Para [Str "Torture",Space,Str "device."]]])
+ ,([Str "Cello",LineBreak,Str "Violoncello"],
+ [[Para [Str "Low-voiced",Space,Str "stringed",Space,Str "instrument."]]])]
+,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
+,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",SoftBreak,Str "this"],Str "."]
+,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",SoftBreak,Strong [Str "is",Space,Str "this"],Str "."]
+,Para [Str "Empty",Space,Strong [],Space,Str "and",Space,Emph [],Str "."]
+,Para [Str "An",SoftBreak,Emph [Link ("",[],[]) [Str "emphasized",SoftBreak,Str "link"] ("/url","")],Str "."]
+,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
+,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
+,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
+,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
+,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",SoftBreak,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",SoftBreak,Code ("",[],[]) "<html>",Str "."]
+,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "small",Space,Str "caps"],Str "."]
+,Para [Str "These",Space,Str "are",Space,Str "all",Space,Str "underlined:",Space,Str "foo",Space,Str "and",Space,Str "bar."]
+,Para [Str "These",Space,Str "are",Space,Str "all",Space,Str "strikethrough:",Space,Strikeout [Str "foo"],Str ",",SoftBreak,Strikeout [Str "bar"],Str ",",Space,Str "and",Space,Strikeout [Str "baz"],Str "."]
+,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
+,Para [Str "\"Hello,\"",Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Str "\"'Shelob'",Space,Str "is",Space,Str "my",Space,Str "name.\""]
+,Para [Str "'A',",Space,Str "'B',",Space,Str "and",Space,Str "'C'",Space,Str "are",Space,Str "letters."]
+,Para [Str "'Oak,'",Space,Str "'elm,'",Space,Str "and",Space,Str "'beech'",Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Str "'pine.'"]
+,Para [Str "'He",Space,Str "said,",Space,Str "\"I",Space,Str "want",Space,Str "to",Space,Str "go.\"'",Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70's?"]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code ("",[],[]) "code",Str "'",Space,Str "and",Space,Str "a",SoftBreak,Str "\"",Link ("",[],[]) [Str "quoted",SoftBreak,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"."]
+,Para [Str "Some",Space,Str "dashes:",Space,Str "one---two",Space,Str "---",Space,Str "three--four",Space,Str "--",Space,Str "five."]
+,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5-7,",Space,Str "255-66,",Space,Str "1987-1999."]
+,Para [Str "Ellipses...and.",Space,Str ".",Space,Str ".and",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "."]
+,Header 1 ("latex",[],[]) [Str "LaTeX"]
+,BulletList
+ [[Para [Str "\\cite[22-23]{smith.1899}"]]
+ ,[Para [Str "\\doublespacing"]]
+ ,[Para [Str "$2+2=4$"]]
+ ,[Para [Str "$x",Space,Str "\\in",Space,Str "y$"]]
+ ,[Para [Str "$\\alpha",Space,Str "\\wedge",Space,Str "\\omega$"]]
+ ,[Para [Str "$223$"]]
+ ,[Para [Str "$p$-Tree"]]
+ ,[Para [Str "$\\frac{d}{dx}f(x)=\\lim_{h\\to",Space,Str "0}\\frac{f(x+h)-f(x)}{h}$"]]
+ ,[Para [Str "Here's",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Str "$\\alpha",Space,Str "+",Space,Str "\\omega",Space,Str "\\times",SoftBreak,Str "x^2$."]]]
+,Para [Str "These",Space,Str "shouldn't",Space,Str "be",Space,Str "math:"]
+,BulletList
+ [[Para [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",SoftBreak,Code ("",[],[]) "$e = mc^2$",Str "."]]
+ ,[Para [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",Space,Str "(It",SoftBreak,Str "worked",Space,Str "if",Space,Str "\"lot\"",Space,Str "is",Space,Str "emphasized.)"]]
+ ,[Para [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",SoftBreak,Str "emphasized"],Space,Str "23$."]]]
+,Para [Str "Here's",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
+,Para [Str "\\begin{tabular}{|l|l|}\\hline",Space,Str "Animal",Space,Str "&",Space,Str "Number",Space,Str "\\\\",Space,Str "\\hline",Space,Str "Dog",Space,Str "&",SoftBreak,Str "2",Space,Str "\\\\",Space,Str "Cat",Space,Str "&",Space,Str "1",Space,Str "\\\\",Space,Str "\\hline",Space,Str "\\end{tabular}"]
+,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
+,BulletList
+ [[Para [Str "I",Space,Str "hat:",Space,Str "\206"]]
+ ,[Para [Str "o",Space,Str "umlaut:",Space,Str "\246"]]
+ ,[Para [Str "section:",Space,Str "\167"]]
+ ,[Para [Str "set",Space,Str "membership:",Space,Str "elem"]]
+ ,[Para [Str "copyright:",Space,Str "\169"]]]
+,Para [Str "AT&T",Space,Str "has",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "their",Space,Str "name."]
+,Para [Str "AT&T",Space,Str "is",Space,Str "another",Space,Str "way",Space,Str "to",Space,Str "write",Space,Str "it."]
+,Para [Str "This",Space,Str "&",Space,Str "that."]
+,Para [Str "4",Space,Str "<",Space,Str "5."]
+,Para [Str "6",Space,Str ">",Space,Str "5."]
+,Para [Str "Backslash:",Space,Str "\\"]
+,Para [Str "Backtick:",Space,Str "`"]
+,Para [Str "Asterisk:",Space,Str "*"]
+,Para [Str "Underscore:",Space,Str "_"]
+,Para [Str "Left",Space,Str "brace:",Space,Str "{"]
+,Para [Str "Right",Space,Str "brace:",Space,Str "}"]
+,Para [Str "Left",Space,Str "bracket:",Space,Str "["]
+,Para [Str "Right",Space,Str "bracket:",Space,Str "]"]
+,Para [Str "Left",Space,Str "paren:",Space,Str "("]
+,Para [Str "Right",Space,Str "paren:",Space,Str ")"]
+,Para [Str "Greater-than:",Space,Str ">"]
+,Para [Str "Hash:",Space,Str "#"]
+,Para [Str "Period:",Space,Str "."]
+,Para [Str "Bang:",Space,Str "!"]
+,Para [Str "Plus:",Space,Str "+"]
+,Para [Str "Minus:",Space,Str "-"]
+,Header 1 ("links",[],[]) [Str "Links"]
+,Header 2 ("explicit",[],[]) [Str "Explicit"]
+,Para [Str "Just",Space,Str "a",SoftBreak,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
+,Para [Link ("",[],[]) [Str "URL",SoftBreak,Str "and",Space,Str "title"] ("/url/","title"),Str "."]
+,Para [Link ("",[],[]) [Str "URL",SoftBreak,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."]
+,Para [Link ("",[],[]) [Str "URL",SoftBreak,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."]
+,Para [Link ("",[],[]) [Str "URL",SoftBreak,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")]
+,Para [Link ("",[],[]) [Str "URL",SoftBreak,Str "and",Space,Str "title"] ("/url/","title with single quotes")]
+,Para [Str "Email",Space,Str "link",Space,Str "(nobody",Space,Str "[at]",Space,Str "nowhere.net)"]
+,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
+,Header 2 ("reference",[],[]) [Str "Reference"]
+,Para [Str "Foo",SoftBreak,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
+,Para [Str "Foo",SoftBreak,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
+,Para [Str "Foo",SoftBreak,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
+,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",SoftBreak,Str "[brackets]"] ("/url/",""),Str "."]
+,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",SoftBreak,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
+,Para [Str "Indented",SoftBreak,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
+,Para [Str "Indented",SoftBreak,Link ("",[],[]) [Str "twice"] ("/url",""),Str "."]
+,Para [Str "Indented",SoftBreak,Link ("",[],[]) [Str "thrice"] ("/url",""),Str "."]
+,Para [Str "This",Space,Str "should",Space,Str "[not]",Space,Str "be",Space,Str "a",Space,Str "link."]
+,CodeBlock ("",[],[]) "[not]: /url"
+,Para [Str "Foo",SoftBreak,Link ("",[],[]) [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."]
+,Para [Str "Foo",SoftBreak,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."]
+,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
+,Para [Str "Here's",Space,Str "a",SoftBreak,Link ("",[],[]) [Str "link",SoftBreak,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
+,Para [Str "Here's",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",SoftBreak,Link ("",[],[]) [Str "AT&T"] ("http://att.com/","AT&T"),Str "."]
+,Para [Str "Here's",Space,Str "an",SoftBreak,Link ("",[],[]) [Str "inline",SoftBreak,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
+,Para [Str "Here's",Space,Str "an",SoftBreak,Link ("",[],[]) [Str "inline",SoftBreak,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
+,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand:",SoftBreak,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
+,BulletList
+ [[Para [Str "In",Space,Str "a",Space,Str "list?"]]
+ ,[Para [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+ ,[Para [Str "It",Space,Str "should."]]]
+,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere.net"]
+,BlockQuote
+ [Para [Str "Blockquoted:",SoftBreak,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",SoftBreak,Code ("",[],[]) "<http://example.com/>"]
+,CodeBlock ("",[],[]) "or here: <http://example.com/>"
+,Header 1 ("images",[],[]) [Str "Images"]
+,Para [Str "From",Space,Str "\"Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
+,Para [Image ("",[],[]) [] ("lalune.jpg","Voyage dans la Lune")]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",SoftBreak,Image ("",[],[]) [] ("movie.jpg",""),SoftBreak,Str "icon."]
+,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Link ("",[],[]) [Str "(1)"] ("#note_1",""),Str ",",SoftBreak,Str "and",SoftBreak,Str "another",Link ("",[],[]) [Str "(longnote)"] ("#note_longnote",""),Str ".",SoftBreak,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",SoftBreak,Str "contains",Space,Str "a",Space,Str "space^(my",Space,Str "note)."]
+,Para [Link ("",[],[]) [Str "(1)"] ("#ref_1",""),Space,Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",SoftBreak,Str "go",Space,Str "anywhere",Space,Str "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end."]
+,Para [Link ("",[],[]) [Str "(longnote)"] ("#ref_longnote",""),Space,Str "Here's",SoftBreak,Str "the",Space,Str "other",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."]
+,Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",SoftBreak,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)."]
+,CodeBlock ("",[],[]) " { <code> }"
+,Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",SoftBreak,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",SoftBreak,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines."]
+,Para [Str "text",Space,Emph [Str "Leading",Space,Str "space"]]
+,Para [Emph [Str "Trailing",Space,Str "space"],Space,Str "text"]
+,Para [Str "text",Space,Emph [Str "Leading",Space,Str "spaces"]]
+,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"]
+,Header 1 ("tables",[],[]) [Str "Tables"]
+,Header 2 ("tables-with-headers",[],[]) [Str "Tables",Space,Str "with",Space,Str "Headers"]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[Para [Str "X"]]
+ ,[Para [Str "Y"]]
+ ,[Para [Str "Z"]]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Header 2 ("tables-without-headers",[],[]) [Str "Tables",Space,Str "without",Space,Str "Headers"]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[]
+ ,[]
+ ,[]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[]
+ ,[]
+ ,[]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[]
+ ,[]
+ ,[]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
+ [[]
+ ,[]
+ ,[]]
+ [[[Para [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Para [Str "3"]]]
+ ,[[Para [Str "4"]]
+ ,[Para [Str "5"]]
+ ,[Para [Str "6"]]]]
+,Header 2 ("empty-tables",[],[]) [Str "Empty",Space,Str "Tables"]
+,Para [Str "This",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "empty."]]
diff --git a/test/jats-reader.xml b/test/jats-reader.xml
new file mode 100644
index 000000000..eb06fcc22
--- /dev/null
+++ b/test/jats-reader.xml
@@ -0,0 +1,1773 @@
+<?xml version="1.0" encoding="utf-8" ?>
+<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.0 20120330//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">
+<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>
+</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<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>
+ Box-style:
+ </p>
+ <disp-quote>
+ <p>
+ Example:
+ </p>
+ <preformat>sub status {
+ print &quot;working&quot;;
+}</preformat>
+ </disp-quote>
+ <disp-quote>
+ <list list-type="order">
+ <list-item>
+ <p>
+ do laundry
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ take out the trash
+ </p>
+ </list-item>
+ </list>
+ </disp-quote>
+ <p>
+ Here's a nested one:
+ </p>
+ <disp-quote>
+ <p>
+ Joe said:
+ </p>
+ <disp-quote>
+ <p>
+ Don't quote me.
+ </p>
+ </disp-quote>
+ </disp-quote>
+ <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>
+ <p>
+ List styles:
+ </p>
+ <list list-type="order"></list>
+ <list list-type="roman-lower"></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>
+ <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>
+ </sec>
+ <sec id="definition">
+ <title>Definition</title>
+ <def-list>
+ <def-item>
+ <term>
+ Violin
+ </term>
+ <def>
+ <p>
+ Stringed musical instrument.
+ </p>
+ <p>
+ Torture device.
+ </p>
+ </def>
+ </def-item>
+ <def-item>
+ <term>
+ Cello<break />Violoncello
+ </term>
+ <def>
+ <p>
+ Low-voiced stringed instrument.
+ </p>
+ </def>
+ </def-item>
+ </def-list>
+ </sec>
+</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 role="strong">strong</bold>, and so
+ <bold role="strong">is this</bold>.
+ </p>
+ <p>
+ Empty <bold role="strong"></bold> and <italic></italic>.
+ </p>
+ <p>
+ An
+ <italic><ext-link ext-link-type="uri" xlink:href="/url">emphasized
+ link</ext-link></italic>.
+ </p>
+ <p>
+ <bold role="strong"><italic>This is strong and em.</italic></bold>
+ </p>
+ <p>
+ So is <bold role="strong"><italic>this</italic></bold> word.
+ </p>
+ <p>
+ <bold role="strong"><italic>This is strong and em.</italic></bold>
+ </p>
+ <p>
+ So is <bold role="strong"><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>
+ This is <sc role="smallcaps">small caps</sc>.
+ </p>
+ <p>
+ These are all underlined: foo and bar.
+ </p>
+ <p>
+ These are all strikethrough: <strike>foo</strike>,
+ <strike>bar</strike>, and <strike>baz</strike>.
+ </p>
+</sec>
+<sec id="smart-quotes-ellipses-dashes">
+ <title>Smart quotes, ellipses, dashes</title>
+ <p>
+ &quot;Hello,&quot; said the spider. &quot;'Shelob' is my name.&quot;
+ </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, &quot;I want to go.&quot;' Were you alive in the 70's?
+ </p>
+ <p>
+ Here is some quoted '<monospace>code</monospace>' and a
+ &quot;<ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&amp;bar=2">quoted
+ link</ext-link>&quot;.
+ </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>
+ \cite[22-23]{smith.1899}
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ \doublespacing
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ $2+2=4$
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ $x \in y$
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ $\alpha \wedge \omega$
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ $223$
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ $p$-Tree
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
+ </p>
+ </list-item>
+ <list-item>
+ <p>
+ Here's one that has a line break in it: $\alpha + \omega \times
+ x^2$.
+ </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 &quot;lot&quot; is emphasized.)
+ </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>
+ <p>
+ \begin{tabular}{|l|l|}\hline Animal &amp; Number \\ \hline Dog &amp;
+ 2 \\ Cat &amp; 1 \\ \hline \end{tabular}
+ </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: elem
+ </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>
+ Email link (nobody [at] nowhere.net)
+ </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>
+ Foo
+ <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>.
+ </p>
+ <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: nobody [at] nowhere.net
+ </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 &quot;Voyage dans la Lune&quot; by Georges Melies (1902):
+ </p>
+ <p>
+ <inline-graphic mimetype="image" mime-subtype="jpeg" xlink:href="lalune.jpg" xlink:title="Voyage dans la Lune" />
+ </p>
+ <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 alt="(1)" rid="note_1">(1)</xref>,
+ and
+ another<xref alt="(longnote)" rid="note_longnote">(longnote)</xref>.
+ This should <italic>not</italic> be a footnote reference, because it
+ contains a space^(my note).
+ </p>
+ <p>
+ <xref alt="(1)" rid="ref_1">(1)</xref> Here is the footnote. It can
+ go anywhere in the document, not just at the end.
+ </p>
+ <p>
+ <xref alt="(longnote)" rid="ref_longnote">(longnote)</xref> Here's
+ the other note. This one contains multiple blocks.
+ </p>
+ <p>
+ Caret characters are used to indicate that the blocks all belong to
+ a single footnote (as with block quotes).
+ </p>
+ <preformat> { &lt;code&gt; }</preformat>
+ <p>
+ If you want, you can use a caret at the beginning of every line, as
+ with blockquotes, but all that you need is a caret at the beginning
+ of the first line of the block and any preceding blank lines.
+ </p>
+ <p>
+ text <italic>Leading space</italic>
+ </p>
+ <p>
+ <italic>Trailing space</italic> text
+ </p>
+ <p>
+ text <italic>Leading spaces</italic>
+ </p>
+ <p>
+ <italic>Trailing spaces</italic> text
+ </p>
+</sec>
+<sec id="tables">
+ <title>Tables</title>
+ <sec id="tables-with-headers">
+ <title>Tables with Headers</title>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col width="33*" align="left" />
+ <col width="33*" align="left" />
+ <col width="33*" align="left" />
+ <thead>
+ <tr>
+ <th>
+ <p>
+ X
+ </p>
+ </th>
+ <th>
+ <p>
+ Y
+ </p>
+ </th>
+ <th>
+ <p>
+ Z
+ </p>
+ </th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ </sec>
+ <sec id="tables-without-headers">
+ <title>Tables without Headers</title>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ <table>
+ <col align="left" />
+ <col align="left" />
+ <col align="left" />
+ <tbody>
+ <tr>
+ <td>
+ <p>
+ 1
+ </p>
+ </td>
+ <td>
+ <p>
+ 2
+ </p>
+ </td>
+ <td>
+ <p>
+ 3
+ </p>
+ </td>
+ </tr>
+ <tr>
+ <td>
+ <p>
+ 4
+ </p>
+ </td>
+ <td>
+ <p>
+ 5
+ </p>
+ </td>
+ <td>
+ <p>
+ 6
+ </p>
+ </td>
+ </tr>
+ </tbody>
+ </table>
+ </sec>
+ <sec id="empty-tables">
+ <title>Empty Tables</title>
+ <p>
+ This section should be empty.
+ </p>
+ </sec>
+</sec>
+</body>
+<back>
+</back>
+</article>
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index 123434411..ff852ee0e 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -11,6 +11,7 @@ import qualified Tests.Readers.Creole
import qualified Tests.Readers.Docx
import qualified Tests.Readers.EPUB
import qualified Tests.Readers.HTML
+import qualified Tests.Readers.JATS
import qualified Tests.Readers.LaTeX
import qualified Tests.Readers.Markdown
import qualified Tests.Readers.Muse
@@ -61,6 +62,7 @@ tests = testGroup "pandoc tests" [ Tests.Command.tests
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests
, testGroup "Markdown" Tests.Readers.Markdown.tests
, testGroup "HTML" Tests.Readers.HTML.tests
+ , testGroup "JATS" Tests.Readers.JATS.tests
, testGroup "Org" Tests.Readers.Org.tests
, testGroup "RST" Tests.Readers.RST.tests
, testGroup "Docx" Tests.Readers.Docx.tests