aboutsummaryrefslogtreecommitdiff
path: root/tests
diff options
context:
space:
mode:
Diffstat (limited to 'tests')
-rw-r--r--tests/Tests/Old.hs8
-rw-r--r--tests/Tests/Readers/Docx.hs34
-rw-r--r--tests/Tests/Readers/EPUB.hs8
-rw-r--r--tests/Tests/Readers/LaTeX.hs52
-rw-r--r--tests/Tests/Readers/Markdown.hs53
-rw-r--r--tests/Tests/Readers/Org.hs138
-rw-r--r--tests/Tests/Readers/RST.hs45
-rw-r--r--tests/Tests/Readers/Txt2Tags.hs3
-rw-r--r--tests/Tests/Shared.hs37
-rw-r--r--tests/Tests/Writers/Docx.hs129
-rw-r--r--tests/Tests/Writers/LaTeX.hs5
-rw-r--r--tests/Tests/Writers/Markdown.hs91
-rw-r--r--tests/Tests/Writers/RST.hs79
-rw-r--r--tests/docbook-reader.docbook22
-rw-r--r--tests/docbook-reader.native69
-rw-r--r--tests/docx/german_styled_lists.docxbin0 -> 43957 bytes
-rw-r--r--tests/docx/german_styled_lists.native6
-rw-r--r--tests/docx/i18n_blocks.docxbin0 -> 13680 bytes
-rw-r--r--tests/docx/i18n_blocks.native8
-rw-r--r--tests/docx/image_no_embed_writer.native2
-rw-r--r--tests/docx/image_vml.docxbin0 -> 23559 bytes
-rw-r--r--tests/docx/image_vml.native4
-rw-r--r--tests/docx/inline_formatting_writer.native5
-rw-r--r--tests/docx/inline_images_writer.native2
-rw-r--r--tests/docx/links.docxbin41751 -> 45361 bytes
-rw-r--r--tests/docx/links.native1
-rw-r--r--tests/docx/links_writer.native6
-rw-r--r--tests/docx/lists_writer.native17
-rw-r--r--tests/docx/numbered_header.docxbin0 -> 26129 bytes
-rw-r--r--tests/docx/numbered_header.native1
-rw-r--r--tests/docx/table_with_list_cell.docxbin0 -> 32615 bytes
-rw-r--r--tests/docx/table_with_list_cell.native11
-rw-r--r--tests/docx/verbatim_subsuper.docxbin0 -> 10353 bytes
-rw-r--r--tests/docx/verbatim_subsuper.native8
-rw-r--r--tests/dokuwiki_external_images.dokuwiki1
-rw-r--r--tests/dokuwiki_external_images.native1
-rw-r--r--tests/dokuwiki_inline_formatting.dokuwiki3
-rw-r--r--tests/epub/features.epubbin67495 -> 66370 bytes
-rw-r--r--tests/epub/features.native38
-rw-r--r--tests/epub/img.epubbin0 -> 61768 bytes
-rw-r--r--tests/html-reader.html248
-rw-r--r--tests/html-reader.native129
-rw-r--r--tests/latex-reader.latex27
-rw-r--r--tests/latex-reader.native11
-rw-r--r--tests/lhs-test.html5
-rw-r--r--tests/lhs-test.html+lhs5
-rw-r--r--tests/lhs-test.latex6
-rw-r--r--tests/lhs-test.latex+lhs6
-rw-r--r--tests/markdown-reader-more.native10
-rw-r--r--tests/markdown-reader-more.txt16
-rw-r--r--tests/media/rId25.jpg0
-rw-r--r--tests/media/rId26.jpg0
-rw-r--r--tests/media/rId27.jpg0
-rw-r--r--tests/pipe-tables.txt4
-rw-r--r--tests/rst-reader.native6
-rw-r--r--tests/s5-basic.html2
-rw-r--r--tests/s5-fragment.html2
-rw-r--r--tests/s5-inserts.html2
-rw-r--r--tests/tables.asciidoc1
-rw-r--r--tests/tables.haddock1
-rw-r--r--tests/tables.opendocument8
-rw-r--r--tests/tables.org1
-rw-r--r--tests/tables.rst1
-rw-r--r--tests/test-pandoc.hs4
-rw-r--r--tests/twiki-reader.native174
-rw-r--r--tests/twiki-reader.twiki221
-rw-r--r--tests/writer.asciidoc7
-rw-r--r--tests/writer.dokuwiki8
-rw-r--r--tests/writer.fb22
-rw-r--r--tests/writer.html20
-rw-r--r--tests/writer.icml133
-rw-r--r--tests/writer.latex24
-rw-r--r--tests/writer.markdown4
-rw-r--r--tests/writer.mediawiki7
-rw-r--r--tests/writer.opendocument8
-rw-r--r--tests/writer.opml14
-rw-r--r--tests/writer.plain4
-rw-r--r--tests/writer.rst7
-rw-r--r--tests/writer.texinfo46
79 files changed, 1747 insertions, 314 deletions
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 8a256b761..047ad0481 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -18,6 +18,7 @@ import Prelude hiding ( readFile )
import qualified Data.ByteString.Lazy as B
import Text.Pandoc.UTF8 (toStringLazy)
import Text.Printf
+import Text.Pandoc.Error
readFileUTF8 :: FilePath -> IO String
readFileUTF8 f = B.readFile f >>= return . toStringLazy
@@ -130,6 +131,8 @@ tests = [ testGroup "markdown"
"dokuwiki_inline_formatting.native" "dokuwiki_inline_formatting.dokuwiki"
, test "multiblock table" ["-r", "native", "-w", "dokuwiki", "-s"]
"dokuwiki_multiblock_table.native" "dokuwiki_multiblock_table.dokuwiki"
+ , test "external images" ["-r", "native", "-w", "dokuwiki", "-s"]
+ "dokuwiki_external_images.native" "dokuwiki_external_images.dokuwiki"
]
, testGroup "opml"
[ test "basic" ["-r", "native", "-w", "opml", "--columns=78", "-s"]
@@ -153,6 +156,9 @@ tests = [ testGroup "markdown"
, test "formatting" ["-r", "epub", "-w", "native"]
"epub/formatting.epub" "epub/formatting.native"
]
+ , testGroup "twiki"
+ [ test "reader" ["-r", "twiki", "-w", "native", "-s"]
+ "twiki-reader.twiki" "twiki-reader.native" ]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests f)
[ "opendocument" , "context" , "texinfo", "icml"
, "man" , "plain" , "rtf", "org", "asciidoc"
@@ -177,7 +183,7 @@ lhsReaderTest :: String -> Test
lhsReaderTest format =
testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"]
("lhs-test" <.> format) norm
- where normalizer = writeNative def . normalize . readNative
+ where normalizer = writeNative def . normalize . handleError . readNative
norm = if format == "markdown+lhs"
then "lhs-test-markdown.native"
else "lhs-test.native"
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index 234b1b5b7..47292bc99 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -13,7 +13,7 @@ import Text.Pandoc.Writers.Native (writeNative)
import qualified Data.Map as M
import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
import Codec.Archive.Zip
-import System.FilePath (combine)
+import Text.Pandoc.Error
-- We define a wrapper around pandoc that doesn't normalize in the
-- tests. Since we do our own normalization, we want to make sure
@@ -42,8 +42,8 @@ compareOutput :: ReaderOptions
compareOutput opts docxFile nativeFile = do
df <- B.readFile docxFile
nf <- Prelude.readFile nativeFile
- let (p, _) = readDocx opts df
- return $ (noNorm p, noNorm (readNative nf))
+ let (p, _) = handleError $ readDocx opts df
+ return $ (noNorm p, noNorm (handleError $ readNative nf))
testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO opts name docxFile nativeFile = do
@@ -60,7 +60,7 @@ testCompare = testCompareWithOpts def
getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
getMedia archivePath mediaPath = do
zf <- B.readFile archivePath >>= return . toArchive
- return $ findEntryByPath (combine "word" mediaPath) zf >>= (Just . fromEntry)
+ return $ findEntryByPath ("word/" ++ mediaPath) zf >>= (Just . fromEntry)
compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool
compareMediaPathIO mediaPath mediaBag docxPath = do
@@ -80,7 +80,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do
compareMediaBagIO :: FilePath -> IO Bool
compareMediaBagIO docxFile = do
df <- B.readFile docxFile
- let (_, mb) = readDocx def df
+ let (_, mb) = handleError $ readDocx def df
bools <- mapM
(\(fp, _, _) -> compareMediaPathIO fp mb docxFile)
(mediaDirectory mb)
@@ -115,6 +115,10 @@ tests = [ testGroup "inlines"
"docx/image.docx"
"docx/image_no_embed.native"
, testCompare
+ "VML image"
+ "docx/image_vml.docx"
+ "docx/image_vml.native"
+ , testCompare
"inline image in links"
"docx/inline_images.docx"
"docx/inline_images.native"
@@ -142,6 +146,10 @@ tests = [ testGroup "inlines"
"inline code (with VerbatimChar style)"
"docx/inline_code.docx"
"docx/inline_code.native"
+ , testCompare
+ "inline code in subscript and superscript"
+ "docx/verbatim_subsuper.docx"
+ "docx/verbatim_subsuper.native"
]
, testGroup "blocks"
[ testCompare
@@ -153,6 +161,14 @@ tests = [ testGroup "inlines"
"docx/already_auto_ident.docx"
"docx/already_auto_ident.native"
, testCompare
+ "numbered headers automatically made into list"
+ "docx/numbered_header.docx"
+ "docx/numbered_header.native"
+ , testCompare
+ "i18n blocks (headers and blockquotes)"
+ "docx/i18n_blocks.docx"
+ "docx/i18n_blocks.native"
+ , testCompare
"lists"
"docx/lists.docx"
"docx/lists.native"
@@ -161,6 +177,10 @@ tests = [ testGroup "inlines"
"docx/definition_list.docx"
"docx/definition_list.native"
, testCompare
+ "custom defined lists in styles"
+ "docx/german_styled_lists.docx"
+ "docx/german_styled_lists.native"
+ , testCompare
"footnotes and endnotes"
"docx/notes.docx"
"docx/notes.native"
@@ -177,6 +197,10 @@ tests = [ testGroup "inlines"
"docx/tables.docx"
"docx/tables.native"
, testCompare
+ "tables with lists in cells"
+ "docx/table_with_list_cell.docx"
+ "docx/table_with_list_cell.native"
+ , testCompare
"code block"
"docx/codeblock.docx"
"docx/codeblock.native"
diff --git a/tests/Tests/Readers/EPUB.hs b/tests/Tests/Readers/EPUB.hs
index f27ea979f..bfdaa45b7 100644
--- a/tests/Tests/Readers/EPUB.hs
+++ b/tests/Tests/Readers/EPUB.hs
@@ -8,9 +8,11 @@ import qualified Data.ByteString.Lazy as BL
import Text.Pandoc.Readers.EPUB
import Text.Pandoc.MediaBag (MediaBag, mediaDirectory)
import Control.Applicative
+import System.FilePath (joinPath)
+import Text.Pandoc.Error
getMediaBag :: FilePath -> IO MediaBag
-getMediaBag fp = snd . readEPUB def <$> BL.readFile fp
+getMediaBag fp = snd . handleError . readEPUB def <$> BL.readFile fp
testMediaBag :: FilePath -> [(String, String, Int)] -> IO ()
testMediaBag fp bag = do
@@ -22,12 +24,12 @@ testMediaBag fp bag = do
(actBag == bag)
featuresBag :: [(String, String, Int)]
-featuresBag = [("img/ElementaryMathExample.png","image/png",1331),("img/Maghreb1.png","image/png",2520),("img/check.gif","image/gif",1340),("img/check.jpg","image/jpeg",2661),("img/check.png","image/png",2815),("img/cichons_diagram.png","image/png",7045),("img/complex_number.png","image/png",5238),("img/multiscripts_and_greek_alphabet.png","image/png",10060)]
+featuresBag = [(joinPath ["img","check.gif"],"image/gif",1340),(joinPath ["img","check.jpg"],"image/jpeg",2661),(joinPath ["img","check.png"],"image/png",2815),(joinPath ["img","multiscripts_and_greek_alphabet.png"],"image/png",10060)]
tests :: [Test]
tests =
[ testGroup "EPUB Mediabag"
[ testCase "features bag"
- (testMediaBag "epub/features.epub" featuresBag)
+ (testMediaBag "epub/img.epub" featuresBag)
]
]
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index 8ff23ebc1..b72d707e7 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -7,15 +7,21 @@ import Tests.Helpers
import Tests.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
+import Data.Monoid (mempty)
+import Text.Pandoc.Error
latex :: String -> Pandoc
-latex = readLaTeX def
+latex = handleError . readLaTeX def
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
(=:) = test latex
+simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
+simpleTable' aligns = table "" (zip aligns (repeat 0.0))
+ (map (const mempty) aligns)
+
tests :: [Test]
tests = [ testGroup "basic"
[ "simple" =:
@@ -62,10 +68,54 @@ tests = [ testGroup "basic"
"\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock ""
]
+ , testGroup "tables"
+ [ "Single cell table" =:
+ "\\begin{tabular}{|l|}Test\\\\\\end{tabular}" =?>
+ simpleTable' [AlignLeft] [[plain "Test"]]
+ , "Multi cell table" =:
+ "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Multi line table" =:
+ unlines [ "\\begin{tabular}{|c|}"
+ , "One\\\\"
+ , "Two\\\\"
+ , "Three\\\\"
+ , "\\end{tabular}" ] =?>
+ simpleTable' [AlignCenter]
+ [[plain "One"], [plain "Two"], [plain "Three"]]
+ , "Empty table" =:
+ "\\begin{tabular}{}\\end{tabular}" =?>
+ simpleTable' [] []
+ , "Table with fixed column width" =:
+ "\\begin{tabular}{|p{5cm}r|}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignLeft,AlignRight] [[plain "One", plain "Two"]]
+ , "Table with empty column separators" =:
+ "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Table with custom column separators" =:
+ unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}"
+ , "One&Two\\\\"
+ , "\\end{tabular}" ] =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Table with vertical alignment argument" =:
+ "\\begin{tabular}[t]{r|r}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignRight] [[plain "One", plain "Two"]]
+ ]
+
, testGroup "citations"
[ natbibCitations
, biblatexCitations
]
+
+ , let hex = ['0'..'9']++['a'..'f'] in
+ testGroup "Character Escapes"
+ [ "Two-character escapes" =:
+ concat ["^^"++[i,j] | i <- hex, j <- hex] =?>
+ para (str ['\0'..'\255'])
+ , "One-character escapes" =:
+ concat ["^^"++[i] | i <- hex] =?>
+ para (str $ ['p'..'y']++['!'..'&'])
+ ]
]
baseCitation :: Citation
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index b45d94032..1cc00fd5e 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -9,17 +9,21 @@ import Text.Pandoc.Builder
import qualified Data.Set as Set
-- import Text.Pandoc.Shared ( normalize )
import Text.Pandoc
+import Text.Pandoc.Error
markdown :: String -> Pandoc
-markdown = readMarkdown def
+markdown = handleError . readMarkdown def
markdownSmart :: String -> Pandoc
-markdownSmart = readMarkdown def { readerSmart = True }
+markdownSmart = handleError . readMarkdown def { readerSmart = True }
markdownCDL :: String -> Pandoc
-markdownCDL = readMarkdown def { readerExtensions = Set.insert
+markdownCDL = handleError . readMarkdown def { readerExtensions = Set.insert
Ext_compact_definition_lists $ readerExtensions def }
+markdownGH :: String -> Pandoc
+markdownGH = handleError . readMarkdown def { readerExtensions = githubMarkdownExtensions }
+
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
@@ -27,7 +31,7 @@ infix 4 =:
testBareLink :: (String, Inlines) -> Test
testBareLink (inp, ils) =
- test (readMarkdown def{ readerExtensions =
+ test (handleError . readMarkdown def{ readerExtensions =
Set.fromList [Ext_autolink_bare_uris, Ext_raw_html] })
inp (inp, doc $ para ils)
@@ -184,6 +188,11 @@ tests = [ testGroup "inline code"
]
, testGroup "bare URIs"
(map testBareLink bareLinkTests)
+ , testGroup "autolinks"
+ [ "with unicode dash following" =:
+ "<http://foo.bar>\8212" =?> para (autolink "http://foo.bar" <>
+ str "\8212")
+ ]
, testGroup "Headers"
[ "blank line before header" =:
"\n# Header\n"
@@ -199,6 +208,9 @@ tests = [ testGroup "inline code"
, test markdownSmart "apostrophe in French"
("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
=?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
+ , test markdownSmart "apostrophe after math" $ -- issue #1909
+ "The value of the $x$'s and the systems' condition." =?>
+ para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
]
, testGroup "footnotes"
[ "indent followed by newline and flush-left text" =:
@@ -212,7 +224,7 @@ tests = [ testGroup "inline code"
=?> para (note (para "See [^1]"))
]
, testGroup "lhs"
- [ test (readMarkdown def{ readerExtensions = Set.insert
+ [ test (handleError . readMarkdown def{ readerExtensions = Set.insert
Ext_literate_haskell $ readerExtensions def })
"inverse bird tracks and html" $
"> a\n\n< b\n\n<div>\n"
@@ -271,5 +283,36 @@ tests = [ testGroup "inline code"
plain (text "if this button exists") <>
rawBlock "html" "</button>" <>
divWith nullAttr (para $ text "with this div too.")]
+ , test markdownGH "issue #1636" $
+ unlines [ "* a"
+ , "* b"
+ , "* c"
+ , " * d" ]
+ =?>
+ bulletList [ plain "a"
+ , plain "b"
+ , plain "c" <> bulletList [plain "d"] ]
+ ]
+ , testGroup "citations"
+ [ "simple" =:
+ "@item1" =?> para (cite [
+ Citation{ citationId = "item1"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ ] "@item1")
+ , "key starts with digit" =:
+ "@1657:huyghens" =?> para (cite [
+ Citation{ citationId = "1657:huyghens"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ ] "@1657:huyghens")
]
]
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index cc4e495f3..4cec54a68 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -4,14 +4,17 @@ module Tests.Readers.Org (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Data.List (intersperse)
import Data.Monoid (mempty, mappend, mconcat)
+import Text.Pandoc.Error
org :: String -> Pandoc
-org = readOrg def
+org = handleError . readOrg def
+
+orgSmart :: String -> Pandoc
+orgSmart = handleError . readOrg def { readerSmart = True }
infix 4 =:
(=:) :: ToString c
@@ -126,6 +129,18 @@ tests =
, (emph "b") <> "."
])
+ , "Quotes are forbidden border chars" =:
+ "/'nope/ *nope\"*" =?>
+ para ("/'nope/" <> space <> "*nope\"*")
+
+ , "Commata are forbidden border chars" =:
+ "/nada,/" =?>
+ para "/nada,/"
+
+ , "Markup should work properly after a blank line" =:
+ unlines ["foo", "", "/bar/"] =?>
+ (para $ text "foo") <> (para $ emph $ text "bar")
+
, "Inline math must stay within three lines" =:
unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
para ((math "a\nb\nc") <> space <>
@@ -185,10 +200,26 @@ tests =
"[[http://zeitlens.com/]]" =?>
(para $ link "http://zeitlens.com/" "" "http://zeitlens.com/")
+ , "Absolute file link" =:
+ "[[/url][hi]]" =?>
+ (para $ link "file:///url" "" "hi")
+
+ , "Link to file in parent directory" =:
+ "[[../file.txt][moin]]" =?>
+ (para $ link "../file.txt" "" "moin")
+
+ , "Empty link (for gitit interop)" =:
+ "[[][New Link]]" =?>
+ (para $ link "" "" "New Link")
+
, "Image link" =:
"[[sunset.png][dusk.svg]]" =?>
(para $ link "sunset.png" "" (image "dusk.svg" "" ""))
+ , "Image link with non-image target" =:
+ "[[http://example.com][logo.png]]" =?>
+ (para $ link "http://example.com" "" (image "logo.png" "" ""))
+
, "Plain link" =:
"Posts on http://zeitlens.com/ can be funny at times." =?>
(para $ spcSep [ "Posts", "on"
@@ -203,6 +234,14 @@ tests =
, "for", "fnords."
])
+ , "Absolute file link" =:
+ "[[file:///etc/passwd][passwd]]" =?>
+ (para $ link "file:///etc/passwd" "" "passwd")
+
+ , "File link" =:
+ "[[file:target][title]]" =?>
+ (para $ link "target" "" "title")
+
, "Anchor" =:
"<<anchor>> Link here later." =?>
(para $ spanWith ("anchor", [], []) mempty <>
@@ -264,6 +303,18 @@ tests =
"\\notacommand{foo}" =?>
para (rawInline "latex" "\\notacommand{foo}")
+ , "MathML symbol in LaTeX-style" =:
+ "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?>
+ para ("There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ').")
+
+ , "MathML symbol in LaTeX-style, including braces" =:
+ "\\Aacute{}stor" =?>
+ para "Ástor"
+
+ , "MathML copy sign" =:
+ "\\copy" =?>
+ para "©"
+
, "LaTeX citation" =:
"\\cite{Coffee}" =?>
let citation = Citation
@@ -446,6 +497,18 @@ tests =
, header 2 ("walk" <> space <> "dog")
]
+ , "Comment Trees" =:
+ unlines [ "* COMMENT A comment tree"
+ , " Not much going on here"
+ , "** This will be dropped"
+ , "* Comment tree above"
+ ] =?>
+ header 1 "Comment tree above"
+
+ , "Nothing but a COMMENT header" =:
+ "* COMMENT Test" =?>
+ (mempty::Blocks)
+
, "Paragraph starting with an asterisk" =:
"*five" =?>
para "*five"
@@ -574,6 +637,13 @@ tests =
, plain "Item2"
]
+ , "Unindented *" =:
+ ("- Item1\n" ++
+ "* Item2\n") =?>
+ bulletList [ plain "Item1"
+ ] <>
+ header 1 "Item2"
+
, "Multi-line Bullet Lists" =:
("- *Fat\n" ++
" Tony*\n" ++
@@ -618,6 +688,33 @@ tests =
]
]
+ , "Bullet List with Decreasing Indent" =:
+ (" - Discovery\n\
+ \ - Human After All\n") =?>
+ mconcat [ bulletList [ plain "Discovery" ]
+ , bulletList [ plain ("Human" <> space <> "After" <> space <> "All")]
+ ]
+
+ , "Header follows Bullet List" =:
+ (" - Discovery\n\
+ \ - Human After All\n\
+ \* Homework") =?>
+ mconcat [ bulletList [ plain "Discovery"
+ , plain ("Human" <> space <> "After" <> space <> "All")
+ ]
+ , header 1 "Homework"
+ ]
+
+ , "Bullet List Unindented with trailing Header" =:
+ ("- Discovery\n\
+ \- Homework\n\
+ \* NotValidListItem") =?>
+ mconcat [ bulletList [ plain "Discovery"
+ , plain "Homework"
+ ]
+ , header 1 "NotValidListItem"
+ ]
+
, "Simple Ordered List" =:
("1. Item1\n" ++
"2. Item2\n") =?>
@@ -698,7 +795,9 @@ tests =
]
])
]
-
+ , "Definition list with multi-word term" =:
+ " - Elijah Wood :: He plays Frodo" =?>
+ definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])]
, "Compact definition list" =:
unlines [ "- ATP :: adenosine 5' triphosphate"
, "- DNA :: deoxyribonucleic acid"
@@ -711,6 +810,16 @@ tests =
, ("PCR", [ plain $ spcSep [ "polymerase", "chain", "reaction" ] ])
]
+ , "Definition List With Trailing Header" =:
+ "- definition :: list\n\
+ \- cool :: defs\n\
+ \* header" =?>
+ mconcat [ definitionList [ ("definition", [plain "list"])
+ , ("cool", [plain "defs"])
+ ]
+ , header 1 "header"
+ ]
+
, "Loose bullet list" =:
unlines [ "- apple"
, ""
@@ -944,7 +1053,7 @@ tests =
, ""
, "#+RESULTS:"
, ": 65" ] =?>
- rawBlock "html" ""
+ rawBlock "html" ""
, "Example block" =:
unlines [ "#+begin_example"
@@ -1051,4 +1160,25 @@ tests =
]
in codeBlockWith ( "", classes, params) "code body\n"
]
+ , testGroup "Smart punctuation"
+ [ test orgSmart "quote before ellipses"
+ ("'...hi'"
+ =?> para (singleQuoted "…hi"))
+
+ , test orgSmart "apostrophe before emph"
+ ("D'oh! A l'/aide/!"
+ =?> para ("D’oh! A l’" <> emph "aide" <> "!"))
+
+ , test orgSmart "apostrophe in French"
+ ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
+ =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
+
+ , test orgSmart "Quotes cannot occur at the end of emphasized text"
+ ("/say \"yes\"/" =?>
+ para ("/say" <> space <> doubleQuoted "yes" <> "/"))
+
+ , test orgSmart "Dashes are allowed at the borders of emphasis'"
+ ("/foo---/" =?>
+ para (emph "foo—"))
+ ]
]
diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs
index a80dc32b7..5eabec89a 100644
--- a/tests/Tests/Readers/RST.hs
+++ b/tests/Tests/Readers/RST.hs
@@ -7,10 +7,11 @@ import Tests.Helpers
import Tests.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
+import Text.Pandoc.Error
import Data.Monoid (mempty)
rst :: String -> Pandoc
-rst = readRST def{ readerStandalone = True }
+rst = handleError . readRST def{ readerStandalone = True }
infix 4 =:
(=:) :: ToString c
@@ -67,5 +68,45 @@ tests = [ "line block with blank line" =:
link "http://foo.bar.baz" "" "http://foo.bar.baz" <> ". " <>
link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)"
<> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")")
+ , testGroup "literal / line / code blocks"
+ [ "indented literal block" =: unlines
+ [ "::"
+ , ""
+ , " block quotes"
+ , ""
+ , " can go on for many lines"
+ , "but must stop here"]
+ =?> (doc $
+ codeBlock "block quotes\n\ncan go on for many lines" <>
+ para "but must stop here")
+ , "line block with 3 lines" =: "| a\n| b\n| c"
+ =?> para ("a" <> linebreak <> "b" <> linebreak <> "c")
+ , "quoted literal block using >" =: "::\n\n> quoted\n> block\n\nOrdinary paragraph"
+ =?> codeBlock "> quoted\n> block" <> para "Ordinary paragraph"
+ , "quoted literal block using | (not a line block)" =: "::\n\n| quoted\n| block\n\nOrdinary paragraph"
+ =?> codeBlock "| quoted\n| block" <> para "Ordinary paragraph"
+ , "class directive with single paragraph" =: ".. class:: special\n\nThis is a \"special\" paragraph."
+ =?> divWith ("", ["special"], []) (para "This is a \"special\" paragraph.")
+ , "class directive with two paragraphs" =: ".. class:: exceptional remarkable\n\n First paragraph.\n\n Second paragraph."
+ =?> divWith ("", ["exceptional", "remarkable"], []) (para "First paragraph." <> para "Second paragraph.")
+ , "class directive around literal block" =: ".. class:: classy\n\n::\n\n a\n b"
+ =?> divWith ("", ["classy"], []) (codeBlock "a\nb")]
+ , testGroup "interpreted text roles"
+ [ "literal role prefix" =: ":literal:`a`" =?> para (code "a")
+ , "literal role postfix" =: "`a`:literal:" =?> para (code "a")
+ , "literal text" =: "``text``" =?> para (code "text")
+ , "code role" =: ":code:`a`" =?> para (codeWith ("", ["sourceCode"], []) "a")
+ , "inherited code role" =: ".. role:: codeLike(code)\n\n:codeLike:`a`"
+ =?> para (codeWith ("", ["codeLike", "sourceCode"], []) "a")
+ , "custom code role with language field"
+ =: ".. role:: lhs(code)\n :language: haskell\n\n:lhs:`a`"
+ =?> para (codeWith ("", ["lhs", "haskell","sourceCode"], []) "a")
+ , "custom role with unspecified parent role"
+ =: ".. role:: classy\n\n:classy:`text`"
+ =?> para (spanWith ("", ["classy"], []) "text")
+ , "role with recursive inheritance"
+ =: ".. role:: haskell(code)\n.. role:: lhs(haskell)\n\n:lhs:`text`"
+ =?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text")
+ , "unknown role" =: ":unknown:`text`" =?> para (str "text")
+ ]
]
-
diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs
index fd7c767e0..938a2b455 100644
--- a/tests/Tests/Readers/Txt2Tags.hs
+++ b/tests/Tests/Readers/Txt2Tags.hs
@@ -7,12 +7,13 @@ import Tests.Helpers
import Tests.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
+import Text.Pandoc.Error
import Data.List (intersperse)
import Data.Monoid (mempty, mconcat)
import Text.Pandoc.Readers.Txt2Tags
t2t :: String -> Pandoc
-t2t s = readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def s
+t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
infix 4 =:
(=:) :: ToString c
diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs
index b6671835c..9b55b7b1d 100644
--- a/tests/Tests/Shared.hs
+++ b/tests/Tests/Shared.hs
@@ -9,6 +9,7 @@ import Test.Framework.Providers.HUnit
import Test.HUnit ( assertBool, (@?=) )
import Text.Pandoc.Builder
import Data.Monoid
+import System.FilePath (joinPath)
tests :: [Test]
tests = [ testGroup "normalize"
@@ -40,21 +41,21 @@ p_normalize_no_trailing_spaces ils = null ils' || last ils' /= Space
testCollapse :: [Test]
testCollapse = map (testCase "collapse")
- [ (collapseFilePath "" @?= "")
- , (collapseFilePath "./foo" @?= "foo")
- , (collapseFilePath "././../foo" @?= "../foo")
- , (collapseFilePath "../foo" @?= "../foo")
- , (collapseFilePath "/bar/../baz" @?= "/baz")
- , (collapseFilePath "/../baz" @?= "/../baz")
- , (collapseFilePath "./foo/.././bar/../././baz" @?= "baz")
- , (collapseFilePath "./" @?= "")
- , (collapseFilePath "././" @?= "")
- , (collapseFilePath "../" @?= "..")
- , (collapseFilePath ".././" @?= "..")
- , (collapseFilePath "./../" @?= "..")
- , (collapseFilePath "../../" @?= "../..")
- , (collapseFilePath "parent/foo/baz/../bar" @?= "parent/foo/bar")
- , (collapseFilePath "parent/foo/baz/../../bar" @?= "parent/bar")
- , (collapseFilePath "parent/foo/.." @?= "parent")
- , (collapseFilePath "/parent/foo/../../bar" @?= "/bar")
- , (collapseFilePath "/./parent/foo" @?= "/parent/foo")]
+ [ (collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""]))
+ , (collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"]))
+ , (collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]]))
+ , (collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"]))
+ , (collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"]))
+ , (collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"]))
+ , (collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"]))
+ , (collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""]))
+ , (collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""]))
+ , (collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."]))
+ , (collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."]))
+ , (collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."]))
+ , (collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."]))
+ , (collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"]))
+ , (collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"]))
+ , (collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"]))
+ , (collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"]))
+ , (collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"]))]
diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs
new file mode 100644
index 000000000..068c5a935
--- /dev/null
+++ b/tests/Tests/Writers/Docx.hs
@@ -0,0 +1,129 @@
+module Tests.Writers.Docx (tests) where
+
+import Text.Pandoc.Options
+import Text.Pandoc.Readers.Native
+import Text.Pandoc.Definition
+import Tests.Helpers
+import Test.Framework
+import Text.Pandoc.Readers.Docx
+import Text.Pandoc.Writers.Docx
+import Text.Pandoc.Error
+
+type Options = (WriterOptions, ReaderOptions)
+
+compareOutput :: Options
+ -> FilePath
+ -> IO (Pandoc, Pandoc)
+compareOutput opts nativeFile = do
+ nf <- Prelude.readFile nativeFile
+ df <- writeDocx (fst opts) (handleError $ readNative nf)
+ let (p, _) = handleError $ readDocx (snd opts) df
+ return (p, handleError $ readNative nf)
+
+testCompareWithOptsIO :: Options -> String -> FilePath -> IO Test
+testCompareWithOptsIO opts name nativeFile = do
+ (dp, np) <- compareOutput opts nativeFile
+ return $ test id name (dp, np)
+
+testCompareWithOpts :: Options -> String -> FilePath -> Test
+testCompareWithOpts opts name nativeFile =
+ buildTest $ testCompareWithOptsIO opts name nativeFile
+
+testCompare :: String -> FilePath -> Test
+testCompare = testCompareWithOpts def
+
+tests :: [Test]
+tests = [ testGroup "inlines"
+ [ testCompare
+ "font formatting"
+ "docx/inline_formatting_writer.native"
+ , testCompare
+ "font formatting with character styles"
+ "docx/char_styles.native"
+ , testCompare
+ "hyperlinks"
+ "docx/links_writer.native"
+ , testCompare
+ "inline image"
+ "docx/image_no_embed_writer.native"
+ , testCompare
+ "inline image in links"
+ "docx/inline_images_writer.native"
+ , testCompare
+ "handling unicode input"
+ "docx/unicode.native"
+ , testCompare
+ "literal tabs"
+ "docx/tabs.native"
+ , testCompare
+ "normalizing inlines"
+ "docx/normalize.native"
+ , testCompare
+ "normalizing inlines deep inside blocks"
+ "docx/deep_normalize.native"
+ , testCompare
+ "move trailing spaces outside of formatting"
+ "docx/trailing_spaces_in_formatting.native"
+ , testCompare
+ "inline code (with VerbatimChar style)"
+ "docx/inline_code.native"
+ , testCompare
+ "inline code in subscript and superscript"
+ "docx/verbatim_subsuper.native"
+ ]
+ , testGroup "blocks"
+ [ testCompare
+ "headers"
+ "docx/headers.native"
+ , testCompare
+ "headers already having auto identifiers"
+ "docx/already_auto_ident.native"
+ , testCompare
+ "numbered headers automatically made into list"
+ "docx/numbered_header.native"
+ , testCompare
+ "i18n blocks (headers and blockquotes)"
+ "docx/i18n_blocks.native"
+ -- Continuation does not survive round-trip
+ , testCompare
+ "lists"
+ "docx/lists_writer.native"
+ , testCompare
+ "definition lists"
+ "docx/definition_list.native"
+ , testCompare
+ "custom defined lists in styles"
+ "docx/german_styled_lists.native"
+ , testCompare
+ "footnotes and endnotes"
+ "docx/notes.native"
+ , testCompare
+ "blockquotes (parsing indent as blockquote)"
+ "docx/block_quotes_parse_indent.native"
+ , testCompare
+ "hanging indents"
+ "docx/hanging_indent.native"
+ -- tables headers do not survive round-trip, should look into that
+ , testCompare
+ "tables"
+ "docx/tables.native"
+ , testCompare
+ "tables with lists in cells"
+ "docx/table_with_list_cell.native"
+ , testCompare
+ "code block"
+ "docx/codeblock.native"
+ , testCompare
+ "dropcap paragraphs"
+ "docx/drop_cap.native"
+ ]
+ , testGroup "metadata"
+ [ testCompareWithOpts (def,def{readerStandalone=True})
+ "metadata fields"
+ "docx/metadata.native"
+ , testCompareWithOpts (def,def{readerStandalone=True})
+ "stop recording metadata with normal text"
+ "docx/metadata_after_normal.native"
+ ]
+
+ ]
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index 965589965..d1cfd3ddf 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -52,7 +52,7 @@ tests = [ testGroup "code blocks"
[ "unnumbered header" =:
headerWith ("foo",["unnumbered"],[]) 1
(text "Header 1" <> note (plain $ text "note")) =?>
- "\\section*{Header 1\\footnote{note}}\\label{foo}\n\\addcontentsline{toc}{section}{Header 1}\n"
+ "\\section*{\\texorpdfstring{Header 1\\footnote{note}}{Header 1}}\\label{foo}\n\\addcontentsline{toc}{section}{Header 1}\n"
, "in list item" =:
bulletList [header 2 (text "foo")] =?>
"\\begin{itemize}\n\\item ~\n \\subsection{foo}\n\\end{itemize}"
@@ -60,6 +60,9 @@ tests = [ testGroup "code blocks"
definitionList [(text "foo", [header 2 (text "bar"),
para $ text "baz"])] =?>
"\\begin{description}\n\\item[foo] ~ \n\\subsection{bar}\n\nbaz\n\\end{description}"
+ , "containing image" =:
+ header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
+ "\\section{\\texorpdfstring{\\protect\\includegraphics{imgs/foo.jpg}}{Alt text}}"
]
, testGroup "inline code"
[ "struck out and highlighted" =:
diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs
index c2a8f5903..dce40ddcb 100644
--- a/tests/Tests/Writers/Markdown.hs
+++ b/tests/Tests/Writers/Markdown.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
+{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Tests.Writers.Markdown (tests) where
import Test.Framework
@@ -35,4 +36,92 @@ tests = [ "indented code after list"
=: bulletList [ plain "foo" <> bulletList [ plain "bar" ],
plain "baz" ]
=?> "- foo\n - bar\n- baz\n"
- ]
+ ] ++ [shortcutLinkRefsTests]
+
+shortcutLinkRefsTests :: Test
+shortcutLinkRefsTests =
+ let infix 4 =:
+ (=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> Test
+ (=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc)
+ in testGroup "Shortcut reference links"
+ [ "Simple link (shortcutable)"
+ =: (para (link "/url" "title" "foo"))
+ =?> "[foo]\n\n [foo]: /url \"title\""
+ , "Followed by another link (unshortcutable)"
+ =: (para ((link "/url1" "title1" "first")
+ <> (link "/url2" "title2" "second")))
+ =?> unlines [ "[first][][second]"
+ , ""
+ , " [first]: /url1 \"title1\""
+ , " [second]: /url2 \"title2\""
+ ]
+ , "Followed by space and another link (unshortcutable)"
+ =: (para ((link "/url1" "title1" "first") <> " "
+ <> (link "/url2" "title2" "second")))
+ =?> unlines [ "[first][] [second]"
+ , ""
+ , " [first]: /url1 \"title1\""
+ , " [second]: /url2 \"title2\""
+ ]
+ , "Reference link is used multiple times (unshortcutable)"
+ =: (para ((link "/url1" "" "foo") <> (link "/url2" "" "foo")
+ <> (link "/url3" "" "foo")))
+ =?> unlines [ "[foo][][foo][1][foo][2]"
+ , ""
+ , " [foo]: /url1"
+ , " [1]: /url2"
+ , " [2]: /url3"
+ ]
+ , "Reference link is used multiple times (unshortcutable)"
+ =: (para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo")
+ <> " " <> (link "/url3" "" "foo")))
+ =?> unlines [ "[foo][] [foo][1] [foo][2]"
+ , ""
+ , " [foo]: /url1"
+ , " [1]: /url2"
+ , " [2]: /url3"
+ ]
+ , "Reference link is followed by text in brackets"
+ =: (para ((link "/url" "" "link") <> "[text in brackets]"))
+ =?> unlines [ "[link][][text in brackets]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by space and text in brackets"
+ =: (para ((link "/url" "" "link") <> " [text in brackets]"))
+ =?> unlines [ "[link][] [text in brackets]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by RawInline"
+ =: (para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]"))
+ =?> unlines [ "[link][][rawText]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by space and RawInline"
+ =: (para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]"))
+ =?> unlines [ "[link][] [rawText]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by RawInline with space"
+ =: (para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]"))
+ =?> unlines [ "[link][] [rawText]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by citation"
+ =: (para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]")))
+ =?> unlines [ "[link][][@author]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by space and citation"
+ =: (para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]")))
+ =?> unlines [ "[link][] [@author]"
+ , ""
+ , " [link]: /url"
+ ]
+ ]
diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs
new file mode 100644
index 000000000..2a511782f
--- /dev/null
+++ b/tests/Tests/Writers/RST.hs
@@ -0,0 +1,79 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.RST (tests) where
+
+import Test.Framework
+import Text.Pandoc.Builder
+import Text.Pandoc
+import Tests.Helpers
+import Tests.Arbitrary()
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> Test
+(=:) = test (writeRST def{ writerHighlight = True } . toPandoc)
+
+tests :: [Test]
+tests = [ testGroup "rubrics"
+ [ "in list item" =:
+ bulletList [header 2 (text "foo")] =?>
+ "- .. rubric:: foo"
+ , "in definition list item" =:
+ definitionList [(text "foo", [header 2 (text "bar"),
+ para $ text "baz"])] =?>
+ unlines
+ [ "foo"
+ , " .. rubric:: bar"
+ , ""
+ , " baz"]
+ , "in block quote" =:
+ blockQuote (header 1 (text "bar")) =?>
+ " .. rubric:: bar"
+ , "with id" =:
+ blockQuote (headerWith ("foo",[],[]) 1 (text "bar")) =?>
+ unlines
+ [ " .. rubric:: bar"
+ , " :name: foo"]
+ , "with id class" =:
+ blockQuote (headerWith ("foo",["baz"],[]) 1 (text "bar")) =?>
+ unlines
+ [ " .. rubric:: bar"
+ , " :name: foo"
+ , " :class: baz"]
+ ]
+ , testGroup "headings"
+ [ "normal heading" =:
+ header 1 (text "foo") =?>
+ unlines
+ [ "foo"
+ , "==="]
+ , "heading levels" =:
+ header 1 (text "Header 1") <>
+ header 3 (text "Header 2") <>
+ header 2 (text "Header 2") <>
+ header 1 (text "Header 1") <>
+ header 4 (text "Header 2") <>
+ header 5 (text "Header 3") <>
+ header 3 (text "Header 2") =?>
+ unlines
+ [ "Header 1"
+ , "========"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 1"
+ , "========"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 3"
+ , "~~~~~~~~"
+ , ""
+ , "Header 2"
+ , "--------"]
+ ]
+ ]
diff --git a/tests/docbook-reader.docbook b/tests/docbook-reader.docbook
index 9ba965d9b..cf5059646 100644
--- a/tests/docbook-reader.docbook
+++ b/tests/docbook-reader.docbook
@@ -509,6 +509,25 @@ These should not be escaped: \$ \\ \&gt; \[ \{
B. Williams
</para>
</sect2>
+ <sect2 id="callout">
+ <title>Callout</title>
+ <para>Simple.</para>
+ <calloutlist>
+ <callout arearefs="loop1-letrec-co" id="loop1-letrec">
+ <para id="x_QA1">A <code>__letrec</code> is equivalent to a normal
+ Haskell &let;.</para>
+ </callout>
+ <callout arearefs="loop1-def-co" id="loop1-def">
+ <para id="x_RA1">&GHC; compiled the body of our list comprehension into
+ a loop named <function>go_s1YC</function>.</para>
+ </callout>
+ <callout arearefs="loop1-pat-empty-co" id="loop1-pat-empty">
+ <para id="x_SA1">If our &case; expression matches the empty list, we
+ return the empty list. This is reassuringly
+ familiar.</para>
+ </callout>
+ </calloutlist>
+ </sect2>
</sect1>
<sect1 id="definition-lists">
<title>Definition Lists</title>
@@ -691,6 +710,9 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<literal>&lt;html&gt;</literal>.
</para>
<para>
+ More code: <classname>Class</classname> and <type>Type</type>
+ </para>
+ <para>
<emphasis role="strikethrough">This is
<emphasis>strikeout</emphasis>.</emphasis>
</para>
diff --git a/tests/docbook-reader.native b/tests/docbook-reader.native
index 90d76b3c2..353a352a2 100644
--- a/tests/docbook-reader.native
+++ b/tests/docbook-reader.native
@@ -1,22 +1,22 @@
Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
-,Header 1 ("",[],[]) [Str "Headers"]
-,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")]
-,Header 3 ("",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
-,Header 4 ("",[],[]) [Str "Level",Space,Str "4"]
-,Header 5 ("",[],[]) [Str "Level",Space,Str "5"]
+,Header 1 ("headers",[],[]) [Str "Headers"]
+,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,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"]
,Para [Str "Hi."]
-,Header 1 ("",[],[]) [Str "Level",Space,Str "1"]
-,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Emph [Str "emphasis"]]
-,Header 3 ("",[],[]) [Str "Level",Space,Str "3"]
+,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 ("",[],[]) [Str "Level",Space,Str "2"]
+,Header 2 ("level-2",[],[]) [Str "Level",Space,Str "2"]
,Para [Str "with",Space,Str "no",Space,Str "blank",Space,Str "line"]
-,Header 1 ("",[],[]) [Str "Paragraphs"]
+,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"]
,Para [Str "Here\8217s",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",Space,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",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
-,Header 1 ("",[],[]) [Str "Block",Space,Str "Quotes"]
+,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."]]
@@ -35,13 +35,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[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 "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
-,Header 1 ("",[],[]) [Str "Code",Space,Str "Blocks"]
+,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 ("",[],[]) [Str "Lists"]
-,Header 2 ("",[],[]) [Str "Unordered"]
+,Header 1 ("lists",[],[]) [Str "Lists"]
+,Header 2 ("unordered",[],[]) [Str "Unordered"]
,Para [Str "Asterisks",Space,Str "loose:"]
,BulletList
[[Para [Str "asterisk",Space,Str "1"]]
@@ -57,7 +57,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[[Para [Str "Minus",Space,Str "1"]]
,[Para [Str "Minus",Space,Str "2"]]
,[Para [Str "Minus",Space,Str "3"]]]
-,Header 2 ("",[],[]) [Str "Ordered"]
+,Header 2 ("ordered",[],[]) [Str "Ordered"]
,OrderedList (1,Decimal,DefaultDelim)
[[Para [Str "First"]]
,[Para [Str "Second"]]
@@ -73,7 +73,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,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",Space,Str "dog\8217s",Space,Str "back."]]
,[Para [Str "Item",Space,Str "2."]]
,[Para [Str "Item",Space,Str "3."]]]
-,Header 2 ("",[],[]) [Str "Nested"]
+,Header 2 ("nested",[],[]) [Str "Nested"]
,BulletList
[[Para [Str "Tab"]
,BulletList
@@ -98,14 +98,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Para [Str "Fie"]]
,[Para [Str "Foe"]]]]
,[Para [Str "Third"]]]
-,Header 2 ("",[],[]) [Str "Tabs",Space,Str "and",Space,Str "spaces"]
+,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 ("",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
+,Header 2 ("fancy-list-markers",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
,OrderedList (2,Decimal,DefaultDelim)
[[Para [Str "begins",Space,Str "with",Space,Str "2"]]
,[Para [Str "and",Space,Str "now",Space,Str "3"]
@@ -134,7 +134,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "list",Space,Str "item:"]
,Para [Str "M.A.\160\&2007"]
,Para [Str "B.",Space,Str "Williams"]
-,Header 1 ("",[],[]) [Str "Definition",Space,Str "Lists"]
+,Header 2 ("callout",[],[]) [Str "Callout"]
+,Para [Str "Simple."]
+,BulletList
+ [[Para [Str "A",Space,Code ("",[],[]) "__letrec",Space,Str "is",Space,Str "equivalent",Space,Str "to",Space,Str "a",Space,Str "normal",Space,Str "Haskell",Space,Str "LET."]]
+ ,[Para [Str "GHC",Space,Str "compiled",Space,Str "the",Space,Str "body",Space,Str "of",Space,Str "our",Space,Str "list",Space,Str "comprehension",Space,Str "into",Space,Str "a",Space,Str "loop",Space,Str "named",Space,Code ("",[],[]) "go_s1YC",Str "."]]
+ ,[Para [Str "If",Space,Str "our",Space,Str "CASE",Space,Str "expression",Space,Str "matches",Space,Str "the",Space,Str "empty",Space,Str "list,",Space,Str "we",Space,Str "return",Space,Str "the",Space,Str "empty",Space,Str "list.",Space,Str "This",Space,Str "is",Space,Str "reassuringly",Space,Str "familiar."]]]
+,Header 1 ("definition-lists",[],[]) [Str "Definition",Space,Str "Lists"]
,DefinitionList
[([Str "apple"],
[[Para [Str "red",Space,Str "fruit"]]])
@@ -170,7 +176,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,OrderedList (1,Decimal,DefaultDelim)
[[Para [Str "sublist"]]
,[Para [Str "sublist"]]]]])]
-,Header 1 ("",[],[]) [Str "Inline",Space,Str "Markup"]
+,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",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
@@ -179,20 +185,21 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,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 ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
+,Para [Str "More",Space,Str "code:",Space,Code ("",[],[]) "Class",Space,Str "and",Space,Code ("",[],[]) "Type"]
,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello\160there"],Str "."]
,Para [Str "Subscripts:",Space,Str "H",Subscript [Str "2"],Str "O,",Space,Str "H",Subscript [Str "23"],Str "O,",Space,Str "H",Subscript [Str "many\160of\160them"],Str "O."]
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "the",Space,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
-,Header 1 ("",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
+,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]]
,Para [Quoted DoubleQuote [Str "A"],Str ",",Space,Quoted DoubleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted DoubleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted DoubleQuote [Str "He",Space,Str "said,",Space,Quoted SingleQuote [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\8217s?"]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
,Para [Str "Ellipses\8230and\8230and\8230."]
-,Header 1 ("",[],[]) []
+,Header 1 ("math",[],[]) []
,Para [Math DisplayMath "e = mc^{2}",Math DisplayMath "1",Space,Math InlineMath "e = mc^{2}",Space,Math DisplayMath "e = mc^{2}"]
-,Header 1 ("",[],[]) [Str "Special",Space,Str "Characters"]
+,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"]]
@@ -221,8 +228,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Bang:",Space,Str "!"]
,Para [Str "Plus:",Space,Str "+"]
,Para [Str "Minus:",Space,Str "-"]
-,Header 1 ("",[],[]) [Str "Links"]
-,Header 2 ("",[],[]) [Str "Explicit"]
+,Header 1 ("links",[],[]) [Str "Links"]
+,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
@@ -232,7 +239,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Link [Str "with_underscore"] ("/url/with_underscore","")]
,Para [Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,Para [Link [Str "Empty"] ("",""),Str "."]
-,Header 2 ("",[],[]) [Str "Reference"]
+,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
@@ -245,12 +252,12 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/",""),Str "."]
-,Header 2 ("",[],[]) [Str "With",Space,Str "ampersands"]
+,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,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\8217s",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:",Space,Link [Str "AT&T"] ("http://att.com/",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
-,Header 2 ("",[],[]) [Str "Autolinks"]
+,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,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?"]]
@@ -261,18 +268,18 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
-,Header 1 ("",[],[]) [Str "Images"]
+,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [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 [Str "lalune"] ("lalune.jpg","")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [] ("movie.jpg",""),Space,Str "icon."]
-,Header 1 ("",[],[]) [Str "Footnotes"]
+,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,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",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,DefaultDelim)
[[Para [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]]]]
,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]
-,Header 1 ("",[],[]) [Str "Tables"]
+,Header 1 ("tables",[],[]) [Str "Tables"]
,Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"]
,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
[[Plain [Str "Right"]]
diff --git a/tests/docx/german_styled_lists.docx b/tests/docx/german_styled_lists.docx
new file mode 100644
index 000000000..ce454e9cc
--- /dev/null
+++ b/tests/docx/german_styled_lists.docx
Binary files differ
diff --git a/tests/docx/german_styled_lists.native b/tests/docx/german_styled_lists.native
new file mode 100644
index 000000000..4d5456dfc
--- /dev/null
+++ b/tests/docx/german_styled_lists.native
@@ -0,0 +1,6 @@
+[BulletList
+ [[Para [Str "One",Space,Str "level",Space,Str "of",Space,Str "the",Space,Str "list."]]
+ ,[Para [Str "Second",Space,Str "level",Space,Str "of",Space,Str "the",Space,Str "list."]
+ ,BulletList
+ [[Para [Str "Next",Space,Str "level",Space,Str "of",Space,Str "the",Space,Str "list"]]]]
+ ,[Para [Str "Back",Space,Str "to",Space,Str "the",Space,Str "top",Space,Str "level."]]]]
diff --git a/tests/docx/i18n_blocks.docx b/tests/docx/i18n_blocks.docx
new file mode 100644
index 000000000..36341c363
--- /dev/null
+++ b/tests/docx/i18n_blocks.docx
Binary files differ
diff --git a/tests/docx/i18n_blocks.native b/tests/docx/i18n_blocks.native
new file mode 100644
index 000000000..582a7360d
--- /dev/null
+++ b/tests/docx/i18n_blocks.native
@@ -0,0 +1,8 @@
+[Header 1 ("this-is-heading-1",[],[]) [Str "This",Space,Str "is",Space,Str "Heading",Space,Str "1"]
+,Header 2 ("this-is-heading-2",[],[]) [Str "This",Space,Str "is",Space,Str "Heading",Space,Str "2"]
+,BlockQuote
+ [Para [Str "This",Space,Str "is",Space,Str "Quote"]
+ ,Para [Str "This",Space,Str "is",Space,Str "Block",Space,Str "Text"]]
+,BulletList
+ [[Para [Str "This",Space,Str "is",Space,Str "list",Space,Str "item",Space,Str "1"]]
+ ,[Para [Str "This",Space,Str "is",Space,Str "list",Space,Str "item",Space,Str "2"]]]]
diff --git a/tests/docx/image_no_embed_writer.native b/tests/docx/image_no_embed_writer.native
new file mode 100644
index 000000000..21802ebd1
--- /dev/null
+++ b/tests/docx/image_no_embed_writer.native
@@ -0,0 +1,2 @@
+[Para [Str "An",Space,Str "image:"]
+,Para [Image [] ("media/rId25.jpg","")]]
diff --git a/tests/docx/image_vml.docx b/tests/docx/image_vml.docx
new file mode 100644
index 000000000..9e4018e00
--- /dev/null
+++ b/tests/docx/image_vml.docx
Binary files differ
diff --git a/tests/docx/image_vml.native b/tests/docx/image_vml.native
new file mode 100644
index 000000000..8c5450a19
--- /dev/null
+++ b/tests/docx/image_vml.native
@@ -0,0 +1,4 @@
+[Header 1 ("vml-image",[],[]) [Strong [Str "VML",Space,Str "Image"]]
+,BlockQuote
+ [Para [Str "It",Space,Str "should",Space,Str "follow",Space,Str "below:"]
+ ,Para [Image [] ("media/image4.jpeg","")]]]
diff --git a/tests/docx/inline_formatting_writer.native b/tests/docx/inline_formatting_writer.native
new file mode 100644
index 000000000..be346204e
--- /dev/null
+++ b/tests/docx/inline_formatting_writer.native
@@ -0,0 +1,5 @@
+[Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."]
+,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."]
+,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Emph [Str "single",Space,Str "underlines",Space,Str "for",Space,Str "emphasis"],Str "."]
+,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."]
+,Para [Str "A",Space,Str "line",LineBreak,Str "break."]]
diff --git a/tests/docx/inline_images_writer.native b/tests/docx/inline_images_writer.native
new file mode 100644
index 000000000..da2a2709b
--- /dev/null
+++ b/tests/docx/inline_images_writer.native
@@ -0,0 +1,2 @@
+[Para [Str "This",Space,Str "picture",Space,Image [] ("media/rId26.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."]
+,Para [Str "Here",Space,Str "is",Space,Link [Str "one",Space,Image [] ("media/rId27.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]]
diff --git a/tests/docx/links.docx b/tests/docx/links.docx
index 10ec62fd7..538b84b08 100644
--- a/tests/docx/links.docx
+++ b/tests/docx/links.docx
Binary files differ
diff --git a/tests/docx/links.native b/tests/docx/links.native
index c741fe875..cd7ab6fb6 100644
--- a/tests/docx/links.native
+++ b/tests/docx/links.native
@@ -1,5 +1,6 @@
[Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."]
+,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://johnmacfarlane.net/pandoc/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."]
,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]
diff --git a/tests/docx/links_writer.native b/tests/docx/links_writer.native
new file mode 100644
index 000000000..cc00e4326
--- /dev/null
+++ b/tests/docx/links_writer.native
@@ -0,0 +1,6 @@
+[Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"]
+,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."]
+,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://johnmacfarlane.net/pandoc/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."]
+,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."]
+,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."]
+,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]]
diff --git a/tests/docx/lists_writer.native b/tests/docx/lists_writer.native
new file mode 100644
index 000000000..4c44ea603
--- /dev/null
+++ b/tests/docx/lists_writer.native
@@ -0,0 +1,17 @@
+[Header 2 ("some-nested-lists",[],[]) [Str "Some",Space,Str "nested",Space,Str "lists"]
+,OrderedList (1,Decimal,Period)
+ [[Para [Str "one"]]
+ ,[Para [Str "two"]
+ ,OrderedList (1,LowerAlpha,DefaultDelim)
+ [[Para [Str "a"]]
+ ,[Para [Str "b"]]]]]
+,BulletList
+ [[Para [Str "one"]]
+ ,[Para [Str "two"]
+ ,BulletList
+ [[Para [Str "three"]
+ ,BulletList
+ [[Para [Str "four"]]]]]]
+ ,[Para [Str "Same",Space,Str "list"]]]
+,BulletList
+ [[Para [Str "Different",Space,Str "list",Space,Str "adjacent",Space,Str "to",Space,Str "the",Space,Str "one",Space,Str "above."]]]]
diff --git a/tests/docx/numbered_header.docx b/tests/docx/numbered_header.docx
new file mode 100644
index 000000000..66ce7648d
--- /dev/null
+++ b/tests/docx/numbered_header.docx
Binary files differ
diff --git a/tests/docx/numbered_header.native b/tests/docx/numbered_header.native
new file mode 100644
index 000000000..a8dd1e897
--- /dev/null
+++ b/tests/docx/numbered_header.native
@@ -0,0 +1 @@
+[Header 1 ("a-numbered-header.",[],[]) [Str "A",Space,Str "Numbered",Space,Str "Header."]]
diff --git a/tests/docx/table_with_list_cell.docx b/tests/docx/table_with_list_cell.docx
new file mode 100644
index 000000000..1db065770
--- /dev/null
+++ b/tests/docx/table_with_list_cell.docx
Binary files differ
diff --git a/tests/docx/table_with_list_cell.native b/tests/docx/table_with_list_cell.native
new file mode 100644
index 000000000..81bb15a1e
--- /dev/null
+++ b/tests/docx/table_with_list_cell.native
@@ -0,0 +1,11 @@
+[Table [] [AlignDefault,AlignDefault] [0.0,0.0]
+ [[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]
+ ,[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]]
+ [[[BulletList
+ [[Para [Str "Cell",Space,Str "with"]]
+ ,[Para [Str "A"]]
+ ,[Para [Str "Bullet",Space,Str "list"]]]]
+ ,[OrderedList (1,Decimal,Period)
+ [[Para [Str "Cell",Space,Str "with"]]
+ ,[Para [Str "A"]]
+ ,[Para [Str "Numbered",Space,Str "list."]]]]]]]
diff --git a/tests/docx/verbatim_subsuper.docx b/tests/docx/verbatim_subsuper.docx
new file mode 100644
index 000000000..2cb0dc16d
--- /dev/null
+++ b/tests/docx/verbatim_subsuper.docx
Binary files differ
diff --git a/tests/docx/verbatim_subsuper.native b/tests/docx/verbatim_subsuper.native
new file mode 100644
index 000000000..2e11e646a
--- /dev/null
+++ b/tests/docx/verbatim_subsuper.native
@@ -0,0 +1,8 @@
+[Para [Str "m",Superscript [Str "2"]]
+,Para [Str "m",Superscript [Code ("",[],[]) "2"]]
+,Para [Code ("",[],[]) "m",Superscript [Str "2"]]
+,Para [Code ("",[],[]) "m",Superscript [Code ("",[],[]) "2"]]
+,Para [Str "m",Subscript [Str "2"]]
+,Para [Str "m",Subscript [Code ("",[],[]) "2"]]
+,Para [Code ("",[],[]) "m",Subscript [Str "2"]]
+,Para [Code ("",[],[]) "m",Subscript [Code ("",[],[]) "2"]]]
diff --git a/tests/dokuwiki_external_images.dokuwiki b/tests/dokuwiki_external_images.dokuwiki
new file mode 100644
index 000000000..cc7eddcda
--- /dev/null
+++ b/tests/dokuwiki_external_images.dokuwiki
@@ -0,0 +1 @@
+{{https://cooluri.com/image.png|HTTPS image}} {{http://cooluri.com/image.png|HTTP image}} {{ftp://ftp.cooluri.com/image.png|FTP image}} {{file:///tmp/coolimage.png|Filesystem image}} {{:/image.jpg|Relative image 1}} {{:image.jpg|Relative image 2}}
diff --git a/tests/dokuwiki_external_images.native b/tests/dokuwiki_external_images.native
new file mode 100644
index 000000000..c2b8876d3
--- /dev/null
+++ b/tests/dokuwiki_external_images.native
@@ -0,0 +1 @@
+[Para [Image [Str "HTTPS",Space,Str "image"] ("https://cooluri.com/image.png",""),Space,Image [Str "HTTP",Space,Str "image"] ("http://cooluri.com/image.png",""),Space,Image [Str "FTP",Space,Str "image"] ("ftp://ftp.cooluri.com/image.png",""),Space,Image [Str "Filesystem",Space,Str "image"] ("file:///tmp/coolimage.png",""),Space,Image [Str "Relative",Space,Str "image",Space,Str "1"] ("/image.jpg",""),Space,Image [Str "Relative",Space,Str "image",Space,Str "2"] ("image.jpg","")]]
diff --git a/tests/dokuwiki_inline_formatting.dokuwiki b/tests/dokuwiki_inline_formatting.dokuwiki
index dd5cb52b4..262094184 100644
--- a/tests/dokuwiki_inline_formatting.dokuwiki
+++ b/tests/dokuwiki_inline_formatting.dokuwiki
@@ -6,7 +6,8 @@ Some people use single underlines for //emphasis//.
Above the line is <sup>superscript</sup> and below the line is <sub>subscript</sub>.
-A line\\ break.
+A line\\
+break.
hello %%//%% world %%**%% from %%__%% me
diff --git a/tests/epub/features.epub b/tests/epub/features.epub
index 8dcae384b..2690eec8b 100644
--- a/tests/epub/features.epub
+++ b/tests/epub/features.epub
Binary files differ
diff --git a/tests/epub/features.native b/tests/epub/features.native
index f01070383..6ccc04f43 100644
--- a/tests/epub/features.native
+++ b/tests/epub/features.native
@@ -1,5 +1,4 @@
-[Para [Image [] ("img/multiscripts_and_greek_alphabet.png","")]
-,Para [Span ("front.xhtml",[],[]) []]
+[Para [Span ("front.xhtml",[],[]) []]
,RawBlock (Format "html") "<section>"
,Header 1 ("",[],[]) [Str "Reflowable",Space,Str "EPUB",Space,Str "3",Space,Str "Conformance",Space,Str "Test",Space,Str "Document:",Space,Str "0100"]
,RawBlock (Format "html") "<section>"
@@ -28,31 +27,6 @@
[[Plain [Str "@@@TODO",Space,Str "provide",Space,Str "info",Space,Str "on",Space,Str "where",Space,Str "to",Space,Str "get",Space,Str "the",Space,Str "results",Space,Str "form"]]])]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
-,Para [Span ("content-images-001.xhtml",[],[]) []]
-,RawBlock (Format "html") "<section>"
-,Header 2 ("content-images-001.xhtml#multimedia",[],[]) [Str "Multimedia"]
-,RawBlock (Format "html") "<section>"
-,Header 3 ("content-images-001.xhtml#images",[],[]) [Str "Images"]
-,RawBlock (Format "html") "<section id=\"img-010\" class=\"ctest\">"
-,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "img-010"],Space,Str "GIF"]
-,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "GIF",Space,Str "image",Space,Str "format",Space,Str "is",Space,Str "supported."]
-,Para [Image [Str "gif",Space,Str "test"] ("img/check.gif","")]
-,Para [Str "If",Space,Str "a",Space,Str "checkmark",Space,Str "precedes",Space,Str "this",Space,Str "paragaph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "<section id=\"img-020\" class=\"ctest\">"
-,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "img-020"],Space,Str "PNG"]
-,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "PNG",Space,Str "image",Space,Str "format",Space,Str "is",Space,Str "supported."]
-,Para [Image [Str "png",Space,Str "test"] ("img/check.png","")]
-,Para [Str "If",Space,Str "a",Space,Str "checkmark",Space,Str "precedes",Space,Str "this",Space,Str "paragaph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "<section id=\"img-030\" class=\"ctest\">"
-,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "img-030"],Space,Str "JPEG"]
-,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "JPEG",Space,Str "image",Space,Str "format",Space,Str "is",Space,Str "supported."]
-,Para [Image [Str "jpeg",Space,Str "test"] ("img/check.jpg","")]
-,Para [Str "If",Space,Str "a",Space,Str "checkmark",Space,Str "precedes",Space,Str "this",Space,Str "paragaph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "</section>"
,Para [Span ("content-mathml-001.xhtml",[],[]) []]
,RawBlock (Format "html") "<section>"
,Header 2 ("content-mathml-001.xhtml#mathml",[],[]) [Str "MathML"]
@@ -94,13 +68,13 @@
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-024"],Str "Horizontal",Space,Str "stretch,",Space,Code ("",[],[]) "mover",Str ",",Space,Code ("",[],[]) "munder",Str ",",Space,Str "and",Space,Code ("",[],[]) "mspace",Space,Str "elements"]
,Para [Str "Tests",Space,Str "whether",Space,Str "horizontal",Space,Str "stretch,",Space,Code ("",[],[]) "mover",Str ",",Space,Code ("",[],[]) "munder",Str ",",Space,Code ("",[],[]) "mspace",Space,Str "elements",Space,Str "are",Space,Str "supported."]
,Para [Math DisplayMath "c = \\overset{\\text{complex\\ number}}{\\overbrace{\\underset{\\text{real}}{\\underbrace{\\mspace{20mu} a\\mspace{20mu}}} + \\underset{\\text{imaginary}}{\\underbrace{\\quad b{\\mathbb{i}}\\quad}}}}"]
-,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Image [Str "description",Space,Str "of",Space,Str "imaginary",Space,Str "number:",Space,Str "c",Space,Str "=",Space,Str "a",Space,Str "+bi",Space,Str "with",Space,Str "an",Space,Str "overbrace",Space,Str "reading",Space,Str "'complex",Space,Str "number'",Space,Str "and",Space,Str "underbraces",Space,Str "below",Space,Str "'a'",Space,Str "and",Space,Str "'b",Space,Str "i'",Space,Str "reading",Space,Str "'real'",Space,Str "and",Space,Str "'imaginary'",Space,Str "respectively."] ("img/complex_number.png",""),Str "."]
+,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"mathml-025\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-025"],Str "Testing",Space,Code ("",[],[]) "mtable",Space,Str "with",Space,Code ("",[],[]) "colspan",Space,Str "and",Space,Code ("",[],[]) "rowspan",Space,Str "attributes,",Space,Str "Hebrew",Space,Str "and",Space,Str "Script",Space,Str "fonts"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "mtable",Space,Str "with",Space,Code ("",[],[]) "colspan",Space,Str "and",Space,Code ("",[],[]) "mspace",Space,Str "attributes",Space,Str "(colum",Space,Str "and",Space,Str "row",Space,Str "spanning)",Space,Str "are",Space,Str "supported;",Space,Str "uses",Space,Str "Hebrew",Space,Str "and",Space,Str "Script",Space,Str "alphabets."]
,Para [Math DisplayMath "\\begin{array}{llllllllll}\n & {\\operatorname{cov}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{L} \\right)} & \\longrightarrow & 2^{\\aleph_{0}} \\\\\n & \\uparrow & & \\uparrow & & \\uparrow & & \\uparrow & & \\\\\n & {\\mathfrak{b}} & \\longrightarrow & {\\mathfrak{d}} & & & & & & \\\\\n & \\uparrow & & \\uparrow & & & & & & \\\\\n\\aleph_{1} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cov}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{L} \\right)} & \\\\\n\\end{array}"]
-,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link [Str "Cicho\324's",Space,Str "Diagram"] ("Cicho%C5%84's_diagram",""),Str ":",Space,Image [Str "rendering",Space,Str "of",Space,Str "Cicho\324's",Space,Str "diagram."] ("img/cichons_diagram.png",""),Str "."]
+,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link [Str "Cicho\324's",Space,Str "Diagram"] ("Cicho%C5%84's_diagram",""),Str ":",Space,Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"mathml-026\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-026"],Str "BiDi,",Space,Str "RTL",Space,Str "and",Space,Str "Arabic",Space,Str "alphabets"]
@@ -111,7 +85,7 @@
,RawBlock (Format "html") "<section id=\"mathml-027\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-027"],Str "Elementary",Space,Str "math:",Space,Str "long",Space,Str "division",Space,Str "notation"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "mlongdiv",Space,Str "elements",Space,Str "(from",Space,Str "elementary",Space,Str "math)",Space,Str "are",Space,Str "supported."]
-,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Str "the",Space,Str "following",Space,Str "image:",Space,Image [Str "A",Space,Str "long",Space,Str "division",Space,Str "dividing",Space,Str "1306",Space,Str "by",Space,Str "3,",Space,Str "presented",Space,Str "in",Space,Str "'lefttop'",Space,Str "(US)",Space,Str "notation"] ("img/ElementaryMathExample.png",""),Str "."]
+,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Str "the",Space,Str "following",Space,Str "image:",Space,Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-switch-001.xhtml",[],[]) []]
@@ -130,6 +104,4 @@
,Para [Str "If",Space,Str "a",Space,Str "MathML",Space,Str "equation",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,Para [Str "If",Space,Str "test",Space,Code ("",[],[]) "switch-010",Space,Str "did",Space,Str "not",Space,Str "pass,",Space,Str "this",Space,Str "test",Space,Str "should",Space,Str "be",Space,Str "marked",Space,Code ("",[],[]) "Not Supported",Str "."]
,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "</section>"
-,Para [Span ("Maghreb1.png",[],[]) []]
-,Para [Image [] ("img/Maghreb1.png","")]]
+,RawBlock (Format "html") "</section>"]
diff --git a/tests/epub/img.epub b/tests/epub/img.epub
new file mode 100644
index 000000000..ebe80d935
--- /dev/null
+++ b/tests/epub/img.epub
Binary files differ
diff --git a/tests/html-reader.html b/tests/html-reader.html
index 14ad3ed54..749925b2a 100644
--- a/tests/html-reader.html
+++ b/tests/html-reader.html
@@ -433,6 +433,7 @@ An e-mail address: nobody [at] nowhere.net<blockquote>
<p>text<em> Leading spaces</em></p>
<p><em>Trailing spaces </em>text</p>
<h1>Tables</h1>
+<h2>Tables with Headers</h2>
<table>
<tr>
<th>X</th>
@@ -450,6 +451,251 @@ An e-mail address: nobody [at] nowhere.net<blockquote>
<td>6</td>
</tr>
</table>
-</body>
+<hr />
+<table>
+ <thead>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <thead>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <th>1</th>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <th>4</th>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <thead>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <th>1</th>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ </tbody>
+ <tfoot>
+ <tr>
+ <th>4</th>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tfoot>
+</table>
+<hr />
+<table>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ <tr>
+ <th>1</th>
+ <th>2</th>
+ <th>3</th>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+</table>
+<hr />
+<table>
+ <tbody>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <thead>
+ </thead>
+ <tbody>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <thead>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ </tbody>
+ <tbody>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <thead>
+ <tr>
+ <th>X</th>
+ <th>Y</th>
+ <th>Z</th>
+ </tr>
+ </thead>
+ <tbody>
+ <tr>
+ <td>1</td>
+ <td><p>2</p></td>
+ <td>3</td>
+ </tr>
+ </tbody>
+ <tbody>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<h2>Tables without Headers</h2>
+<table>
+ <tbody>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+</table>
+<hr />
+<table>
+ <thead>
+ </thead>
+ <tbody>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tbody>
+</table>
+<hr />
+<table>
+ <tbody>
+ <tr>
+ <td>1</td>
+ <td>2</td>
+ <td>3</td>
+ </tr>
+ </tbody>
+ <tfoot>
+ <tr>
+ <td>4</td>
+ <td>5</td>
+ <td>6</td>
+ </tr>
+ </tfoot>
+</table>
+<h2>Empty Tables</h2>
+<p>This section should be empty.</p>
+<table>
+ <tbody>
+ </tbody>
+</table>
+<table>
+</table>
</body>
</html>
diff --git a/tests/html-reader.native b/tests/html-reader.native
index aef6e40fc..b2d660fda 100644
--- a/tests/html-reader.native
+++ b/tests/html-reader.native
@@ -311,6 +311,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,Para [Str "text",Space,Emph [Str "Leading",Space,Str "spaces"]]
,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"]
,Header 1 ("",[],[]) [Str "Tables"]
+,Header 2 ("",[],[]) [Str "Tables",Space,Str "with",Space,Str "Headers"]
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
[[Plain [Str "X"]]
,[Plain [Str "Y"]]
@@ -320,4 +321,130 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,[Plain [Str "3"]]]
,[[Plain [Str "4"]]
,[Plain [Str "5"]]
- ,[Plain [Str "6"]]]]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.3333333333333333,0.3333333333333333,0.3333333333333333]
+ [[Plain [Str "X"]]
+ ,[Plain [Str "Y"]]
+ ,[Plain [Str "Z"]]]
+ [[[Plain [Str "1"]]
+ ,[Para [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,Header 2 ("",[],[]) [Str "Tables",Space,Str "without",Space,Str "Headers"]
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ []
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ []
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ []
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,HorizontalRule
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ []
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]
+ ,[Plain [Str "3"]]]
+ ,[[Plain [Str "4"]]
+ ,[Plain [Str "5"]]
+ ,[Plain [Str "6"]]]]
+,Header 2 ("",[],[]) [Str "Empty",Space,Str "Tables"]
+,Para [Str "This",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "empty."]]
diff --git a/tests/latex-reader.latex b/tests/latex-reader.latex
index 2ebdfed99..4324dbfbe 100644
--- a/tests/latex-reader.latex
+++ b/tests/latex-reader.latex
@@ -845,4 +845,31 @@ indented.
\$ \% \& \# \_ \{ \}
+\section{Block newcommands}
+
+See e.g. issues #1866, #1835
+
+\newcommand{\FIG}[3]{
+ \begin{figure}[h!]
+ \centering
+ \includegraphics[width=#2\columnwidth,angle=0]{#1}
+ \caption{#3}
+ \label{fig:#1}
+ \end{figure}
+}
+
+\newcommand{\separator}{\vspace{4em}}
+
+\separator
+
+\FIG{lalune.jpg}{0.5}{Test caption}
+
+\newcommand{\wbal}{The Wikibook about \LaTeX}
+
+\wbal is a good resource for learning \LaTeX.
+
+\separator with trailing inlines
+
+\FIG{lalune.jpg}{0.5}{Test caption} with trailing inlines
+
\end{document}
diff --git a/tests/latex-reader.native b/tests/latex-reader.native
index abc4b05a7..fbc191125 100644
--- a/tests/latex-reader.native
+++ b/tests/latex-reader.native
@@ -372,4 +372,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[[Para [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]]]]
,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]
,Header 1 ("escaped-characters",[],[]) [Str "Escaped",Space,Str "characters"]
-,Para [Str "$",Space,Str "%",Space,Str "&",Space,Str "#",Space,Str "_",Space,Str "{",Space,Str "}"]]
+,Para [Str "$",Space,Str "%",Space,Str "&",Space,Str "#",Space,Str "_",Space,Str "{",Space,Str "}"]
+,Header 1 ("block-newcommands",[],[]) [Str "Block",Space,Str "newcommands"]
+,Para [Str "See",Space,Str "e.g.",Space,Str "issues",Space,Str "#1866,",Space,Str "#1835"]
+,RawBlock (Format "latex") "\\vspace{4em}"
+,Para [RawInline (Format "latex") "\\centering",Image [Str "Test",Space,Str "caption",Span ("",[],[("data-label","fig:lalune.jpg")]) []] ("lalune.jpg","fig:")]
+,Para [Span ("",[],[]) [Str "The",Space,Str "Wikibook",Space,Str "about",Space,Str "LaTeX"],Str "is",Space,Str "a",Space,Str "good",Space,Str "resource",Space,Str "for",Space,Str "learning",Space,Str "LaTeX."]
+,RawBlock (Format "latex") "\\vspace{4em}"
+,Para [Str "with",Space,Str "trailing",Space,Str "inlines"]
+,Para [RawInline (Format "latex") "\\centering",Image [Str "Test",Space,Str "caption",Span ("",[],[("data-label","fig:lalune.jpg")]) []] ("lalune.jpg","fig:")]
+,Para [Str "with",Space,Str "trailing",Space,Str "inlines"]]
diff --git a/tests/lhs-test.html b/tests/lhs-test.html
index bde505a1e..362c93c04 100644
--- a/tests/lhs-test.html
+++ b/tests/lhs-test.html
@@ -7,6 +7,7 @@
<title></title>
<style type="text/css">code{white-space: pre;}</style>
<style type="text/css">
+div.sourceCode { overflow-x: auto; }
table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode {
margin: 0; padding: 0; vertical-align: baseline; border: none; }
table.sourceCode { width: 100%; line-height: 100%; }
@@ -29,9 +30,9 @@ code > span.er { color: #ff0000; font-weight: bold; }
<body>
<h1 id="lhs-test">lhs test</h1>
<p><code>unsplit</code> is an arrow that takes a pair of values and combines them to return a single value:</p>
-<pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d
+<div class="sourceCode"><pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d
unsplit <span class="fu">=</span> arr <span class="fu">.</span> uncurry
- <span class="co">-- arr (\op (x,y) -&gt; x `op` y)</span></code></pre>
+ <span class="co">-- arr (\op (x,y) -&gt; x `op` y)</span></code></pre></div>
<p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p>
<pre><code>f *** g = first f &gt;&gt;&gt; second g</code></pre>
<p>Block quote:</p>
diff --git a/tests/lhs-test.html+lhs b/tests/lhs-test.html+lhs
index fcdcad303..492d9c718 100644
--- a/tests/lhs-test.html+lhs
+++ b/tests/lhs-test.html+lhs
@@ -7,6 +7,7 @@
<title></title>
<style type="text/css">code{white-space: pre;}</style>
<style type="text/css">
+div.sourceCode { overflow-x: auto; }
table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode {
margin: 0; padding: 0; vertical-align: baseline; border: none; }
table.sourceCode { width: 100%; line-height: 100%; }
@@ -29,9 +30,9 @@ code > span.er { color: #ff0000; font-weight: bold; }
<body>
<h1 id="lhs-test">lhs test</h1>
<p><code>unsplit</code> is an arrow that takes a pair of values and combines them to return a single value:</p>
-<pre class="sourceCode literate literatehaskell"><code class="sourceCode literatehaskell"><span class="ot">&gt; unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d
+<div class="sourceCode"><pre class="sourceCode literate literatehaskell"><code class="sourceCode literatehaskell"><span class="ot">&gt; unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d
<span class="ot">&gt;</span> unsplit <span class="fu">=</span> arr <span class="fu">.</span> uncurry
-<span class="ot">&gt;</span> <span class="co">-- arr (\op (x,y) -&gt; x `op` y)</span></code></pre>
+<span class="ot">&gt;</span> <span class="co">-- arr (\op (x,y) -&gt; x `op` y)</span></code></pre></div>
<p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p>
<pre><code>f *** g = first f &gt;&gt;&gt; second g</code></pre>
<p>Block quote:</p>
diff --git a/tests/lhs-test.latex b/tests/lhs-test.latex
index b4f1b2e59..a94a0540f 100644
--- a/tests/lhs-test.latex
+++ b/tests/lhs-test.latex
@@ -70,6 +70,12 @@
\date{}
+% Redefines (sub)paragraphs to behave more like sections
+\let\oldparagraph\paragraph
+\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}}
+\let\oldsubparagraph\subparagraph
+\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}}
+
\begin{document}
\section{lhs test}\label{lhs-test}
diff --git a/tests/lhs-test.latex+lhs b/tests/lhs-test.latex+lhs
index 20c0c08cb..b69a2add4 100644
--- a/tests/lhs-test.latex+lhs
+++ b/tests/lhs-test.latex+lhs
@@ -51,6 +51,12 @@
\date{}
+% Redefines (sub)paragraphs to behave more like sections
+\let\oldparagraph\paragraph
+\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}}
+\let\oldsubparagraph\subparagraph
+\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}}
+
\begin{document}
\section{lhs test}\label{lhs-test}
diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native
index 30da0afbb..96204898e 100644
--- a/tests/markdown-reader-more.native
+++ b/tests/markdown-reader-more.native
@@ -17,6 +17,7 @@
,Header 3 ("my-header",[],[]) [Str "my",Space,Str "header"]
,Header 2 ("in-math",[],[]) [Str "$",Space,Str "in",Space,Str "math"]
,Para [Math InlineMath "\\$2 + \\$3"]
+,Para [Math InlineMath "x = \\text{the $n$th root of $y$}"]
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "math:"]
,Para [Str "$PATH",Space,Str "90",Space,Str "$PATH"]
,Header 2 ("commented-out-list-item",[],[]) [Str "Commented-out",Space,Str "list",Space,Str "item"]
@@ -78,6 +79,8 @@
,Para [Str "Link",Space,Str "to",Space,Link [Str "Explicit",Space,Str "header",Space,Str "attributes"] ("#foobar",""),Str "."]
,Para [Str "But",Space,Str "this",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "link",Space,Str "to",Space,Link [Str "My",Space,Str "other",Space,Str "header"] ("/foo",""),Str ",",Space,Str "since",Space,Str "the",Space,Str "reference",Space,Str "is",Space,Str "defined."]
,Header 2 ("foobar",["baz"],[("key","val")]) [Str "Explicit",Space,Str "header",Space,Str "attributes"]
+,BlockQuote
+ [Header 2 ("foobar",["baz"],[("key","val")]) [Str "Header",Space,Str "attributes",Space,Str "inside",Space,Str "block",Space,Str "quote"]]
,Header 2 ("line-blocks",[],[]) [Str "Line",Space,Str "blocks"]
,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
,Para [Str "Continuation",Space,Str "line",LineBreak,Str "\160\160and",Space,Str "another"]
@@ -149,6 +152,11 @@
,Para [Link [Str "linky"] ("hi_(there_(nested))","")]
,Header 2 ("reference-link-fallbacks",[],[]) [Str "Reference",Space,Str "link",Space,Str "fallbacks"]
,Para [Str "[",Emph [Str "not",Space,Str "a",Space,Str "link"],Str "]",Space,Str "[",Emph [Str "nope"],Str "]\8230"]
+,Header 2 ("reference-link-followed-by-a-citation",[],[]) [Str "Reference",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "citation"]
+,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",Space,Str "most",Space,Str "vocal",Space,Str "proponent."]
,Header 2 ("empty-reference-links",[],[]) [Str "Empty",Space,Str "reference",Space,Str "links"]
,Para [Str "bar"]
-,Para [Link [Str "foo2"] ("","")]]
+,Para [Link [Str "foo2"] ("","")]
+,Header 2 ("wrapping-shouldnt-introduce-new-list-items",[],[]) [Str "Wrapping",Space,Str "shouldn\8217t",Space,Str "introduce",Space,Str "new",Space,Str "list",Space,Str "items"]
+,BulletList
+ [[Plain [Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "2015."]]]]
diff --git a/tests/markdown-reader-more.txt b/tests/markdown-reader-more.txt
index c486f8885..99e9ec7e8 100644
--- a/tests/markdown-reader-more.txt
+++ b/tests/markdown-reader-more.txt
@@ -60,6 +60,8 @@
$\$2 + \$3$
+$x = \text{the $n$th root of $y$}$
+
This should not be math:
$PATH 90 $PATH
@@ -174,6 +176,8 @@ But this is not a link to [My other header], since the reference is defined.
## Explicit header attributes {#foobar .baz key="val"}
+> ## Header attributes inside block quote {#foobar .baz key="val"}
+
## Line blocks
| But can a bee be said to be
@@ -258,6 +262,13 @@ Empty cells
[*not a link*] [*nope*]...
+## Reference link followed by a citation
+
+MapReduce is a paradigm popularized by [Google] [@mapreduce] as its
+most vocal proponent.
+
+[Google]: http://google.com
+
## Empty reference links
[foo2]:
@@ -265,3 +276,8 @@ Empty cells
bar
[foo2]
+
+## Wrapping shouldn't introduce new list items
+
+- blah blah blah blah blah blah blah blah blah blah blah blah blah blah 2015.
+
diff --git a/tests/media/rId25.jpg b/tests/media/rId25.jpg
new file mode 100644
index 000000000..e69de29bb
--- /dev/null
+++ b/tests/media/rId25.jpg
diff --git a/tests/media/rId26.jpg b/tests/media/rId26.jpg
new file mode 100644
index 000000000..e69de29bb
--- /dev/null
+++ b/tests/media/rId26.jpg
diff --git a/tests/media/rId27.jpg b/tests/media/rId27.jpg
new file mode 100644
index 000000000..e69de29bb
--- /dev/null
+++ b/tests/media/rId27.jpg
diff --git a/tests/pipe-tables.txt b/tests/pipe-tables.txt
index ee8d54d9f..83debd595 100644
--- a/tests/pipe-tables.txt
+++ b/tests/pipe-tables.txt
@@ -1,7 +1,7 @@
Simplest table without caption:
| Default1 | Default2 | Default3 |
-|----------|----------|----------|
+ |----------|----------|----------|
|12|12|12|
|123|123|123|
|1|1|1|
@@ -27,6 +27,7 @@ Simple table without caption:
Headerless table without caption:
+| | | |
|------:|:-----|:------:|
|12|12|12|
|123|123|123|
@@ -48,5 +49,6 @@ One-column:
Header-less one-column:
+| |
|:-:|
|hi|
diff --git a/tests/rst-reader.native b/tests/rst-reader.native
index c77d15775..1f402f835 100644
--- a/tests/rst-reader.native
+++ b/tests/rst-reader.native
@@ -322,12 +322,12 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Null
,Para [Str "And",Space,Str "now",Space,Str "with",Space,RawInline (Format "html") "<b>inline</b> <span id=\"test\">HTML</span>",Str "."]
,Null
-,Para [Str "And",Space,Str "some",Space,Str "inline",Space,Str "haskell",Space,Code ("",["sourceCode","haskell"],[]) "fmap id [1,2..10]",Str "."]
+,Para [Str "And",Space,Str "some",Space,Str "inline",Space,Str "haskell",Space,Code ("",["haskell","sourceCode"],[]) "fmap id [1,2..10]",Str "."]
,Null
,Null
-,Para [Str "Indirect",Space,Str "python",Space,Str "role",Space,Code ("",["sourceCode","python"],[]) "[x*x for x in [1,2,3,4,5]]",Str "."]
+,Para [Str "Indirect",Space,Str "python",Space,Str "role",Space,Code ("",["python","indirect","sourceCode"],[]) "[x*x for x in [1,2,3,4,5]]",Str "."]
,Null
,Null
-,Para [Str "Different",Space,Str "indirect",Space,Str "C",Space,Code ("",["sourceCode","c"],[]) "int x = 15;",Str "."]
+,Para [Str "Different",Space,Str "indirect",Space,Str "C",Space,Code ("",["c","different-indirect","sourceCode"],[]) "int x = 15;",Str "."]
,Header 2 ("literal-symbols",[],[]) [Str "Literal",Space,Str "symbols"]
,Para [Str "2*2",Space,Str "=",Space,Str "4*1"]]
diff --git a/tests/s5-basic.html b/tests/s5-basic.html
index ceb896b8e..ac153d0f1 100644
--- a/tests/s5-basic.html
+++ b/tests/s5-basic.html
@@ -46,7 +46,7 @@
<div id="math" class="slide section level1">
<h1>Math</h1>
<ul>
-<li><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
+<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
</ul>
</div>
</div>
diff --git a/tests/s5-fragment.html b/tests/s5-fragment.html
index e8a888972..81c578d25 100644
--- a/tests/s5-fragment.html
+++ b/tests/s5-fragment.html
@@ -5,5 +5,5 @@
</ul>
<h1 id="math">Math</h1>
<ul>
-<li><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
+<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
</ul>
diff --git a/tests/s5-inserts.html b/tests/s5-inserts.html
index 455225f9b..2feed4173 100644
--- a/tests/s5-inserts.html
+++ b/tests/s5-inserts.html
@@ -27,7 +27,7 @@ STUFF INSERTED
</ul>
<h1 id="math">Math</h1>
<ul>
-<li><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
+<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
</ul>
STUFF INSERTED
</body>
diff --git a/tests/tables.asciidoc b/tests/tables.asciidoc
index ba647866a..2a24544a3 100644
--- a/tests/tables.asciidoc
+++ b/tests/tables.asciidoc
@@ -65,4 +65,3 @@ Multiline table without column headers:
|First |row |12.0 |Example of a row that spans multiple lines.
|Second |row |5.0 |Here's another one. Note the blank line between rows.
|=======================================================================
-
diff --git a/tests/tables.haddock b/tests/tables.haddock
index 413ec97ad..f9efdc0de 100644
--- a/tests/tables.haddock
+++ b/tests/tables.haddock
@@ -74,4 +74,3 @@ Multiline table without column headers:
> the blank line between
> rows.
> ----------- ---------- ------------ --------------------------
-
diff --git a/tests/tables.opendocument b/tests/tables.opendocument
index ff304ef26..aa35abc91 100644
--- a/tests/tables.opendocument
+++ b/tests/tables.opendocument
@@ -63,7 +63,7 @@
</table:table-cell>
</table:table-row>
</table:table>
-<text:p text:style-name="Caption">Demonstration of simple table
+<text:p text:style-name="TableCaption">Demonstration of simple table
syntax.</text:p>
<text:p text:style-name="First_20_paragraph">Simple table without
caption:</text:p>
@@ -197,7 +197,7 @@ spaces:</text:p>
</table:table-cell>
</table:table-row>
</table:table>
-<text:p text:style-name="Caption">Demonstration of simple table
+<text:p text:style-name="TableCaption">Demonstration of simple table
syntax.</text:p>
<text:p text:style-name="First_20_paragraph">Multiline table with
caption:</text:p>
@@ -253,8 +253,8 @@ caption:</text:p>
</table:table-cell>
</table:table-row>
</table:table>
-<text:p text:style-name="Caption">Here's the caption. It may span multiple
-lines.</text:p>
+<text:p text:style-name="TableCaption">Here's the caption. It may span
+multiple lines.</text:p>
<text:p text:style-name="First_20_paragraph">Multiline table without
caption:</text:p>
<table:table table:name="Table5" table:style-name="Table5">
diff --git a/tests/tables.org b/tests/tables.org
index 8d9100d07..9eaf5e706 100644
--- a/tests/tables.org
+++ b/tests/tables.org
@@ -49,4 +49,3 @@ Multiline table without column headers:
| First | row | 12.0 | Example of a row that spans multiple lines. |
| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
-
diff --git a/tests/tables.rst b/tests/tables.rst
index e77f69d97..25d5932ea 100644
--- a/tests/tables.rst
+++ b/tests/tables.rst
@@ -88,4 +88,3 @@ Multiline table without column headers:
| | | | the blank line between |
| | | | rows. |
+-------------+------------+--------------+----------------------------+
-
diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs
index b7b1c30b1..805bad414 100644
--- a/tests/test-pandoc.hs
+++ b/tests/test-pandoc.hs
@@ -20,6 +20,8 @@ import qualified Tests.Writers.Native
import qualified Tests.Writers.Markdown
import qualified Tests.Writers.Plain
import qualified Tests.Writers.AsciiDoc
+import qualified Tests.Writers.Docx
+import qualified Tests.Writers.RST
import qualified Tests.Shared
import qualified Tests.Walk
import Text.Pandoc.Shared (inDirectory)
@@ -38,6 +40,8 @@ tests = [ testGroup "Old" Tests.Old.tests
, testGroup "Markdown" Tests.Writers.Markdown.tests
, testGroup "Plain" Tests.Writers.Plain.tests
, testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests
+ , testGroup "Docx" Tests.Writers.Docx.tests
+ , testGroup "RST" Tests.Writers.RST.tests
]
, testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests
diff --git a/tests/twiki-reader.native b/tests/twiki-reader.native
new file mode 100644
index 000000000..bde55a378
--- /dev/null
+++ b/tests/twiki-reader.native
@@ -0,0 +1,174 @@
+Pandoc (Meta {unMeta = fromList []})
+[Header 1 ("header",[],[]) [Str "header"]
+,Header 2 ("header-level-two",[],[]) [Str "header",Space,Str "level",Space,Str "two"]
+,Header 3 ("header-level-3",[],[]) [Str "header",Space,Str "level",Space,Str "3"]
+,Header 4 ("header-level-four",[],[]) [Str "header",Space,Emph [Str "level"],Space,Str "four"]
+,Header 5 ("header-level-5",[],[]) [Str "header",Space,Str "level",Space,Str "5"]
+,Header 6 ("header-level-6",[],[]) [Str "header",Space,Str "level",Space,Str "6"]
+,Para [Str "---+++++++",Space,Str "not",Space,Str "a",Space,Str "header"]
+,Para [Str "--++",Space,Str "not",Space,Str "a",Space,Str "header"]
+,Header 1 ("emph-and-strong",[],[]) [Str "emph",Space,Str "and",Space,Str "strong"]
+,Para [Emph [Str "emph"],Space,Strong [Str "strong"]]
+,Para [Emph [Strong [Str "strong",Space,Str "and",Space,Str "emph"]]]
+,Para [Strong [Emph [Str "emph",Space,Str "inside"],Space,Str "strong"]]
+,Para [Strong [Str "strong",Space,Str "with",Space,Emph [Str "emph"]]]
+,Para [Emph [Strong [Str "strong",Space,Str "inside"],Space,Str "emph"]]
+,Header 1 ("horizontal-rule",[],[]) [Str "horizontal",Space,Str "rule"]
+,Para [Str "top"]
+,HorizontalRule
+,Para [Str "bottom"]
+,HorizontalRule
+,Header 1 ("nop",[],[]) [Str "nop"]
+,Para [Str "_not",Space,Str "emph_"]
+,Header 1 ("entities",[],[]) [Str "entities"]
+,Para [Str "hi",Space,Str "&",Space,Str "low"]
+,Para [Str "hi",Space,Str "&",Space,Str "low"]
+,Para [Str "G\246del"]
+,Para [Str "\777\2730"]
+,Header 1 ("comments",[],[]) [Str "comments"]
+,Para [Str "inline",Space,Str "comment"]
+,Para [Str "between",Space,Str "blocks"]
+,Header 1 ("linebreaks",[],[]) [Str "linebreaks"]
+,Para [Str "hi",LineBreak,Str "there"]
+,Para [Str "hi",LineBreak,Space,Str "there"]
+,Header 1 ("inline-code",[],[]) [Str "inline",Space,Str "code"]
+,Para [Code ("",[],[]) "*\8594*",Space,Code ("",[],[]) "typed",Space,Code ("",["haskell"],[]) ">>="]
+,Header 1 ("code-blocks",[],[]) [Str "code",Space,Str "blocks"]
+,CodeBlock ("",[],[]) "case xs of\n (_:_) -> reverse xs\n [] -> ['*']"
+,CodeBlock ("",["haskell"],[]) "case xs of\n (_:_) -> reverse xs\n [] -> ['*']"
+,Header 1 ("block-quotes",[],[]) [Str "block",Space,Str "quotes"]
+,Para [Str "Regular",Space,Str "paragraph"]
+,BlockQuote
+ [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote."]
+ ,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]]
+,Para [Str "Nother",Space,Str "paragraph."]
+,Header 1 ("external-links",[],[]) [Str "external",Space,Str "links"]
+,Para [Link [Emph [Str "Google"],Space,Str "search",Space,Str "engine"] ("http://google.com","")]
+,Para [Link [Str "http://johnmacfarlane.net/pandoc/"] ("http://johnmacfarlane.net/pandoc/","")]
+,Para [Link [Str "http://google.com"] ("http://google.com",""),Space,Link [Str "http://yahoo.com"] ("http://yahoo.com","")]
+,Para [Link [Str "email",Space,Str "me"] ("mailto:info@example.org","")]
+,Para [Str "http://google.com"]
+,Para [Str "http://google.com"]
+,Para [Str "http://google.com"]
+,Para [Str "info@example.org"]
+,Para [Str "info@example.org"]
+,Para [Str "info@example.org"]
+,Header 1 ("lists",[],[]) [Str "lists"]
+,BulletList
+ [[Plain [Str "Start",Space,Str "each",Space,Str "line"]]
+ ,[Plain [Str "with",Space,Str "an",Space,Str "asterisk",Space,Str "(*)."]
+ ,BulletList
+ [[Plain [Str "More",Space,Str "asterisks",Space,Str "gives",Space,Str "deeper"]
+ ,BulletList
+ [[Plain [Str "and",Space,Str "deeper",Space,Str "levels."]]]]]]
+ ,[Plain [Str "Line",Space,Str "breaks",LineBreak,Str "don't",Space,Str "break",Space,Str "levels."]]
+ ,[Plain [Str "Continuations",Space,Str "are",Space,Str "also",Space,Str "possible"]
+ ,BulletList
+ [[Plain [Str "and",Space,Str "do",Space,Str "not",Space,Str "break",Space,Str "the",Space,Str "list",Space,Str "flow"]]]]
+ ,[Plain [Str "Level",Space,Str "one"]]]
+,Para [Str "Any",Space,Str "other",Space,Str "start",Space,Str "ends",Space,Str "the",Space,Str "list."]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "Start",Space,Str "each",Space,Str "line"]]
+ ,[Plain [Str "with",Space,Str "a",Space,Str "number",Space,Str "(1.)."]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "More",Space,Str "number",Space,Str "signs",Space,Str "gives",Space,Str "deeper"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "and",Space,Str "deeper"]]
+ ,[Plain [Str "levels."]]]]]]
+ ,[Plain [Str "Line",Space,Str "breaks",LineBreak,Str "don't",Space,Str "break",Space,Str "levels."]]
+ ,[Plain [Str "Blank",Space,Str "lines"]]]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "end",Space,Str "the",Space,Str "list",Space,Str "and",Space,Str "start",Space,Str "another."]]]
+,Para [Str "Any",Space,Str "other",Space,Str "start",Space,Str "also",Space,Str "ends",Space,Str "the",Space,Str "list."]
+,DefinitionList
+ [([Str "item",Space,Str "1"],
+ [[Plain [Str "definition",Space,Str "1"]]])
+ ,([Str "item",Space,Str "2"],
+ [[Plain [Str "definition",Space,Str "2-1",Space,Str "definition",Space,Str "2-2"]]])
+ ,([Str "item",Space,Emph [Str "3"]],
+ [[Plain [Str "definition",Space,Emph [Str "3"]]]])]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "one"]]
+ ,[Plain [Str "two"]
+ ,BulletList
+ [[Plain [Str "two",Space,Str "point",Space,Str "one"]]
+ ,[Plain [Str "two",Space,Str "point",Space,Str "two"]]]]
+ ,[Plain [Str "three"]
+ ,DefinitionList
+ [([Str "three",Space,Str "item",Space,Str "one"],
+ [[Plain [Str "three",Space,Str "def",Space,Str "one"]]])]]
+ ,[Plain [Str "four"]
+ ,DefinitionList
+ [([Str "four",Space,Str "def",Space,Str "one"],
+ [[Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "continuation"]]])]]
+ ,[Plain [Str "five"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "five",Space,Str "sub",Space,Str "1"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "five",Space,Str "sub",Space,Str "1",Space,Str "sub",Space,Str "1"]]]]
+ ,[Plain [Str "five",Space,Str "sub",Space,Str "2"]]]]]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "other"]
+ ,OrderedList (1,UpperRoman,DefaultDelim)
+ [[Plain [Str "list"]]
+ ,[Plain [Str "styles"]]]]
+ ,[Plain [Str "are"]
+ ,OrderedList (1,LowerRoman,DefaultDelim)
+ [[Plain [Str "also"]]
+ ,[Plain [Str "possible"]]]]
+ ,[Plain [Str "all"]
+ ,OrderedList (1,LowerAlpha,DefaultDelim)
+ [[Plain [Str "the"]]
+ ,[Plain [Str "different"]]
+ ,[Plain [Str "styles"]]]]
+ ,[Plain [Str "are"]
+ ,OrderedList (1,UpperAlpha,DefaultDelim)
+ [[Plain [Str "implemented"]]
+ ,[Plain [Str "and"]]
+ ,[Plain [Str "supported"]]]]]
+,Header 1 ("tables",[],[]) [Str "tables"]
+,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
+ [[]
+ ,[]]
+ [[[Plain [Str "Orange"]]
+ ,[Plain [Str "Apple"]]]
+ ,[[Plain [Str "Bread"]]
+ ,[Plain [Str "Pie"]]]
+ ,[[Plain [Str "Butter"]]
+ ,[Plain [Str "Ice",Space,Str "cream"]]]]
+,Table [] [AlignLeft,AlignLeft] [0.0,0.0]
+ [[Plain [Str "Orange"]]
+ ,[Plain [Str "Apple"]]]
+ [[[Plain [Str "Bread"]]
+ ,[Plain [Str "Pie"]]]
+ ,[[Plain [Strong [Str "Butter"]]]
+ ,[Plain [Str "Ice",Space,Str "cream"]]]]
+,Table [] [AlignLeft,AlignLeft] [0.0,0.0]
+ [[Plain [Str "Orange"]]
+ ,[Plain [Str "Apple"]]]
+ [[[Plain [Str "Bread",LineBreak,LineBreak,Str "and",Space,Str "cheese"]]
+ ,[Plain [Str "Pie",LineBreak,LineBreak,Strong [Str "apple"],Space,Str "and",Space,Emph [Str "carrot"]]]]]
+,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
+ [[]
+ ,[]
+ ,[]]
+ [[[Plain [Str "Orange"]]
+ ,[Plain [Str "Apple"]]
+ ,[Plain [Str "more"]]]
+ ,[[Plain [Str "Bread"]]
+ ,[Plain [Str "Pie"]]
+ ,[Plain [Str "more"]]]
+ ,[[Plain [Str "Butter"]]
+ ,[Plain [Str "Ice",Space,Str "cream"]]
+ ,[Plain [Str "and",Space,Str "more"]]]]
+,Header 1 ("macros",[],[]) [Str "macros"]
+,Para [Span ("",["twiki-macro","TEST"],[]) []]
+,Para [Span ("",["twiki-macro","TEST"],[]) [Str ""]]
+,Para [Span ("",["twiki-macro","TEST"],[]) [Str "content with spaces"]]
+,Para [Span ("",["twiki-macro","TEST"],[]) [Str "content with spaces"]]
+,Para [Span ("",["twiki-macro","TEST"],[("ARG1","test")]) [Str "content with spaces"]]
+,Para [Span ("",["twiki-macro","TEST"],[]) [Str "content with spaces ARG1=test"]]
+,Para [Span ("",["twiki-macro","TEST"],[("ARG1","test")]) [Str "content with spaces"]]
+,Para [Span ("",["twiki-macro","TEST"],[("ARG1","test"),("ARG2","test2")]) [Str ""]]
+,Para [Span ("",["twiki-macro","TEST"],[("ARG1","test"),("ARG2","test2")]) [Str ""]]
+,Para [Span ("",["twiki-macro","TEST"],[("ARG1","test"),("ARG2","test2")]) [Str "multiline\ndoes also work"]]]
diff --git a/tests/twiki-reader.twiki b/tests/twiki-reader.twiki
new file mode 100644
index 000000000..51828ef80
--- /dev/null
+++ b/tests/twiki-reader.twiki
@@ -0,0 +1,221 @@
+---+ header
+
+---++ header level two
+
+---+++ header level 3
+
+---++++ header _level_ four
+
+---+++++ header level 5
+
+---++++++ header level 6
+
+---+++++++ not a header
+
+ --++ not a header
+
+---+ emph and strong
+
+_emph_ *strong*
+
+__strong and emph__
+
+*<i>emph inside</i> strong*
+
+*strong with <i>emph</i>*
+
+_<b>strong inside</b> emph_
+
+---+ horizontal rule
+
+top
+---
+bottom
+
+---
+
+---+ nop
+
+<nop>_not emph_
+
+---+ entities
+
+hi & low
+
+hi &amp; low
+
+G&ouml;del
+
+&#777;&#xAAA;
+
+---+ comments
+
+inline <!-- secret --> comment
+
+<!-- secret -->
+
+between blocks
+
+ <!-- secret -->
+
+---+ linebreaks
+
+hi%BR%there
+
+hi%BR%
+there
+
+---+ inline code
+
+<code>*→*</code> =typed= <code class="haskell">>>=</code>
+
+---+ code blocks
+
+<verbatim>
+case xs of
+ (_:_) -> reverse xs
+ [] -> ['*']
+</verbatim>
+
+<verbatim class="haskell">
+case xs of
+ (_:_) -> reverse xs
+ [] -> ['*']
+</verbatim>
+
+---+ block quotes
+
+Regular paragraph
+<blockquote>
+This is a block quote.
+
+With two paragraphs.
+</blockquote>
+Nother paragraph.
+
+---+ external links
+
+[[http://google.com][<i>Google</i> search engine]]
+
+http://johnmacfarlane.net/pandoc/
+
+[[http://google.com]] [[http://yahoo.com]]
+
+[[mailto:info@example.org][email me]]
+
+!http://google.com
+
+<nop>http://google.com
+
+<noautolink>
+http://google.com
+</noautolink>
+
+!info@example.org
+
+<nop>info@example.org
+
+<noautolink>
+info@example.org
+</noautolink>
+
+---+ lists
+
+ * Start each line
+ * with an asterisk (*).
+ * More asterisks gives deeper
+ * and deeper levels.
+ * Line breaks%BR%don't break levels.
+ * Continuations
+ are also possible
+ * and do not break the list flow
+ * Level one
+Any other start ends the list.
+
+ 1. Start each line
+ 1. with a number (1.).
+ 1. More number signs gives deeper
+ 1. and deeper
+ 1. levels.
+ 1. Line breaks%BR%don't break levels.
+ 1. Blank lines
+
+ 1. end the list and start another.
+Any other start also
+ends the list.
+
+ $ item 1: definition 1
+ $ item 2: definition 2-1
+ definition 2-2
+ $ item _3_: definition _3_
+
+ 1. one
+ 1. two
+ * two point one
+ * two point two
+ 1. three
+ $ three item one: three def one
+ 1. four
+ $ four def one: this
+ is a continuation
+ 1. five
+ 1. five sub 1
+ 1. five sub 1 sub 1
+ 1. five sub 2
+
+ 1. other
+ I. list
+ I. styles
+ 1. are
+ i. also
+ i. possible
+ 1. all
+ a. the
+ a. different
+ a. styles
+ 1. are
+ A. implemented
+ A. and
+ A. supported
+
+---+ tables
+
+|Orange|Apple|
+|Bread|Pie|
+|Butter|Ice cream|
+
+|*Orange*|*Apple*|
+|Bread|Pie|
+|*Butter*|Ice cream|
+
+|*Orange*|*Apple*|
+|Bread%BR%%BR%and cheese|Pie%BR%%BR%*apple* and <i>carrot</i>|
+
+| Orange | Apple | more |
+| Bread | Pie | more |
+| Butter | Ice cream | and more |
+
+---+ macros
+
+%TEST%
+
+%TEST{}%
+
+%TEST{content with spaces}%
+
+%TEST{"content with spaces"}%
+
+%TEST{"content with spaces" ARG1="test"}%
+
+%TEST{content with spaces ARG1=test}%
+
+%TEST{ARG1=test content with spaces}%
+
+%TEST{ARG1=test ARG2=test2}%
+
+%TEST{ARG1="test" ARG2="test2"}%
+
+%TEST{ARG1="test"
+ARG2="test2"
+multiline
+does also work}%
diff --git a/tests/writer.asciidoc b/tests/writer.asciidoc
index 4b063fe68..aebc529f0 100644
--- a/tests/writer.asciidoc
+++ b/tests/writer.asciidoc
@@ -375,15 +375,19 @@ HTML Blocks
Simple block on one line:
foo
+
And nested without indentation:
foo
bar
+
Interpreted markdown in a table:
This is _emphasized_
+
And this is *strong*
+
Here’s a simple block:
foo
@@ -405,6 +409,7 @@ As should this:
Now, nested:
foo
+
This should just be an HTML comment:
Multiline:
@@ -485,7 +490,7 @@ Ellipses…and…and….
LaTeX
-----
-*
+*
* latexmath:[$2+2=4$]
* latexmath:[$x \in y$]
* latexmath:[$\alpha \wedge \omega$]
diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki
index 704e79b87..2c3c9b1b5 100644
--- a/tests/writer.dokuwiki
+++ b/tests/writer.dokuwiki
@@ -36,7 +36,8 @@ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Beca
Here’s one with a bullet. * criminey.
-There should be a hard line break\\ here.
+There should be a hard line break\\
+here.
----
@@ -268,7 +269,8 @@ Multiple blocks with italics:
<HTML><dt></HTML>//orange//<HTML></dt></HTML>
<HTML><dd></HTML><HTML><p></HTML>orange fruit<HTML></p></HTML>
<code>{ orange code block }</code>
-> <HTML><p></HTML>orange block quote<HTML></p></HTML><HTML></dd></HTML><HTML></dl></HTML>
+> <HTML><p></HTML>orange block quote<HTML></p></HTML>
+<HTML></dd></HTML><HTML></dl></HTML>
Multiple definitions, tight:
@@ -611,7 +613,7 @@ If you want, you can indent every line, but you can also be lazy and just indent
))
> Notes can go in quotes.((In quote.
-))
+> ))
- And in list items.((In list.))
diff --git a/tests/writer.fb2 b/tests/writer.fb2
index ce00cbef3..8cc271deb 100644
--- a/tests/writer.fb2
+++ b/tests/writer.fb2
@@ -1,2 +1,2 @@
<?xml version="1.0" encoding="UTF-8"?>
-<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info><book-title>Pandoc Test Suite</book-title><author><first-name>John</first-name><last-name>MacFarlane</last-name></author><author><nickname>Anonymous</nickname></author><date>July 17, 2006</date></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p>Pandoc Test Suite</p></title><annotation><p>John MacFarlane</p><p>Anonymous</p><p>July 17, 2006</p></annotation><section><p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Headers</p></title><section><title><p>Level 2 with an embedded link &lt;/url&gt;</p></title><section><title><p>Level 3 with emphasis</p></title><section><title><p>Level 4</p></title><section><title><p>Level 5</p></title></section></section></section></section></section><section><title><p>Level 1</p></title><section><title><p>Level 2 with emphasis</p></title><section><title><p>Level 3</p></title><p>with no blank line</p></section></section><section><title><p>Level 2</p></title><p>with no blank line</p><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Paragraphs</p></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<empty-line />here.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Block Quotes</p></title><p>E-mail style:</p><cite><p>This is a block quote. It is pretty short.</p></cite><cite><p>Code in a block quote:</p><empty-line /><p><code>sub status {</code></p><p><code> print &quot;working&quot;;</code></p><p><code>}</code></p><empty-line /><p>A list:</p><p> 1. item one</p><p> 2. item two</p><p>Nested block quotes:</p><cite><p>nested</p></cite><cite><p>nested</p></cite></cite><p>This should not be a block quote: 2 &gt; 1.</p><p>And a following paragraph.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Code Blocks</p></title><p>Code:</p><empty-line /><p><code>---- (should be four hyphens)</code></p><p><code></code></p><p><code>sub status {</code></p><p><code> print &quot;working&quot;;</code></p><p><code>}</code></p><p><code></code></p><p><code>this code block is indented by one tab</code></p><empty-line /><p>And:</p><empty-line /><p><code> this code block is indented by two tabs</code></p><p><code></code></p><p><code>These should not be escaped: \$ \\ \&gt; \[ \{</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Lists</p></title><section><title><p>Unordered</p></title><p>Asterisks tight:</p><p>• asterisk 1</p><p>• asterisk 2</p><p>• asterisk 3</p><p>Asterisks loose:</p><p>• asterisk 1<empty-line /></p><p>• asterisk 2<empty-line /></p><p>• asterisk 3<empty-line /></p><p>Pluses tight:</p><p>• Plus 1</p><p>• Plus 2</p><p>• Plus 3</p><p>Pluses loose:</p><p>• Plus 1<empty-line /></p><p>• Plus 2<empty-line /></p><p>• Plus 3<empty-line /></p><p>Minuses tight:</p><p>• Minus 1</p><p>• Minus 2</p><p>• Minus 3</p><p>Minuses loose:</p><p>• Minus 1<empty-line /></p><p>• Minus 2<empty-line /></p><p>• Minus 3<empty-line /></p></section><section><title><p>Ordered</p></title><p>Tight:</p><p> 1. First</p><p> 2. Second</p><p> 3. Third</p><p>and:</p><p> 1. One</p><p> 2. Two</p><p> 3. Three</p><p>Loose using tabs:</p><p> 1. First<empty-line /></p><p> 2. Second<empty-line /></p><p> 3. Third<empty-line /></p><p>and using spaces:</p><p> 1. One<empty-line /></p><p> 2. Two<empty-line /></p><p> 3. Three<empty-line /></p><p>Multiple paragraphs:</p><p> 1. Item 1, graf one.<empty-line />Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.<empty-line /></p><p> 2. Item 2.<empty-line /></p><p> 3. Item 3.<empty-line /></p></section><section><title><p>Nested</p></title><p>• Tab<p>◦ Tab<p>* Tab</p></p></p><p>Here’s another:</p><p> 1. First</p><p> 2. Second:<p>   • Fee</p><p>   • Fie</p><p>   • Foe</p></p><p> 3. Third</p><p>Same thing but with paragraphs:</p><p> 1. First<empty-line /></p><p> 2. Second:<empty-line /><p>   • Fee</p><p>   • Fie</p><p>   • Foe</p></p><p> 3. Third<empty-line /></p></section><section><title><p>Tabs and spaces</p></title><p>• this is a list item indented with tabs<empty-line /></p><p>• this is a list item indented with spaces<empty-line /><p>◦ this is an example list item indented with tabs<empty-line /></p><p>◦ this is an example list item indented with spaces<empty-line /></p></p></section><section><title><p>Fancy list markers</p></title><p> (2) begins with 2</p><p> (3) and now 3<empty-line />with a continuation<empty-line /><p> (3) iv. sublist with roman numerals, starting with 4</p><p> (3) v. more items<p> (3) v. (A) a subsublist</p><p> (3) v. (B) a subsublist</p></p></p><p>Nesting:</p><p> A. Upper Alpha<p> A. I. Upper Roman.<p> A. I. (6) Decimal start with 6<p> A. I. (6) c) Lower alpha with paren</p></p></p></p><p>Autonumbering:</p><p> 1. Autonumber.</p><p> 2. More.<p> 2. 1. Nested.</p></p><p>Should not be a list item:</p><p>M.A. 2007</p><p>B. Williams</p><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Definition Lists</p></title><p>Tight using spaces:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Tight using tabs:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Loose:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Multiple blocks with italics:</p><p><strong><emphasis>apple</emphasis></strong></p><p>    red fruit<empty-line />    contains seeds, crisp, pleasant to taste<empty-line /></p><p><strong><emphasis>orange</emphasis></strong></p><p>    orange fruit<empty-line /><empty-line /><p><code>    { orange code block }</code></p><empty-line /><cite><p>    orange block quote</p></cite></p><p>Multiple definitions, tight:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line />    bank<empty-line /></p><p>Multiple definitions, loose:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line />    bank<empty-line /></p><p>Blank line after term, indented marker, alternate markers:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /><p> 1. sublist</p><p> 2. sublist</p></p></section><section><title><p>HTML Blocks</p></title><p>Simple block on one line:</p>foo<p>And nested without indentation:</p><p>foo</p>bar<p>Interpreted markdown in a table:</p><empty-line /><p><code>&lt;table&gt;</code></p><empty-line /><empty-line /><p><code>&lt;tr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;td&gt;</code></p><empty-line />This is <emphasis>emphasized</emphasis><empty-line /><p><code>&lt;/td&gt;</code></p><empty-line /><empty-line /><p><code>&lt;td&gt;</code></p><empty-line />And this is <strong>strong</strong><empty-line /><p><code>&lt;/td&gt;</code></p><empty-line /><empty-line /><p><code>&lt;/tr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;/table&gt;</code></p><empty-line /><empty-line /><p><code>&lt;script type=&quot;text/javascript&quot;&gt;document.write(&#39;This *should not* be interpreted as markdown&#39;);&lt;/script&gt;</code></p><empty-line /><p>Here’s a simple block:</p><p>foo</p><p>This should be a code block, though:</p><empty-line /><p><code>&lt;div&gt;</code></p><p><code> foo</code></p><p><code>&lt;/div&gt;</code></p><empty-line /><p>As should this:</p><empty-line /><p><code>&lt;div&gt;foo&lt;/div&gt;</code></p><empty-line /><p>Now, nested:</p>foo<p>This should just be an HTML comment:</p><empty-line /><p><code>&lt;!-- Comment --&gt;</code></p><empty-line /><p>Multiline:</p><empty-line /><p><code>&lt;!--</code></p><p><code>Blah</code></p><p><code>Blah</code></p><p><code>--&gt;</code></p><empty-line /><empty-line /><p><code>&lt;!--</code></p><p><code> This is another comment.</code></p><p><code>--&gt;</code></p><empty-line /><p>Code block:</p><empty-line /><p><code>&lt;!-- Comment --&gt;</code></p><empty-line /><p>Just plain comment, with trailing spaces on the line:</p><empty-line /><p><code>&lt;!-- foo --&gt;</code></p><empty-line /><p>Code:</p><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><p>Hr’s:</p><empty-line /><p><code>&lt;hr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot; /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot; /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot;&gt;</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Inline Markup</p></title><p>This is <emphasis>emphasized</emphasis>, and so <emphasis>is this</emphasis>.</p><p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p><p>An <emphasis>emphasized link<a l:href="#l1" type="note"><sup>[1]</sup></a></emphasis>.</p><p><strong><emphasis>This is strong and em.</emphasis></strong></p><p>So is <strong><emphasis>this</emphasis></strong> word.</p><p><strong><emphasis>This is strong and em.</emphasis></strong></p><p>So is <strong><emphasis>this</emphasis></strong> word.</p><p>This is code: <code>&gt;</code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code>&lt;html&gt;</code>.</p><p><strikethrough>This is <emphasis>strikeout</emphasis>.</strikethrough></p><p>Superscripts: a<sup>bc</sup>d a<sup><emphasis>hello</emphasis></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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Smart quotes, ellipses, dashes</p></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 ‘<code>code</code>’ and a “quoted link<a l:href="#l2" type="note"><sup>[2]</sup></a>”.</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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>LaTeX</p></title><p>• </p><p>• <code>2+2=4</code></p><p>• <code>x \in y</code></p><p>• <code>\alpha \wedge \omega</code></p><p>• <code>223</code></p><p>• <code>p</code>-Tree</p><p>• Here’s some display math: <code>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</code></p><p>• Here’s one that has a line break in it: <code>\alpha + \omega \times x^2</code>.</p><p>These shouldn’t be math:</p><p>• To get the famous equation, write <code>$e = mc^2$</code>.</p><p>• $22,000 is a <emphasis>lot</emphasis> of money. So is $34,000. (It worked if “lot” is emphasized.)</p><p>• Shoes ($20) and socks ($5).</p><p>• Escaped <code>$</code>: $73 <emphasis>this should be emphasized</emphasis> 23$.</p><p>Here’s a LaTeX table:</p><empty-line /><p><code>\begin{tabular}{|l|l|}\hline</code></p><p><code>Animal &amp; Number \\ \hline</code></p><p><code>Dog &amp; 2 \\</code></p><p><code>Cat &amp; 1 \\ \hline</code></p><p><code>\end{tabular}</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Special Characters</p></title><p>Here is some unicode:</p><p>• I hat: Î</p><p>• o umlaut: ö</p><p>• section: §</p><p>• set membership: ∈</p><p>• copyright: ©</p><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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Links</p></title><section><title><p>Explicit</p></title><p>Just a URL<a l:href="#l3" type="note"><sup>[3]</sup></a>.</p><p>URL and title<a l:href="#l4" type="note"><sup>[4]</sup></a>.</p><p>URL and title<a l:href="#l5" type="note"><sup>[5]</sup></a>.</p><p>URL and title<a l:href="#l6" type="note"><sup>[6]</sup></a>.</p><p>URL and title<a l:href="#l7" type="note"><sup>[7]</sup></a></p><p>URL and title<a l:href="#l8" type="note"><sup>[8]</sup></a></p><p>with_underscore<a l:href="#l9" type="note"><sup>[9]</sup></a></p><p>Email link<a l:href="#l10" type="note"><sup>[10]</sup></a></p><p>Empty<a l:href="#l11" type="note"><sup>[11]</sup></a>.</p></section><section><title><p>Reference</p></title><p>Foo bar<a l:href="#l12" type="note"><sup>[12]</sup></a>.</p><p>Foo bar<a l:href="#l13" type="note"><sup>[13]</sup></a>.</p><p>Foo bar<a l:href="#l14" type="note"><sup>[14]</sup></a>.</p><p>With embedded [brackets]<a l:href="#l15" type="note"><sup>[15]</sup></a>.</p><p>b<a l:href="#l16" type="note"><sup>[16]</sup></a> by itself should be a link.</p><p>Indented once<a l:href="#l17" type="note"><sup>[17]</sup></a>.</p><p>Indented twice<a l:href="#l18" type="note"><sup>[18]</sup></a>.</p><p>Indented thrice<a l:href="#l19" type="note"><sup>[19]</sup></a>.</p><p>This should [not][] be a link.</p><empty-line /><p><code>[not]: /url</code></p><empty-line /><p>Foo bar<a l:href="#l20" type="note"><sup>[20]</sup></a>.</p><p>Foo biz<a l:href="#l21" type="note"><sup>[21]</sup></a>.</p></section><section><title><p>With ampersands</p></title><p>Here’s a link with an ampersand in the URL<a l:href="#l22" type="note"><sup>[22]</sup></a>.</p><p>Here’s a link with an amersand in the link text: AT&amp;T<a l:href="#l23" type="note"><sup>[23]</sup></a>.</p><p>Here’s an inline link<a l:href="#l24" type="note"><sup>[24]</sup></a>.</p><p>Here’s an inline link in pointy braces<a l:href="#l25" type="note"><sup>[25]</sup></a>.</p></section><section><title><p>Autolinks</p></title><p>With an ampersand: http://example.com/?foo=1&amp;bar=2<a l:href="#l26" type="note"><sup>[26]</sup></a></p><p>• In a list?</p><p>• http://example.com/<a l:href="#l27" type="note"><sup>[27]</sup></a></p><p>• It should.</p><p>An e-mail address: nobody@nowhere.net<a l:href="#l28" type="note"><sup>[28]</sup></a></p><cite><p>Blockquoted: http://example.com/<a l:href="#l29" type="note"><sup>[29]</sup></a></p></cite><p>Auto-links should not occur here: <code>&lt;http://example.com/&gt;</code></p><empty-line /><p><code>or here: &lt;http://example.com/&gt;</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Images</p></title><p>From “Voyage dans la Lune” by Georges Melies (1902):</p><image l:href="#image1" l:type="imageType" alt="lalune" title="Voyage dans la Lune" /><p>Here is a movie <image l:href="#image2" l:type="inlineImageType" alt="movie" /> icon.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Footnotes</p></title><p>Here is a footnote reference,<a l:href="#n30" type="note"><sup>[30]</sup></a> and another.<a l:href="#n31" type="note"><sup>[31]</sup></a> This should <emphasis>not</emphasis> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a l:href="#n32" type="note"><sup>[32]</sup></a></p><cite><p>Notes can go in quotes.<a l:href="#n33" type="note"><sup>[33]</sup></a></p></cite><p> 1. And in list items.<a l:href="#n34" type="note"><sup>[34]</sup></a></p><p>This paragraph should not be part of the note, as it is not indented.</p></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>/url</code></p></section><section id="l2"><title><p>2</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l3"><title><p>3</p></title><p><code>/url/</code></p></section><section id="l4"><title><p>4</p></title><p>title: <code>/url/</code></p></section><section id="l5"><title><p>5</p></title><p>title preceded by two spaces: <code>/url/</code></p></section><section id="l6"><title><p>6</p></title><p>title preceded by a tab: <code>/url/</code></p></section><section id="l7"><title><p>7</p></title><p>title with &quot;quotes&quot; in it: <code>/url/</code></p></section><section id="l8"><title><p>8</p></title><p>title with single quotes: <code>/url/</code></p></section><section id="l9"><title><p>9</p></title><p><code>/url/with_underscore</code></p></section><section id="l10"><title><p>10</p></title><p><code>mailto:nobody@nowhere.net</code></p></section><section id="l11"><title><p>11</p></title><p><code></code></p></section><section id="l12"><title><p>12</p></title><p><code>/url/</code></p></section><section id="l13"><title><p>13</p></title><p><code>/url/</code></p></section><section id="l14"><title><p>14</p></title><p><code>/url/</code></p></section><section id="l15"><title><p>15</p></title><p><code>/url/</code></p></section><section id="l16"><title><p>16</p></title><p><code>/url/</code></p></section><section id="l17"><title><p>17</p></title><p><code>/url</code></p></section><section id="l18"><title><p>18</p></title><p><code>/url</code></p></section><section id="l19"><title><p>19</p></title><p><code>/url</code></p></section><section id="l20"><title><p>20</p></title><p>Title with &quot;quotes&quot; inside: <code>/url/</code></p></section><section id="l21"><title><p>21</p></title><p>Title with &quot;quote&quot; inside: <code>/url/</code></p></section><section id="l22"><title><p>22</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l23"><title><p>23</p></title><p>AT&amp;T: <code>http://att.com/</code></p></section><section id="l24"><title><p>24</p></title><p><code>/script?foo=1&amp;bar=2</code></p></section><section id="l25"><title><p>25</p></title><p><code>/script?foo=1&amp;bar=2</code></p></section><section id="l26"><title><p>26</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l27"><title><p>27</p></title><p><code>http://example.com/</code></p></section><section id="l28"><title><p>28</p></title><p><code>mailto:nobody@nowhere.net</code></p></section><section id="l29"><title><p>29</p></title><p><code>http://example.com/</code></p></section><section id="n30"><title><p>30</p></title><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></section><section id="n31"><title><p>31</p></title><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><empty-line /><p><code> { &lt;code&gt; }</code></p><empty-line /><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></section><section id="n32"><title><p>32</p></title><p>This is <emphasis>easier</emphasis> to type. Inline notes may contain links<a l:href="#l32" type="note"><sup>[32]</sup></a> and <code>]</code> verbatim characters, as well as [bracketed text].</p></section><section id="n33"><title><p>33</p></title><p>In quote.</p></section><section id="n34"><title><p>34</p></title><p>In list.</p></section></body><binary id="image2" content-type="image/jpeg">/9j/4AAQSkZJRgABAQEASABIAAD//gBQVGhpcyBhcnQgaXMgaW4gdGhlIHB1YmxpYyBkb21haW4uIEtldmluIEh1Z2hlcywga2V2aW5oQGVpdC5jb20sIFNlcHRlbWJlciAxOTk1/9sAQwABAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/9sAQwEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/8AAEQgAFgAUAwEiAAIRAQMRAf/EABoAAQACAwEAAAAAAAAAAAAAAAAICQUGCgf/xAAjEAABBQEAAwABBQAAAAAAAAAGAwQFBwgCAAEJChEVOXa3/8QAFgEBAQEAAAAAAAAAAAAAAAAABggA/8QAJhEBAAECBQEJAAAAAAAAAAAAAQIAAwQFBhEhszE0NlFUcXR1tP/aAAwDAQACEQMRAD8AqQzziPNmpiqnIO1q4H+WkB84MdlzRSuM82/jVw/JCORtRmQz5d2VTy6WmS2eSYx3U/qkSRbgFsqRzH2Is4/mCluXc33vy8xTnJjTNqV/T8LKmkhr8Hq1da2aOvTfIh2CFeNt+GxFBP8AJFdFUbPWh+4FdXV7OtZOMR7mK9lBWNN+JBmMQ5cwmfH8DEFhTZUCRlE6CBq/ds/nBh9oYygeY1L9FnCUnBSN1t+w0l9bNomx1cllsOrL9OCTKtKOIqua6UVjP0dEvTyM7gp/3whbkAD0ScX3r6MLg+C2/XsMhCnJRn/5cVNHyJHiX6JKIFhhqnFeagm9BIgjfcJyNBTZiROBUk6Mp8CJRmT4NWU2MatV7n495DPk/wAbMJSRJOTBDItq0KR5s/nJN7LPW8AJWtYAoKQaDp+u4XShxgXhYcbHoxNTllCwETGQ8ag2jmDVsk8w/wCOp/C/hn+mWV/utpePH+D5wmF39NY6UakjUYR1Dn0YgRM5zQAAAMdfAA4AOAOArjkMNQ3vgm7UKtBR+m9QHFD5tpnDtpy+t2R20gK/OsmFtuDpaL5mVyiT5qdEVAvZci5ch5VoSGKbwlWTBr0RPoZT07av9lHfrXo6yLApWMugKpPM9SV1cDm65s/wkOHZBojoqiM+6GpMSj4FhtayNAUi5H3LfQBG2KWssFoSPuJdKyMLKtpuLi+e3jwFICUg7CSHsNVlYlKdizOTvKdq3KTsG8pQirsAG6vAB5FdhP490U4gfjxi+DedoqO4YftmKdKNulO26jiOv+2Ga/bftVNFXpHtVHrpLpRFJTpP3z77T469++fTx48e4LueE+NY6UKk7UniLP8A7rNf3X6//9k=</binary><binary id="image1" content-type="image/jpeg">/9j/4AAQSkZJRgABAQEAeAB4AAD/2wBDAAYEBQYFBAYGBQYHBwYIChAKCgkJChQODwwQFxQYGBcUFhYaHSUfGhsjHBYWICwgIyYnKSopGR8tMC0oMCUoKSj/2wBDAQcHBwoIChMKChMoGhYaKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCj/wAARCAD6APoDAREAAhEBAxEB/8QAHAAAAAcBAQAAAAAAAAAAAAAAAQIDBAUGBwAI/8QAPhAAAgEDAwIEBAQFAgUFAAMAAQIDAAQRBRIhBjETIkFRB2FxgRQykaEjQlKxwRXwFjNictEIJEPh8SZTgv/EABcBAQEBAQAAAAAAAAAAAAAAAAABAgT/xAAbEQEBAQEAAwEAAAAAAAAAAAAAARECEiExQf/aAAwDAQACEQMRAD8A2t0YoQpwT2qVzMV+N3UHgrDY2eoM0y58VEbgfp9K1yMRmnuJ5h40jyYHGSeKrWE8u2QAApOMdqGCsmT8h70TAJwMAZx249aKBy4c9vTNUC0zDCgmmmG7Ockjkj1PrUTAjcy5XP0ouCgHae4IomOJHhgIc55PHY0Uk5IXLMcUBQ27n96JYO2MYLebHtRBA7BcMx29sdxQJqwZRtIP+BQKpjHHc+xzigNGoAO/k+nPAoAYlee5oBiGeWySO9AJCgY5PHagFCADzj2GaA2N2TkjA/U0HMwbPPeiyBLDfkkj04FCl1cBMgn6URwYFGySR6D2oAeQDAxnHGKAhU4IbGc+tFwnwDj9aK7f8v2oNu+IHxNvJdXmt9EmKWSqArA/mPvxUxMZNe3Ml1dvNcMzSSEsxPOferJhht/OWyAPc0UfdgDcuM8n50AMCykZFARsngcY/egTcbjnJz9O9AB2kZGSQOcUCX8x83bntQCMruJ4B7D1oCyOGzxtJ9M80CAdg5UjFE0aFJrghLeNpHY4IRdx/QUNWCw6D6q1EZttEvirHAZ4ig/U4qw1b9H+CHVN3Mq6hJaWMJ5ZjJ4hA/7R3P3q3ET+pf8Ap/lWNm03XkkkA8qTW+3PHupP9qxopV78G+s7VSV0+OcAn/kzqSfscVvIKzqPTWu6XKE1LSL+Bhz5oDg/cd6lEZzGwLrtPqrA8frUCJfcw9gfegUjZsEAffNADyHt78UAjCjzDJxRcO5Pw3gwCGOVJQp8ZncMGOeNoxwMY96GCbQffFFcUXKjDDt2NEo+N3yyM5z3okKuqJgIzONoJyuMGi4QfGcqSfXBoYHJx659qKIRnnsfUGgJn/poJYoTIGLY+eDzQFlQK2G/KCTmgbspfO0qce/agPGcR7nHf9vnQFfBPlOc88Gg7uucc/M0Bd208YJJweKAYrea4kKQICRGW5IUYUZJ570DYqcknt3FE0VuVyDzj1oamOlulda6puvC0a0eZVIWSbtGn1Y1NNbX0x8ENH0qL8X1NdtqDoNxiQbIh8u+WpqL70Tc6fcxypouiRadbW8hhLFFXcB7Edz+tNFvEZxkmmgShbA9PlUA+Hgg/wBqDgmBkd6ArJuJBGR7VdEdqWgaVqMfh6hp9pcLj/5Ig2KaKJrvwW6S1EFoLaWwmPIe2fAz81ORTRm3UfwI1mzBbRL+K/ReyS/w3x/b+1Wexmev9O6xoE2zWdOubUDszr5T9G7H9auCJj2n3PPrUXTlGBB2kYx96GlQMjJJHuRRXBgDgk8DtRKH8w4OfYA0SUlIMsFXJ4oujHH8ufnRRGOSNoJNAeFC77F2jPucfvQFEqgY3nj/AKaCUY58wwq54AoCzOmVMke9QeRnGR7ZoEIF7pnaTk49KDpSSwQntQJsGKjgggZ9uDQc4OOe1Am2UCkHOR7dqA8t/cSW8MEkrGGEsUTPCk4zj9KJT3pzQtS6m1aPT9Jh8SVxlmJwqL/UfYURuuhfArR7f8NLrF1cXciKDJCrbI2b7c4+9NGtaRptrpdqltYW0VtAn5Y41wBUodvGjqUdQyn0YZqAIreOBFSFFRF7BQAKA1xcRwKplcJuOBn1NAR7y2ikWMzoZnGVQHJNAuQcD3oBKkD2FBy8jnvQFxnjjmg4rxwKBMqCBtPNA3vbCC+tngvYo54HGGSRQQR9DV0Y91n8DNOvFkuOmZmsrk5PgSNuiY98D1X+1XRhWu6DqWgX72er2j2069t/ZvmD2IoGG7jbnj1FFlB224PB+VClN4DYJHyAojmPGCck8cetCAxgjPp6UaAGKtx6+9ATAXO7nFBw8HHLN+goJhBuj2FeAcnmgNazW8U0vjweODGyqpYrsYjytx3x3oGa5LEEjH9XvQGlgmjjMmQq4HBPfPYgevagG5nhe3tkFuInQHxJQTmQntn0wKBKTlAeDx60DSY+U9zn+mgsnQvROr9Y3W2xi8KxV8SXUnCrjvj1Y/IUR6c6A6H03o6wMVgrSXMoBmuX/NIf8Djt/eiLfjJwO9ZBiOfmKDhktzQAzYBLZ8oyaDF+rOptVv8AUjNZL4tjA/lT+kr3wvqTQX/pi3Y+DqFxKXurmFWAaPaVzg4I/b0oHlxqV7penRTXFu93dPLsESYB2k8n7CgnradLq1WaIOFI/K42sPkRQCg3Kcd6Dgp3d6AdrGg5VxnjmgKWB8uQGxnFAUgKuSefSghuqNC0jXbAWGtxQyJKdsYc4YMf6T6GtDzR8S/hnqfSUz3NvuvNILYSZR5o+ezj/Pb6UGfLzyD/AJoFFySQVBHpQDJ5kGByPahAbWxn5+po0OF3D+XPtQJsNwOe+aAuygmMkebgHnHFALHYpJwSeGz2oGpOJWAI49BQEZlYAHkg4oARVOMvtBIJJ7AUAX6xxSOsUgmjViFcKRuHviiVfvhT8NZuqpk1LVFeHRkPlHZpznsP+n50qPS+mWVppdnFa2cEcFtGu1I41ChR8qyHVxK8cLPDD4kgGVQHBNAa0maaBJGTYzDJXOcUCy5JOaA2OMfoaArkheM7vlQNYNOtoWLJCgLHJwo5NApPKLaNpGRQB6j2oGmnRvcyNd3O/DkeErLhkWgklIdCyZOCRzxzQEeRxhdpUnncBkD5UCxXjJ7+tAlctMsIMLohz5mcZAH09aBQYdQwyAeaAuA7MAQxHH0oG1481nbGVInuWU5Kr+bHrgepoKB1u+o6jqlvBH05NevEBPBK0pQR4I4BHZj+1Bb9IS7lsFtNWtYwDGFYB/EXHqpJ7/WtQYx8VfhGbdZtV6Uh8gy81mpyR6koPb5UGKY4YkeYd88fbFAI5AC98c5oQBb+U9+9GnN5RgDgjOPWgAN3yMfWgAqc91/UUD2RSSRg9+49KCR6e0WfX9WS0icRwgb55WOFijH5nP0FBYNRi6dSR7HRNPmu0hOW1GaXaZMdwBwAP3oynE0XRYrFtV02wS4ECj8dp1wcsE7eJEf39qlFZ616ZttPu7Kbp9Zbi0vYzNCcgjHqoHuKsEp8LPh7P1PqjXerxywaXaviRSu1pWH8g+XuflQemIIY7S3SK3hVIo12pGoAAA7AClEL1N1RH0/oTalcwx+IACLaSQKx59Ppmshv0D1jH1ZbTubU27xkkAnKsuSMg/UUFluLlLaJXETyecKAg554zigXiubeRnSKeJ5FOGVXBIPsaBLULoWkIfw3kYsAqIOSTQJMbpm3oqlmwACeF9yfn+1A+Bx34oE5IY5P+YFbnPIzQKAckHuRQCAQOO1AL8r9KDhkZOT9M8UCcrxgAyYJzwD70CT3Itxm8kgi3fly+P7/AOKA9pskhEkZysnOfeg6RH8w3tgjAHtQRZ1uystSg0m5eRJ2UbHceV8fP3oJkBSAVII9xQFdSRwKDDvjN8L/AMSJte6chxcgFrm1QcSf9aj39x61YMH8Q+CkfhqpQncxBDH5H6VRwXJ/Ke1Am2QchuMYOaNFSAVznB9qAm8f10D2RmX8jDHP3oLbebtA6ej0m2LrfX6LcX7IMskf8kf6HcffIoG8yTadZxSTxCK3kRZUwSFfkruIJ78GhiS6Y1OS3160uZJFWO5bwZtxzuQ8bcfPNMZXvo2wsLnQ9R0q/maJNNv5Yo3bjCuMAHPzqA2jdUan0lF0/ZXcElxp9zE+5WVd/DE71IPPB7H2po1bSNXsdYthLp1ykyEcj+ZT817ioITrnoux6vs1gv5JYnjz4ckZ/Ln5etA+6N0BemdBttMina4WEFfFdQpIJJ7D60E5I4Vo9qnnsQO1A3k0yzeTxhCizZJ3qNpz9RQO449igMSxHGW5NAIwBtUAUAMORkfegMhG3jtQD8+fvQGXJz7UAHuRQA5YDI5FB0qCQA5yaCs2/SFit/Jd3AmvJ2bO64ctt5zwD2oLMilVAUDgcAelAJLbhgZz3oGN9HPIYmhtrWRw2czjt7Y+dA+h3mJS67W9gc0AvuLYANADpkZABHY85oPOnxy+Hx06Z+odGjC2jt/7qBRwjH+cY9D6/OrKMebcceHwfaqCYIyDgZ96GhHOFJI4/WjQpXnsaCz9J6fDqGvRC8OLO3Vri5PB/hqMkfc4H3oDT3UupapcXrKS9zISgDdhnAGPbsKC5aLLBHq9p01c6bbagPE23kpJYhmz5IySAAMj6nNGdRnT2lu3V9vaQQrJDHfCMFj5kAfufsMUFogu5H0jrLUYXK+Lq0aRse/lf/8AOKlFfudagvbnQpNQRmtILydCwPdCQcgMOMZFQanPoeiawBd9M6s9jeKPK1vKQp+RFA4septa6fuFtuqbRrmzx5b+BAdo927A+vsflQXfTr2z1O3W5025juIW/mjOR9KAZI914khaRNo4XdwT9KAl3b2+oWpjMoZWbOVfnI9sUCrXUNssUU8w3sQoJH5jQLvwQQC3NAKvuUPtK54waDg23v6UA7weBnNAIOBigMr+hoOjdZQdhBx3waAVG0Z7UBWfAOQSflQChyNxBAxQRutarb6bHALi9trSW4kEcJnGd7ewFA/j8QEK/IA/MBjmgWDDBB7igj9dupLTTbiaHZ4oQ7A7bQW9ATVgwXSNV6onl8azW6t45pWdxHIxWA/zNtz7A8Glg2S1u7fX+nt0J/H2c4MMhmQoW9GBUjj60g8sfEHpebpDqi4sHLG2Y77eQ486E8fcdvtVFekGW4UfegKVAAKgnFGhuDzxQXbpDTZF6a13UnUqrCOzQ5wGZmXIJ+lE0ppkEK6nJcRWcTW9hA08iKcjcowpye/mxQ0+6VRbC/jvLm48L8LG9y8pIOXxkDnuSTipqHXQMng3es9S3fhn8DbvcZI5Mr/lH700dc3Dad8NtPs4nU6jeXD6nMCwBRF5XOfU8YHrTNJFF1X8RawW1jc4GxTKNrZB385yPkBTFw1stSu7Ni9tPLGSQfK5Aphi8J8UNUm6fn0u72yvJ5fGbuF/39aYYtGgadp9/axXnRetzaXqnhqZI3bEcj4547Ak/X6UxFisPiXe6NMdO65057eQAr+LhUlHHbOPX07UwWXpQ6BqMo1LpgW0sioVI8Qgxk+684qC028M5890Y3kHKbUwF+lA4LDOzu2M4FAOG3DaoI9cntQdJxzQEyR259f/AKoGl5fSQRFo7ZpB/MhYIR9zxQdayyXKb7gqox5Yo2yB9WHc0DPUIWnhWKxkuYFRs5gcKWbPY59KBkx6isVeSGW31JNwHhyOUkA+o8v9qCfjkMo/LJFKqBmRvSgc2swnRyFcYODuXGfpQMtRsLK8vYJL+wjuGiUtHK6hghz6Z7H6UEmCsig84I9RigiruC9t0DaaVmIIHhTOQMeuGwT9qCJ1ywv9T0U29xFFiaVBJGHz5M5ODgYPY/arKJPTtLW1t44i7SKq48w8x+ZPrTRJoipGFQAAdgKgzX47dMJrXSrXkUe6807MykDkp/MP8/aro80FQyZ+tUJ7hvH0x270XQ7KGtXvIk0T4c9P2bIhkvpnvJVfjIxhf7qftRDXpu0/1DpzXltUlkvmWMBI+2zdnn64oYa6yX0XTm0i4jQ3t6wmuV53xov5UPpyeeKyLbpFtZ6Xpmn6TqNq7/ic6pqQRR/DVf8Alq2fTOP0FXBnXU+ox32o3lzeW+JrxlMXHKR9wfbJ/tVWK5f3AnaAjafCTwwcY4BOM/qKKSjA4Dg8j37UHZKkE5P0olSFlcLDdJPbTNBOigjxOVZu3+80Rbbnrq9l0t9I6isRd2rgKpPlZMdyre9An07oupoh1zo2+lea2fMlr+WZFx7ZwwqWDVug/ihDq7R6b1EPwmpMNokPlVj8xng1BqEUe1EAJOMDOc5oDSxq6YYeuaAJF4oCBUQ7mJ45zQHYB14wR86AVjBXyjge1AEcRTHlA9hQE8kbgEohJ5yQM0ETHNqMOr3IZQ9tIMQyEjKt7D3FBLqywRPJKTuxlj3zQI3Ut14e+yhWRj28Q7RjH60EfpF3rU/jLqFrHbS4/hqpJXH19aCRa8jgiVr1xGwXzYyf99qA9tc29/aRXFnKs1vINyOO2KByoxwe9AYocHGKBvdwLcWzxSLuR1KuD6gjBoPHXWujt071Nf6YSSkUnkJ4yp5H7f2rQgWAA3Y+1An4j/1t+tBrHxKuYS+gx24LRx6ZFtI/lz60FY0+/v8ASphNpd68EpXY5AGNvzFF1YOirZbzVrvX9dkNxZWH8eeaY5Lyj8qj7kcVlETqOqXd/HrPUNzcNE16Tbwxf1JkEgD2AA/etBte9R2Oq2cv+p6XHJfBFjgmjkMaRgAAEqO5o1FWfbgjsR8+9AlI5CgEggeoNAq0iug8uD7g80KKmCcZ7fPmjJzJfT/hWtjJvhOPK/OOe49u9A96X1W90/VrRtNkkSfxQF8I5yScdvX6UGidSLpfVFzcvbRiy6kgZBGysFW7B9T7HHNSjU+o9S1iz0e2uNLmX8RYxJ+KgYeVwVGTn5d6gjug/iU3UOt/6TewQpP59skL5B29x/8AYoNHPB78Ggb2l3bXO78PKsoyVyvIBHBFAoSkbfyhn4GfWgTnmWFN7ybAvc4Jz9hQRdx1dp0S3Dw+JJHbDdPIUZUjX3yRz9Bmrgzbqb4x9Oxho4bB751O5HPkXPsc80wQHT/xrJ1IHUbGKO0kdRiBiAgz+YjnsPpTKN/tLy3vLOK5t5klt5F3LKhyCPemAYLuK5XMDEj1OCP71ArGWLMPT0oIbU7h11u2t49OllWWNm/FIRsjI4AI/egfQ2ktpbww2XgxoDl9wJ49cUCHUGv2GixM13Mkcm0squwUH5/SrgxDW/jFcXOteHb3otrKEEiRISRM3zGc49v1qDT+gfiBpvV7y2unxTxywRhz4ozuHbOR2+9Bmf8A6kNIEWpaZqiooEqtBIR6kHI/atfRjDEt3AKjgVQjug9j+lQWh72e/htTOzyeCnhHPomeMYoJvQum7vVD47K9jpsQBkvZ5NoAHcgUAa7rKamE0Lp9Xh0G1OZZTwZSO8jn9cCsivdS38F9cJDZIY7G2URxKe5x/MT7nNaEKrENwAFPPlosFwS2cd/cc0UlIm3JOeKDo2LH+UA0SjgDk98URzPiJ2449e/NAbS7v8PdpKkpikQ5WQLkqccGgmYNQmXWLeQLG9wVRQVPlcj+Yn3xQa98OviAjz3WjdXSpFdliEuJCNjDtsJ7enepRdel+kdL0rqOTVdIsoYklV1dixO3nunpg9jUCnU3WMeka5b2EUcl3JInmigQs6ZPlJAHY8+vpQP9O1m3nthNo0cTwM2JDwoVj6H5gd6CbhtUiVn8TcXO4ktkZ+We1BAf8Z6fZ2uqXWpyxQrbStGseQzMB2IA961B59+IHXmodXal+HsPFh04HbHCo25+bY/zQWv4f/CCxvII73qC8iuXYb1tYZeF9txHf6U3BatX+DvSl86x6cr2dwjbnEUmcj6Enj6U8hLdJdEX/SmowJp2tTT6Oc+La3HO0442+3NBf1LmRUjjQAfmc+nyHvWQockYyQcY3CgaabaPZxGNnaUFi3mPb6f+KA2q3RstNurnBxDE0mPfCk1YPMemaP1L8RtYN9fJPc2aMUaVmCKg54H0z6VRYendf6Z6T1W56a6j6fgfwJyguhGJmPzbIzjHtSjTn0zSunbi01fSkt9Os5GAmWNCDOGxtXb6HnNZEZ8etOF90DPKFy1rKk3zAzg/3rXI8u7zvOTg4zVoTLDJ81QWDTb2SwuvFgcrkbXwM5H0PFGqsjpd6+kcT61Nc2ieb8OikFc/9PA+WfSjKA1nWBzpFlZ/hLWM4KH8zsPVj6mghN4IyQRk5NGo5BkFmyAfSgVjChdpGO/FAXYpOHLBe/FAQqoBJbA9sUBGxgtgEj/eaCf6DGjt1TZf8RNGumKS7mQZQkDIB+WaMrf8Ub/ovV7V20JIYL62K4khhCLOCcEcAdu9BmCuEQvxvyFUg42+v+/rQaj0zax/EXRY9Nns0t9TtM+BqCKAjEclXA98jn+1Si7Cz6u6O0tLjTrxLu2tQJJrDwcKE/m2M2SfeoLrpupDV9Mh1OytUS2vIN8m4BZQf6T7+vPpj50GfdK9L6rJqk1y1y0elRDKRqdjHHoyDhjx39e9BZr7fagW0j3kul3iETRqHkeF8ZBUjkZIxjtk5rQ86dW6r+O1OcW0UtvaRsY4oWfLKBxz7k/5NA46P6X1rqS6WPS7V9v88rAqi/f3oN46X6C1DSotkus+BIwKl8hn2+3PapROXPT2t20bPY6kJ5UGYmbIfIHGW5z68VBI6DrzzWSrrAjtrwFUbDja5OBlfuaCbluJLeNwIpLiVF3bVXAP0Pv8qBxLO8cYcW7vnuqkAigNFKs8CyxlwG/lcYI+1A31ayF/pt1auSFmiaM/LIxVgwfoO413o3qqfSLyUSwodogAyZVGcbPTPr71aNDvendJ6wtbu7Fi1lezK0bS4VZMjtnFZE0bC5u9Jh0qRAr2yw4uWx59vBI44PegN1tpbap0lqOk2sipLPB4aFsnHbBNOR5A1exFhqFxbeKkngyMhdOxIPcVuhiZFz/zBUEwcKvYnP6fWi0+6chjn6h062uATFLcRrIMnzAsO9EehNR+GvTV3GUh0+O2YsGaWHIf9amjIfib0no3S0VtFY3M000zMzLJtLKvvkenyx96oz0rwNjA8cj2osFLbVAbOc9jRQiXOAwxnj3oBlAxwDj37UDY+vHOQeTQBIdqjcPMfnQwJclWyBgCjJBFeefw4VaVycBUGST2wAKD0L8H9C1rSIILjWLSCytY1lZASVnlL4PI/wD8+vvUo1uwbxI5GkjdVc7isvOBjtj2qBWKFZiQ8CJCB5FHYj5jHFArDbQ20ey3RY1HOAOPsKCH1u61CPSLt9MtlXUHUrbCbJBbPdtvYetXR5T1y2udD6lni1ErJdJLvlK4wWOCePvVgsV/8Sr67UW1vA0NiowIonMe4+7FeT9ARQRmodWa9EYpPBhs1Tygw26rk9xknkn70EjonxZ17TXjAeKTkZ3L+YZ7N8vpSjX+lOpNM6umgkMG3EgBV1DYbG4kewz2NZGkC43CP8MPFBONysMAD50DaHVH8S6N1a+BaxMUjd280pA5wPb296DrXWLK9WNoJdtwybxDKPDcAnHIoJBifTBzzmgaz2UFzPFNNbwvLCcxuyglT7igdRRKg8qAZ5JAAzQEnuYoHiSWQIZW2ID/ADH2H6UERr12BY6hueIQJaO7SK/nHfnHtx3pyPGWoN4jynuCfU963RF+DL/UtQWTkjaWY/8ATnHFGql+j1VerdJY8r+KiJz/ANwoy9C/EjqSbpbRY723RJC8ojIcZ4IJ/wAVkecer9en1+9FzeLCCq4URjgDP7mtLhteadBY2kMczyHUpcO0YxtiUjgH/q9celAiLy1kjCX1ruyMLNGdrj0+h+lE0+t+kNQltJ7yKS3jgiTxUFw/hySp7qp70NV6YEBgWUNjBoaKeAODnHrRoVgDnBP0ozpxZ2f4y5trVeGuJFiBPpk4zQep9C0LTembS30fQbWP8ZsDyTugZgf6ix9fYZpbgmbXSmXULaa6kMzpltzcjJ//AGpaLCY1CDsF74PrUCgHY0HbSx7Z96BGUfxB2xjtQZ11t0Tb6jNfyw2wM18gV5AcBdpzyPnV0Yp1F0o/TEczXjXaTOQYpIk3QlT3B9Rj0zVl0VKbVppImheUSwbsgFfXHc0De0tri/ujFYQSSyfmKopPHqaDV/g9p+padr/gkSRTzKu0kZRlPLYPbOPf2pg9GWzRCMJAFxH5do4wayKX1z/G0CdzqLWRkiaTxQBLudclQvovbv3oMU/4Z67uwnUAt3u1Zw42yhmx3/Ln8v0oN86L1d00i3i1UiGQIocNnEbnkqT2xgiguEbI4DIysp7EHNAZnxQQ/Usksej3EsCl5EUthR5sY52/Mjigr6Qrp3R15LqEcIlmgdpFGAsY2navPJApyPJtwd8rnGBuJz6Gt0MzGSTyf0qCwSKA5ZsAjnn2otTXQYj/AOMNIDqCrXUZwf8AuGDRG6fF6Gyfo6+ub0CR4EPgIScLIeAcfc1keatN0661a+S3sYTPKzAbV9B7/StLrQ/iXp9pYLp8elWsUM11AzXMqt53I7g7j244oiB6W6Tn6j2TeAy2FspTeB+Z+/8AmgtnWlvpdl1Dp1pq07Ja20GFQpuDHHAwPf39KDHriVTKSPOCeBnHHtQGsrG5v5pfwcTOIlMjgEeVfck0XRIreS7uUigRpJXOEVe5PtRE/wBJ9HaxqvUcdhNFJp0lviaSWVcMgzxgdySeBipo9T6O8NppUJ1K4iW5KgSvIyqxb5jPH0paJm1NvKivE6Mp7MpyP1FQLRTwy58F0cjuAckfagOTtO3+Y8igMWCIWbOPlzQNhNBOWEbq5Q+YKc4+tAD7JEZgQfXj0oI/VtIttXsZLW5hRopByCP/ADVlGRa78Erae63aXK1tG3LAncM/Kmh10l8IZdBv4rxtTE0yggJsyoz6/P0po0zSNKEMdo9xGnjxuzkqMAEgjj7GmialjWQMgyCRyQcGoITqHT7q/a30+G2jFmwLSzl8GPBGFA9c5NBPRwJDbpHCipEi4CjtigqfWltqCaG8WhNbxyzOBIs8W8FcY4+dWQQ/wtuZdIGqadrknhy2u2QyOSEZOeRngY+XvTBZZevOmhC8janbqiZ53Zzj2FMFcs+sh1ZqsFrp8UkGkrlpbh+DNzhVX5Z5NQTfXyWUXSV2t+wW3EZ5I4HHt61eYPI0mA5C9snFaoLsPv8AvUEk5JcA8cZG480WnOlXX4PVLO4yQ0cyP244Yf8AiiPUfUump1B0/c2O8xfi4v8AmL3UcGpgw/SujNX0Trj8PpckimOMvHO/kEg9Rjs3PpV0aFq/Qqa1ZJ/qcrverEqNOwGM+uMfemiVtrKbQdMNjp9rvtkhPht6mU5yT8u1BkvXg1qXUtOvddgRY1R3j2YHiMvZSD27CgzSCyuNQ1KK0giL3Mz4VAOc/wDignoNNOnaHeiW8hgkku/Al2+Ziqgn09M0ETp0qpqSmGKOdFcEeLwMfPHag3JLuCRtPmQWsDhNphtVAcn1w3BPFSwDdWGpX1/OYdOtbbSrlQ80szHdn0GR24/c1AbWemdatLbTJdGvJIJypDQwMV3exwOPatSz9Ei/R+txy2mr3evyHV4miWIDhGwwyGA7nGRS2YNZAUBWYDdjGayEvxMYB3nYu4KCfU+woG93c2enWs1xcPFDCp8zEgDPzq4GGgz22saS1zZSZhkdsFePXt86YHWmySeLNDMYikZ4YNlvvUD+VARxQJqgwRQHUAAe2O1AWOFRM8mDlgB37fagb6reXFt4ItLZJnZsuWfaI0Hdjwcn2FAz0nWX1i4u4xY3VpFbv4eZ1x4vGdy/KgkriN2aMRlQoOW3DOR/5qwYr1P1tp2pdS3WnanKkGh24kRl2eaYgcb/AFxnnAqiv9Jno0dRLJPbtdQtkNPIALaMnODsPPpSjbdK0DTbWQXui+Gsco3BU5hPP5gPT7VkU74t6PZHpq/1N5ZZbwrtRnmOwDPOFJwPsK1xR5ybudw788VaC5X2WoJRULSBpAe5PA/aiinAZnHck4A70THq/Qr23/4Y0u4lmCpLBGA7epxjH60Du+WGOBvFlFuWOFcYyCfbPrUojri6k06xX8PFNfBUJ3ltzM3scVBjfVvVXVNit5dapNDZGQGK3shjeAe7YHIwAOT3zVggNTiu+orrR4p7m+upJFR7h3TPhggDaoBwRjnPH5hV0af0xotnoD3l5dWdrY2YjGLhwPEHoef996CC6m0HpuPpk3Wny2s9sJPHJ3AeI2D39T37UGU9QTDULuGPSLPwIyoVIYk2lj6/X70G2/DPp0hVudRuBLcwxhRGkeEjB9M+p96DSLprVHiieaAE+YxHkke4H1qUOIBawL4uAuc8nvj71AwjRtQ1eO78QNp9odyLju/qT8uf70Gb6r8SpLzryy0vp+4NxYSSCEswI2u2Rn3OOD9qC4dVamen9NlaC7tUaIFvCmnHiy4HJXJxnOeDVwed+rOvLnqSyWO4jZSru/kc7ck+30GKosXw2+KmqaDJDY3jR3OmqNoRhtZAP6SP7Ggtmt63qbTJ1XLazJpslwBFblypEOAA7L2OWANS+xrnR2vW3UmjJeWp8wJSRf6WHeoJdSPMCRmgMq8DmgBpNsgUIxBGSccD70DczmS8MDWoe28MN4+f588rj980CktuJZYpFdlKZ4B4OfegQ1hpIrVjbsRMBhBj8x9qsHnX/hm36y1O/u9V1ddPmS6aD8OkQdyxOSe4OMmqLUvwQsYY4Xjv7m4YEEhwFyMY7fXB5pRbvhp0jqfSMV7b6jqZvLGQAwxAEBDk54PuD6VkVb49a5DBpiaNaeF/FIaQDumOwpzMGDEZQZ5+VboR8In1I+9QWDY6gFn7jjHpQhtJEFbAGBnijT0P8H7qPVOh47a42yNaymPBOcDupoykep+m73V7g/8Av2itQowvJIx6j5/OpRjfUWrax051RPY6LqFy8YACkebO4Z7HjNWCY0ToW2utJbqPreW5na4O4R78cehY9+fQVKLX05p1ro97awC4kX8VFmJLeEKdoyfOxJPbHbHYVAz0rqKPWNauri9t1ktJgILYgEiNFJ/Op9STmrBBdeaFCo0y3jt444DI3jLE204Y5DD+9UPPhv0NaRtPq99mSLOy22nOfdh75oNC0vT7m1uJGvGiii3AW8UDbQAeDu9zUohLlhouqap1VciF4I1FtbxSthtobBIPuTn7VBJ2vUth1TYk2ULi9iALwyKQYz6Z9CM0Ft060/DWEcDHe2Mucdye9BFW3SekWt3LPb2cUTsd2UGCG9x7VYMzufhzdX/WmoXj+BPpx3I7XZMmXYckc8EVRKaP8I+nXikLQuxOQSTnBzj6UEjonw90XSrq3S3s7dplJcl1EhGDx396lFx1TQ4NVjaC7UNCU2lAO/8AvNWDCLp9X+E/WgWImXSp2LRq7eSRT3B9iP8AFSjd9P1+21TRodVsMS2rLmTbyUGOePXFQSltcLcW0c1vh4mXcjDswoDLdRm4FvISsgXeTghDzjAPbPyzmgVFxCzuiOC0WN3sM+5oDqySJmNg3rx7UFb60tNUubGJdFdEvhIdryflUFSM49TVgyTQenJemOorf/U4H1Fpp1edAh/hOQTuQ9375JA4q0bnbPBcxxT20wkjKkqYzlT9ayGWu38um2MbLEJ7iRtoUds+/wAgBzQeW/iHqi6j1PdzeL44HkL9txHtWhVUOVyvHNB2F9zQT8hUAhAdp5FCG0mSAzE4HGDRppvwL1bwOpJbEsFiuYyVX3deR98Zoy2ZtRgmjkSRZocEp51K7se3vUow/rfpFE124mVpfD4mk2MWdCc4A+VWCH1281/UmFnpklzPYRFBEG8uGC4yQfcn9alGgaJo95rRsbi53WaxwrHOm7BjYcHnvz/moJaw07pXSI5IW1K0CQnDhpAWB9R796CudY62msTRW+gadI8KnDXMkLLv9MA8HGOKC3dAXF1dRfh75f41moi4G0AdwcfTj7UFhv7RjqMBV5AJFZHkR8FRjIx6CgpXVNjJ1JqNn07p26CztSJLlpIydyj2J+fGaC+afplrazqLa3SKNIggx3IHYUEsBk4wQc4oK11L1z070/M9rql6wuVA3QopLcjNBDwfFboqeSO2W7kQNxuaEhQfnQLt8TuireVoV1UeXnckTFT9DigHRuv+mbu9ZV1W3Nyc4IRlVl9O47/KgtU+s6baw+JcX1umRkAuM/p3oK/1t0rYdX6cqXKESqN8Ug/Mp9P1qwZ702mo9GdUTWJsmOn3EY8CAORGXJAwScjJ5q0bJDNLb6YklxbKsgA3wwndg9sDtWQN3aw3ZKTwLLEQOGORn6ehoG1vYAw3FikRt7JSuH3Hc/GSc5P0oHn4aO2uGuYyiose044wBQIm6F1dwfh5ARs8R8L2BHGfnQHv9PS4PjxrGLtFKxysm4qD3oCxboIIo7e1jhQHzAYUJ8wP8VYM56j1ktaal1BMrS2sAaK1OQDD6eUepY9yfQVR5zv7hrmaSaRtzyHJY0DcE4BPIPb5UBwOO4oJYzFvzEYHAH9XvQhNZN7AEgDOSDRo/wBA1SXRdVtNQgb/AJUgfBHcZ/8AGaGPVlhPbarZ2t5CEeORBKje2RUrI1zYxTBhMinIwcjvUEcugWkO4AMisMEA8N69u3yoERrOhWNxNYy6hapcxAeJHM+D8u9ASLStLlm/EWdpZyxy+Z3RQ3I5B44oJKTT4blFWSNBEOeBg5+goFYbOK1TKhIxnIbGMH50Cpcyo6AMrIcM2OD68Ggb6Lbbllu5Cd88hYBu6rztWglSNkfm4P70Gaat8Rba96w0vp3R2mhufxyi4kO3YyDOV9+f8VYMw+P0cP8Ax4JVuEKzW8bEr5tuMj0+lUZ7Y2X4288GK+towRlZXYqv9uKCQi6YmbT2u11GzaJWKnYxbBB49KCFnhubdiwL+U8OhP60ElpXUFxY6nDdXQF0qYbZKxwT9vWg3npb42aHcmC11C3uLSQjEkpIdQfr3xUondP6x6e6tv7e101hczRzrNtaFiFC/wAxPYHtUF+lj8bYCTgMG59cUC4OBQQOo2eoXepFTeL/AKYQN1sEwWx6Fu+DQLX2kw3Ok3Vjas9qJ48Exd1PHb9KCE6R0G86Ut7mK71KK4gklM7TyKRIBjtjtjj96AOreudJsrMJbXksk8jBCbVdzRjONxBHP/3QQ9x1jcWGkERWWqXdpMPCt7x4wfFOOWPbA+fAqwZr8TJ9Qbp2ymvEjsrSTEVvawyHz45Lv6E4wPqaoyl8g91OKDlYEc8mgKW5PH7UE80f8PPHl7gDFAZkUjawUIQG8w5ouknAUbl9Dg59KK1X4Z9XXFvo8mlRXax3KHfBG8Rk3qe6jHOc54+dMZO7jr/qK8vWtba4tYu38TwvDOMc8N60wPLbrW10PS7pnvrnUtbAKobgBUUk9jg8f/lMC2rydMdRSaRqWoLEbx4UefwxkL2BVvvn9Klgv3Tp0lPxFno6wJ4IVmEOMEHsf2xUD2e4ks7n+NGDaCMu8q8lCMcEfPNA6tW/EwrMybEYZUHnI9Cf/FAzu7G4LXTWs38SRNqhs4Bz3z9KCO6x07UNT6altNMvEs7xkC7nPlI9R2/egwbrDT+r+kupLCeK9nu3KBYGRy+QvdWFWCU6avtA6h1iKDqLRhpmpvkxz2p8JGb3z7k557VRX77TdHteuPBut401CAouyXGcdvmASaC069030brYaay/CwPFwWspRErfUN7UGZX2hWSiY6ZrMc0CvhUlBUk/UcGgiLq2mtG8F54yDwfDfIoGkrRsSZXwOB2zmgsvw06XHVfUcFvI22xQ753Ze4H8v3OBUo9a6XodjpltHbabDHZIhVsQqBuA9DxznFQTQUe5oDYGMnn7UEbpV3JqDyz+BJFbBtsXiDBf/qx6CgDXL42cSRwGM3UzBQrHGFzy32oG2i2kKTSI80lzMow0rqQoyew+3tQO59KtJJRI9rEzgg7igz3z/egZ6paJdGGwW4eBXy7pGeXUdwT6A5qwebPjJrcOr9TvbWZQ2Onr+Gi2nIJHcj7+vyqigOuRk+vtxQAqEk4BU0ABj7j96CzzKxYD0GeM0CQG3OMAjkfOgbSZwzE4PJyfWi6caTdzaffW95akrPFIrLg/tRHpGzs9C6t0W31FrO3Y43MrcbH9c/eloZ6v0JpWoKlrHHBbScSFEHYc5Pz71NDXUoJrK1g0dvw9qsspW3nXaN6KMrHnH5ieSfan0U3Rr1uidaRbiwk8BUSS6naQkjc3ZcHaRnn70wbja6lZX+nw3NvMksM+FXnPJ9DUCeoXj2hSG2t2km7op4U/f/FAvHaNePb3N0jRzRA7VD8Akc9u/FAvcxnawZQ3HYtjJoKfDFAdeub6Vo1dSULIBtTbgYOfU8jNWUVvrm5ih0m1urixhlsI5HJliOwR5/LkkHHJPamjHdQ0HWdemlutN0+YWBYtC0rHDhjwVz3zWgx1n4e9U6QE8XT5Zd//APR5se9XBXbjS9S0zAvbO5tyWKAOhG4/KpQ3ZHXO5JFK98qRUGhfCbph77Uvx91pv463wVjR0LR7s483796WjW7rTrXpHWrSW2YK7lmXTbaIFpCRjjHOOSeeBipaNLtXuIre3R43lnkGXYADZnnmoH6Dkbzn6UDGWe9a/hKG3jsW8riQMJS3svp86B6zgMQmDtGT8qDNb6XUpOoPx72tzOkjFYowOduDwDjj70Gg6Wsq2KNeAJKRuKk52fIn5DvVkENrvW+iaSAsl0txI2Asdud5Yk4A4pgzv4l9ST6JZSXbyyprWpw+FFa5G21gz5icfzH3pgwCSQlh688+tUEwjjngZ7UHAHuWAHpn+1AXj5frQWXOGBZcKSe3c/rQIyAtnI27eBj/ADQIMAuH8vHBB9DQwVpPLjOckEZ/ahi9/Czqj/S9VhtLm6aG1uZFUsT5VOfX5Gpg9GiNJArxsrxsv1BHypYGF7pljeG3kvLZSlqzNGGxhSRjP6GoG1yLUWiWc2nSPA4KJGItyYHYHHarop3wu0jWYNUvzriNBp8ErraRMANxJ/N7nA7ZqDUHgSQLvAbacjI7H3oOuIFuYzGS68jJRyp4+lA0m0yDwGjiTw3bzBwTuDe+TQVbV+mLmW1NtbSok9weZiC2zPLEZ+/FBM6Xo40/TYdL8Jr21G4vJcuCck55HbFWUKQ/h4tR/DTz2o8TK21qmMgKOf8AfpmrokljG1i5BHI57D5VNorut9Lab1LA638W6H8sboNrqQckq3pntV0RWsfD6K7SGC3vTFahQJY2iVmkI9d+Mimie0Hp2DQ7AQacio3JZgqjcT3zxk1KHGldPWtnqMupS5uNTmGGnk5KjGNqf0r8qgmkhVGcquGblm96BDUZZYLGVrdN8+MIvux7UGKTdXdbaRrFvbaxbWN4d58BmwCjHPORycLx2q4LNe9S9TdN6I13qkWmzSXdwBCGlO4hiMKAB2A9ag0WySQwpLLtMjDcQBhVz6CgoHxF17XbnUYunulgsUsu4TTvjIUAEhR+x4qwZwtkOi7651PXJobm4tohHbQhdgecjnaPZeOfeqMy1vWLvWNQlvb+ZpJpWyT2A9gB6Cgjy5AO4A5oAGRgBR39aA7Z8MkFtxPY0AbV9UGfpQWhj5TkBQGxuBoEGG1iQCyHvj1oELgSkK6oRnIBIxzRdJ28Q3+fHiAds96LoH3AF1wCfyijNbF8JviI1rbQ6Pq/iSopxFOx5Uf0n3qUbWQk8II2SRyDPuCDUHMpSIiJQSBwDwKAgTxApnEbyIQ+APyn0+9A5B3AgfmoEWgcb3VlMpGFYjt+negSs7zxH/C3RWO9UElM8SAHG5fl/agNdXcEbJAZ1WadvDQDJO7Gf7c0ED1dqWv2enzw6Rb24nZfJd3EwREHqxyMZHzOKBbT7H8PZWTK5uZ9o3Xm1SzEry5PsT7UFF+JnUezSZ9LttRs2km2m5KSFWXDZI491AyBzVwK6J8T7CRtPjee0tbaGAtdNISdoXgLEo5JJxyfSmC6aF1fo2vELZXDJOxwkMybHYe4HtUFiJWJd8rKqjuTQcZV8SNI0dy43BlGVA+ZoBniE0RU7tp77Tg5zQUv4hNrU2tdNWOhylPEnaS5UHGYlAzn5cn74oHGt6l0z07k6nJC123HhKPFlbPptGTj9q0Kx0XMvU+ty6vqQtpWlZo4LOdGDWsak8Aflycgk+v2qC8a1q8OnaXLPOz2kCIWkZ+CqjgYx6n0xTBkmp9Sabp0KdRyI5vJkaGw08MVKIDw8jA557896QY1q2o3eqXr3N7O8skjnlnzgn5e1UMCGV/MOM0BJFOVwfX0oFtgZTjkg8UBtpOeO1B3hg85FBZXVMM+VJAA2+h96BO4IMJ/p7qvuKBKacmOKB5CYYx5UzgDPfHzoGwD5OApJHAHrQEAk8NWdNpx+XdkA0AIGhkGWOQcgg8UGw/DP4kmwhi07WCTZqAiSbstGc4+pFKNvs5o7q2Sa3kWaJxkOp4NZDOHUh/qL2k8LW78eG7kbZv+0+/yoEZp7fUpX/BXpgvYZTCSRtO7vtwe/vQdY6jeyatPp91FEPw8aSNMoYbi2cADt6Z70DS60KW7luJdV1JniJzBtURG2b0KN7+/vQKSWUWnLLqN3cSLP4ex5Y8jxiPykr23+nzzigpXUPVOu6Vqmmf8UWttb9OXDqkjRnfI3H849uRkDOKC0axLFr+nLB0rrUMM0bqCIGGGX1AH09qsGc9UfBiTV9Vhu9Pu5oPGLNeG6bczN7jHvVEr058Gre3sLeDVrmOdo3LmSFNjEH+XdntQXO51XQOl5YrCKGWa8SMYS3tzMyLjjJHb9alDqz1S5ktJ7nVdLmSVDiOONfEMiE4Xy+h9xUDm11CaTxEOn3VmpHFxKFCr9s5GPmKAus6jb9M6RJf3c88yxpjcxL7uM5OO3HrQVTSupoOuYdZMTSpptriNFtXKXDA/Pjhs9h2xQOJ7Xpnpa2S91WK2swqjbGw3ysfcnuxrQsGmapYvpwvra1FtDL52Mi+Gx49sZoMb+LXV0t+jWl3OYLGTO2zjx4h2nyszHsG4/Sgxt5ZJmEsjl3PB3GgSlyXBxkDnNADseB2PsaA8SoXQyFgmQCV70B5R/EIjYmPJxnvigEKcYDfrQF2/X9aCwqC7l2zwfT/FAJJ5747E5oGTqZArKOfccftQHZWwmOD23Z4NAEkTEBmwR7g5AoG7KSSE5HyFAMTyQsMHa/cEcEc5oL58P+v7rppdryPNAXx+GfsQe7Z9D2/Wg3zSdX0fqzT08F433eYwscOpHt9PcVkQPW632mX9vfWdrbXiRgrIdu2eHIwGD57+nIoKdc/ELVdC0u5afp27SUtta5vJMMzk+UDjzYHtQWDpj4gxXmif/wAitXZkGZzFGW8MehZO+PmM0Fibr/poWQmF6xXA2xmFg59sKRk0C2nQP1KFvdb0vwIUJNtDKcsVP8zD0Jx2oJDTNA0vR5p7qzs44pJOXkUc/SgNfa/pNvbF5L2JgTsCo2WJzjGKA1jcNcxOF/m/I0zbt4+gxgenNA5s7CCxWWYQxpNLgyMiY3nt2oHajcuexAoEL1C1uyFkVHO1ixHb17/KgwT4rdXWep6oul2OpywaTYqVLxDyySDjaM9x6Z+tWDPdB1TW7Wa9sumpGlursqMQRlpXwd3BA4571RcdN0i41G7h/wBSmNxqdkwn1O6u5/4cAXlYgcnngE/pQNvih8S211obHRyYbWInfJG/Ex9MD2+tBmNzcTXTtJcSSSSHH5jngDAH0oEdxbg5A9wKAzPwO+fegSLfLJoFoR5fUfegXOcHGAT8qAM+XaBzQCCwGDuyPlQWJpV37Q5TIweM7u/f9qA9vNYpFML2KaR8YiaJgAh55PvQRvnYoqA+MThcDnPai4PKWQlH3K6tggjnPaiEmz4ZznBPfFAVWG0AZDH1z2HzoE7lhv8AJIHI/mGRQI8AEeuOMGgndN6pu7V4RJLKY4WDLhypXj0oNL6d+MMS4ttetDdQgDNwAPEwPRh2NZGkabrvTXVZiexvba5aI+ILWZQG3Y4IDdvtQScvTdjK8chtFjkQ+VlYgqPXGKA17daV07apJrV9CsZbELTgbu3YY78UEHf9evJ4K9P6JqGoiR1XxjCUjAJ5OT3NBM9YdSWPTenwy3t7bWbSuBunUthfUhRyT+1BA2vXnS/jGdeo9LnIHljeLwSCe5zgmgejrOz1S3kGhazoaXYGAJ5Sw3e38uaCsJfX02rPD1XfXtvcCXdBJGjLbOO+EK88Y7nIoLB1H1Bb6WkN1ddSQ29io/5MZEjzt7DGTjj2FXNGUfEH4wRaxCtnp2kwGGM7llvBvIOO4XOAe/fNMwZbqusalfLBHfzSvFH+SIgKo+igYqiwWfWV30rpp03p6exJnUPJexQnxuR+Ulu2PkKCrT6jcSiTxZnbxCWcFidxPJJ96BBDlQ35fbFAbahBHJIGO+KAIwg5YnB455oDkKcbW7UAOowSMjOORQcCVXPp+9AqDkHcDmgMNpHPcUBTuzQWCJXcFvKR2Y0CMiqjnz4UcH/6oG8gKluwxyAfSjQ6ylEJBJfv37/OiYQMjbjkZXOSP/FEELAEkNn1waBCXdjORnPoc80CZeTb5wQe2BQAm4y7jlhjvQcWO3cW4GB7ZpgGC5a3uUeNyGQ5GCR+45pgt+l/EzqLTgxj1O5Zc4CSOXCj70wOE+Jd/Pq0V7qVvb3bISAWUBhnuc+/2pgvkHx0soLaNIdKkEiqR5yDg47cYpgresfELSNc1n8VrFtAw2ZBiiywwcgeb14x2xTBYNA13ozUo/GOqWVizDc1nf6crIh/7wOf1rOURvVupdE6ncpFeakiSWsZdbjSLfw1Zs+VVyMHA75xWsFDHU0idTJdf65rT28YKpPvHjKp9Bk49qYK/rGpXF/qU9zPdyzyyMSJJAAx9ifnVlwNZ7vxYEh8GAEHO8DDH5H5U0IPK8jHxSzFQAMnOKgJkFwPT6UBlAII5z3zQCjnA5OKBXeuAT9KABMA208DtxQHRhzgUC3KjJx9z2oAP6/L3NAHC8Hg/XNAcNtGe4oEy5yeaCdLk7yx2qQCAO1AmXZSSexHbPNAhJuLJkgjvzRonuAJy2cd8UCbyOi453Dj7GiYTZyVPPl74oYLJIyq68EH3Gf3oYTDEjLbiP1FEDHOUOdgOfXIBFAm77j5Mnng/WgLI5UE8Eg9iO9AnuJbuQx5wOBQFRxuIbOc54PrQK28ws76F722EyI4d4HJUOPb35yKBm8oeQsi4BPbPb71RyYIHmPGRg00GRsbsHIPY0Bg52AEEseBUCQJyOPXtQDtcdvvjtQCQ/GBwKAuXU4PrQBvZE5IGeO1AffjBJ57UBvEO045HagFWAAzktQKIzBeMg0C5kz5mOG/WgMrDJJ7jmgEnIyOccYoA3cEMRj05oC7/wDeBQTduzEoNxwcZGaAJOWfPNAlISVOT60aIQfkj+amgJ3bnnigKeFGPQUCf/x0Smw4V8exogX/AOY3+/SgKxKxeU459KAgJOckntQJkkcgkGgAAFFz/XQEmJaY7jnk96BM9yPQelAf/wCX7UBv/jagGP8AKB6ZoDf00HMfO/0oAH5TQA/5moECSMDPFAvGASMjPP8AigVX+b60BW7/AHoHEJJD55oDd4snv70CsSjCcDmgVAAbgYoGYJ3nk9qBUAYHAoP/2Q==</binary></FictionBook> \ No newline at end of file
+<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info><book-title>Pandoc Test Suite</book-title><author><first-name>John</first-name><last-name>MacFarlane</last-name></author><author><nickname>Anonymous</nickname></author><date>July 17, 2006</date></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p>Pandoc Test Suite</p></title><annotation><p>John MacFarlane</p><p>Anonymous</p><p>July 17, 2006</p></annotation><section><p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Headers</p></title><section><title><p>Level 2 with an embedded link &lt;/url&gt;</p></title><section><title><p>Level 3 with emphasis</p></title><section><title><p>Level 4</p></title><section><title><p>Level 5</p></title></section></section></section></section></section><section><title><p>Level 1</p></title><section><title><p>Level 2 with emphasis</p></title><section><title><p>Level 3</p></title><p>with no blank line</p></section></section><section><title><p>Level 2</p></title><p>with no blank line</p><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Paragraphs</p></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<empty-line />here.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Block Quotes</p></title><p>E-mail style:</p><cite><p>This is a block quote. It is pretty short.</p></cite><cite><p>Code in a block quote:</p><empty-line /><p><code>sub status {</code></p><p><code> print &quot;working&quot;;</code></p><p><code>}</code></p><empty-line /><p>A list:</p><p> 1. item one</p><p> 2. item two</p><p>Nested block quotes:</p><cite><p>nested</p></cite><cite><p>nested</p></cite></cite><p>This should not be a block quote: 2 &gt; 1.</p><p>And a following paragraph.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Code Blocks</p></title><p>Code:</p><empty-line /><p><code>---- (should be four hyphens)</code></p><p><code></code></p><p><code>sub status {</code></p><p><code> print &quot;working&quot;;</code></p><p><code>}</code></p><p><code></code></p><p><code>this code block is indented by one tab</code></p><empty-line /><p>And:</p><empty-line /><p><code> this code block is indented by two tabs</code></p><p><code></code></p><p><code>These should not be escaped: \$ \\ \&gt; \[ \{</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Lists</p></title><section><title><p>Unordered</p></title><p>Asterisks tight:</p><p>• asterisk 1</p><p>• asterisk 2</p><p>• asterisk 3</p><p>Asterisks loose:</p><p>• asterisk 1<empty-line /></p><p>• asterisk 2<empty-line /></p><p>• asterisk 3<empty-line /></p><p>Pluses tight:</p><p>• Plus 1</p><p>• Plus 2</p><p>• Plus 3</p><p>Pluses loose:</p><p>• Plus 1<empty-line /></p><p>• Plus 2<empty-line /></p><p>• Plus 3<empty-line /></p><p>Minuses tight:</p><p>• Minus 1</p><p>• Minus 2</p><p>• Minus 3</p><p>Minuses loose:</p><p>• Minus 1<empty-line /></p><p>• Minus 2<empty-line /></p><p>• Minus 3<empty-line /></p></section><section><title><p>Ordered</p></title><p>Tight:</p><p> 1. First</p><p> 2. Second</p><p> 3. Third</p><p>and:</p><p> 1. One</p><p> 2. Two</p><p> 3. Three</p><p>Loose using tabs:</p><p> 1. First<empty-line /></p><p> 2. Second<empty-line /></p><p> 3. Third<empty-line /></p><p>and using spaces:</p><p> 1. One<empty-line /></p><p> 2. Two<empty-line /></p><p> 3. Three<empty-line /></p><p>Multiple paragraphs:</p><p> 1. Item 1, graf one.<empty-line />Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.<empty-line /></p><p> 2. Item 2.<empty-line /></p><p> 3. Item 3.<empty-line /></p></section><section><title><p>Nested</p></title><p>• Tab<p>◦ Tab<p>* Tab</p></p></p><p>Here’s another:</p><p> 1. First</p><p> 2. Second:<p>   • Fee</p><p>   • Fie</p><p>   • Foe</p></p><p> 3. Third</p><p>Same thing but with paragraphs:</p><p> 1. First<empty-line /></p><p> 2. Second:<empty-line /><p>   • Fee</p><p>   • Fie</p><p>   • Foe</p></p><p> 3. Third<empty-line /></p></section><section><title><p>Tabs and spaces</p></title><p>• this is a list item indented with tabs<empty-line /></p><p>• this is a list item indented with spaces<empty-line /><p>◦ this is an example list item indented with tabs<empty-line /></p><p>◦ this is an example list item indented with spaces<empty-line /></p></p></section><section><title><p>Fancy list markers</p></title><p> (2) begins with 2</p><p> (3) and now 3<empty-line />with a continuation<empty-line /><p> (3) iv. sublist with roman numerals, starting with 4</p><p> (3) v. more items<p> (3) v. (A) a subsublist</p><p> (3) v. (B) a subsublist</p></p></p><p>Nesting:</p><p> A. Upper Alpha<p> A. I. Upper Roman.<p> A. I. (6) Decimal start with 6<p> A. I. (6) c) Lower alpha with paren</p></p></p></p><p>Autonumbering:</p><p> 1. Autonumber.</p><p> 2. More.<p> 2. 1. Nested.</p></p><p>Should not be a list item:</p><p>M.A. 2007</p><p>B. Williams</p><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Definition Lists</p></title><p>Tight using spaces:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Tight using tabs:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Loose:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Multiple blocks with italics:</p><p><strong><emphasis>apple</emphasis></strong></p><p>    red fruit<empty-line />    contains seeds, crisp, pleasant to taste<empty-line /></p><p><strong><emphasis>orange</emphasis></strong></p><p>    orange fruit<empty-line /><empty-line /><p><code>    { orange code block }</code></p><empty-line /><cite><p>    orange block quote</p></cite></p><p>Multiple definitions, tight:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line />    bank<empty-line /></p><p>Multiple definitions, loose:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line />    bank<empty-line /></p><p>Blank line after term, indented marker, alternate markers:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /><p> 1. sublist</p><p> 2. sublist</p></p></section><section><title><p>HTML Blocks</p></title><p>Simple block on one line:</p>foo<p>And nested without indentation:</p><p>foo</p>bar<p>Interpreted markdown in a table:</p><empty-line /><p><code>&lt;table&gt;</code></p><empty-line /><empty-line /><p><code>&lt;tr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;td&gt;</code></p><empty-line />This is <emphasis>emphasized</emphasis><empty-line /><p><code>&lt;/td&gt;</code></p><empty-line /><empty-line /><p><code>&lt;td&gt;</code></p><empty-line />And this is <strong>strong</strong><empty-line /><p><code>&lt;/td&gt;</code></p><empty-line /><empty-line /><p><code>&lt;/tr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;/table&gt;</code></p><empty-line /><empty-line /><p><code>&lt;script type=&quot;text/javascript&quot;&gt;document.write(&#39;This *should not* be interpreted as markdown&#39;);&lt;/script&gt;</code></p><empty-line /><p>Here’s a simple block:</p><p>foo</p><p>This should be a code block, though:</p><empty-line /><p><code>&lt;div&gt;</code></p><p><code> foo</code></p><p><code>&lt;/div&gt;</code></p><empty-line /><p>As should this:</p><empty-line /><p><code>&lt;div&gt;foo&lt;/div&gt;</code></p><empty-line /><p>Now, nested:</p>foo<p>This should just be an HTML comment:</p><empty-line /><p><code>&lt;!-- Comment --&gt;</code></p><empty-line /><p>Multiline:</p><empty-line /><p><code>&lt;!--</code></p><p><code>Blah</code></p><p><code>Blah</code></p><p><code>--&gt;</code></p><empty-line /><empty-line /><p><code>&lt;!--</code></p><p><code> This is another comment.</code></p><p><code>--&gt;</code></p><empty-line /><p>Code block:</p><empty-line /><p><code>&lt;!-- Comment --&gt;</code></p><empty-line /><p>Just plain comment, with trailing spaces on the line:</p><empty-line /><p><code>&lt;!-- foo --&gt;</code></p><empty-line /><p>Code:</p><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><p>Hr’s:</p><empty-line /><p><code>&lt;hr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot; /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot; /&gt;</code></p><empty-line /><empty-line /><p><code>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot;&gt;</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Inline Markup</p></title><p>This is <emphasis>emphasized</emphasis>, and so <emphasis>is this</emphasis>.</p><p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p><p>An <emphasis>emphasized link<a l:href="#l1" type="note"><sup>[1]</sup></a></emphasis>.</p><p><strong><emphasis>This is strong and em.</emphasis></strong></p><p>So is <strong><emphasis>this</emphasis></strong> word.</p><p><strong><emphasis>This is strong and em.</emphasis></strong></p><p>So is <strong><emphasis>this</emphasis></strong> word.</p><p>This is code: <code>&gt;</code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code>&lt;html&gt;</code>.</p><p><strikethrough>This is <emphasis>strikeout</emphasis>.</strikethrough></p><p>Superscripts: a<sup>bc</sup>d a<sup><emphasis>hello</emphasis></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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Smart quotes, ellipses, dashes</p></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 ‘<code>code</code>’ and a “quoted link<a l:href="#l2" type="note"><sup>[2]</sup></a>”.</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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>LaTeX</p></title><p>• </p><p>• <code>2+2=4</code></p><p>• <code>x \in y</code></p><p>• <code>\alpha \wedge \omega</code></p><p>• <code>223</code></p><p>• <code>p</code>-Tree</p><p>• Here’s some display math: <code>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</code></p><p>• Here’s one that has a line break in it: <code>\alpha + \omega \times x^2</code>.</p><p>These shouldn’t be math:</p><p>• To get the famous equation, write <code>$e = mc^2$</code>.</p><p>• $22,000 is a <emphasis>lot</emphasis> of money. So is $34,000. (It worked if “lot” is emphasized.)</p><p>• Shoes ($20) and socks ($5).</p><p>• Escaped <code>$</code>: $73 <emphasis>this should be emphasized</emphasis> 23$.</p><p>Here’s a LaTeX table:</p><empty-line /><p><code>\begin{tabular}{|l|l|}\hline</code></p><p><code>Animal &amp; Number \\ \hline</code></p><p><code>Dog &amp; 2 \\</code></p><p><code>Cat &amp; 1 \\ \hline</code></p><p><code>\end{tabular}</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Special Characters</p></title><p>Here is some unicode:</p><p>• I hat: Î</p><p>• o umlaut: ö</p><p>• section: §</p><p>• set membership: ∈</p><p>• copyright: ©</p><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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Links</p></title><section><title><p>Explicit</p></title><p>Just a URL<a l:href="#l3" type="note"><sup>[3]</sup></a>.</p><p>URL and title<a l:href="#l4" type="note"><sup>[4]</sup></a>.</p><p>URL and title<a l:href="#l5" type="note"><sup>[5]</sup></a>.</p><p>URL and title<a l:href="#l6" type="note"><sup>[6]</sup></a>.</p><p>URL and title<a l:href="#l7" type="note"><sup>[7]</sup></a></p><p>URL and title<a l:href="#l8" type="note"><sup>[8]</sup></a></p><p>with_underscore<a l:href="#l9" type="note"><sup>[9]</sup></a></p><p>Email link<a l:href="#l10" type="note"><sup>[10]</sup></a></p><p>Empty<a l:href="#l11" type="note"><sup>[11]</sup></a>.</p></section><section><title><p>Reference</p></title><p>Foo bar<a l:href="#l12" type="note"><sup>[12]</sup></a>.</p><p>Foo bar<a l:href="#l13" type="note"><sup>[13]</sup></a>.</p><p>Foo bar<a l:href="#l14" type="note"><sup>[14]</sup></a>.</p><p>With embedded [brackets]<a l:href="#l15" type="note"><sup>[15]</sup></a>.</p><p>b<a l:href="#l16" type="note"><sup>[16]</sup></a> by itself should be a link.</p><p>Indented once<a l:href="#l17" type="note"><sup>[17]</sup></a>.</p><p>Indented twice<a l:href="#l18" type="note"><sup>[18]</sup></a>.</p><p>Indented thrice<a l:href="#l19" type="note"><sup>[19]</sup></a>.</p><p>This should [not][] be a link.</p><empty-line /><p><code>[not]: /url</code></p><empty-line /><p>Foo bar<a l:href="#l20" type="note"><sup>[20]</sup></a>.</p><p>Foo biz<a l:href="#l21" type="note"><sup>[21]</sup></a>.</p></section><section><title><p>With ampersands</p></title><p>Here’s a link with an ampersand in the URL<a l:href="#l22" type="note"><sup>[22]</sup></a>.</p><p>Here’s a link with an amersand in the link text: AT&amp;T<a l:href="#l23" type="note"><sup>[23]</sup></a>.</p><p>Here’s an inline link<a l:href="#l24" type="note"><sup>[24]</sup></a>.</p><p>Here’s an inline link in pointy braces<a l:href="#l25" type="note"><sup>[25]</sup></a>.</p></section><section><title><p>Autolinks</p></title><p>With an ampersand: http://example.com/?foo=1&amp;bar=2<a l:href="#l26" type="note"><sup>[26]</sup></a></p><p>• In a list?</p><p>• http://example.com/<a l:href="#l27" type="note"><sup>[27]</sup></a></p><p>• It should.</p><p>An e-mail address: nobody@nowhere.net<a l:href="#l28" type="note"><sup>[28]</sup></a></p><cite><p>Blockquoted: http://example.com/<a l:href="#l29" type="note"><sup>[29]</sup></a></p></cite><p>Auto-links should not occur here: <code>&lt;http://example.com/&gt;</code></p><empty-line /><p><code>or here: &lt;http://example.com/&gt;</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Images</p></title><p>From “Voyage dans la Lune” by Georges Melies (1902):</p><image l:href="#image1" l:type="imageType" alt="lalune" title="Voyage dans la Lune" /><p>Here is a movie <image l:href="#image2" l:type="inlineImageType" alt="movie" /> icon.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Footnotes</p></title><p>Here is a footnote reference,<a l:href="#n30" type="note"><sup>[30]</sup></a> and another.<a l:href="#n31" type="note"><sup>[31]</sup></a> This should <emphasis>not</emphasis> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a l:href="#n32" type="note"><sup>[32]</sup></a></p><cite><p>Notes can go in quotes.<a l:href="#n33" type="note"><sup>[33]</sup></a></p></cite><p> 1. And in list items.<a l:href="#n34" type="note"><sup>[34]</sup></a></p><p>This paragraph should not be part of the note, as it is not indented.</p></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>/url</code></p></section><section id="l2"><title><p>2</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l3"><title><p>3</p></title><p><code>/url/</code></p></section><section id="l4"><title><p>4</p></title><p>title: <code>/url/</code></p></section><section id="l5"><title><p>5</p></title><p>title preceded by two spaces: <code>/url/</code></p></section><section id="l6"><title><p>6</p></title><p>title preceded by a tab: <code>/url/</code></p></section><section id="l7"><title><p>7</p></title><p>title with &quot;quotes&quot; in it: <code>/url/</code></p></section><section id="l8"><title><p>8</p></title><p>title with single quotes: <code>/url/</code></p></section><section id="l9"><title><p>9</p></title><p><code>/url/with_underscore</code></p></section><section id="l10"><title><p>10</p></title><p><code>mailto:nobody@nowhere.net</code></p></section><section id="l11"><title><p>11</p></title><p><code></code></p></section><section id="l12"><title><p>12</p></title><p><code>/url/</code></p></section><section id="l13"><title><p>13</p></title><p><code>/url/</code></p></section><section id="l14"><title><p>14</p></title><p><code>/url/</code></p></section><section id="l15"><title><p>15</p></title><p><code>/url/</code></p></section><section id="l16"><title><p>16</p></title><p><code>/url/</code></p></section><section id="l17"><title><p>17</p></title><p><code>/url</code></p></section><section id="l18"><title><p>18</p></title><p><code>/url</code></p></section><section id="l19"><title><p>19</p></title><p><code>/url</code></p></section><section id="l20"><title><p>20</p></title><p>Title with &quot;quotes&quot; inside: <code>/url/</code></p></section><section id="l21"><title><p>21</p></title><p>Title with &quot;quote&quot; inside: <code>/url/</code></p></section><section id="l22"><title><p>22</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l23"><title><p>23</p></title><p>AT&amp;T: <code>http://att.com/</code></p></section><section id="l24"><title><p>24</p></title><p><code>/script?foo=1&amp;bar=2</code></p></section><section id="l25"><title><p>25</p></title><p><code>/script?foo=1&amp;bar=2</code></p></section><section id="l26"><title><p>26</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l27"><title><p>27</p></title><p><code>http://example.com/</code></p></section><section id="l28"><title><p>28</p></title><p><code>mailto:nobody@nowhere.net</code></p></section><section id="l29"><title><p>29</p></title><p><code>http://example.com/</code></p></section><section id="n30"><title><p>30</p></title><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></section><section id="n31"><title><p>31</p></title><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><empty-line /><p><code> { &lt;code&gt; }</code></p><empty-line /><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></section><section id="n32"><title><p>32</p></title><p>This is <emphasis>easier</emphasis> to type. Inline notes may contain links<a l:href="#l32" type="note"><sup>[32]</sup></a> and <code>]</code> verbatim characters, as well as [bracketed text].</p></section><section id="n33"><title><p>33</p></title><p>In quote.</p></section><section id="n34"><title><p>34</p></title><p>In list.</p></section></body><binary id="image2" content-type="image/jpeg">/9j/4AAQSkZJRgABAQEASABIAAD//gBQVGhpcyBhcnQgaXMgaW4gdGhlIHB1YmxpYyBkb21haW4uIEtldmluIEh1Z2hlcywga2V2aW5oQGVpdC5jb20sIFNlcHRlbWJlciAxOTk1/9sAQwABAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/9sAQwEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/8AAEQgAFgAUAwEiAAIRAQMRAf/EABoAAQACAwEAAAAAAAAAAAAAAAAICQUGCgf/xAAjEAABBQEAAwABBQAAAAAAAAAGAwQFBwgCAAEJChEVOXa3/8QAFgEBAQEAAAAAAAAAAAAAAAAABggA/8QAJhEBAAECBQEJAAAAAAAAAAAAAQIAAwQFBhEhszE0NlFUcXR1tP/aAAwDAQACEQMRAD8AqQzziPNmpiqnIO1q4H+WkB84MdlzRSuM82/jVw/JCORtRmQz5d2VTy6WmS2eSYx3U/qkSRbgFsqRzH2Is4/mCluXc33vy8xTnJjTNqV/T8LKmkhr8Hq1da2aOvTfIh2CFeNt+GxFBP8AJFdFUbPWh+4FdXV7OtZOMR7mK9lBWNN+JBmMQ5cwmfH8DEFhTZUCRlE6CBq/ds/nBh9oYygeY1L9FnCUnBSN1t+w0l9bNomx1cllsOrL9OCTKtKOIqua6UVjP0dEvTyM7gp/3whbkAD0ScX3r6MLg+C2/XsMhCnJRn/5cVNHyJHiX6JKIFhhqnFeagm9BIgjfcJyNBTZiROBUk6Mp8CJRmT4NWU2MatV7n495DPk/wAbMJSRJOTBDItq0KR5s/nJN7LPW8AJWtYAoKQaDp+u4XShxgXhYcbHoxNTllCwETGQ8ag2jmDVsk8w/wCOp/C/hn+mWV/utpePH+D5wmF39NY6UakjUYR1Dn0YgRM5zQAAAMdfAA4AOAOArjkMNQ3vgm7UKtBR+m9QHFD5tpnDtpy+t2R20gK/OsmFtuDpaL5mVyiT5qdEVAvZci5ch5VoSGKbwlWTBr0RPoZT07av9lHfrXo6yLApWMugKpPM9SV1cDm65s/wkOHZBojoqiM+6GpMSj4FhtayNAUi5H3LfQBG2KWssFoSPuJdKyMLKtpuLi+e3jwFICUg7CSHsNVlYlKdizOTvKdq3KTsG8pQirsAG6vAB5FdhP490U4gfjxi+DedoqO4YftmKdKNulO26jiOv+2Ga/bftVNFXpHtVHrpLpRFJTpP3z77T469++fTx48e4LueE+NY6UKk7UniLP8A7rNf3X6//9k=</binary><binary id="image1" content-type="image/jpeg">/9j/4AAQSkZJRgABAQEAeAB4AAD/2wBDAAYEBQYFBAYGBQYHBwYIChAKCgkJChQODwwQFxQYGBcUFhYaHSUfGhsjHBYWICwgIyYnKSopGR8tMC0oMCUoKSj/2wBDAQcHBwoIChMKChMoGhYaKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCj/wAARCAD6APoDAREAAhEBAxEB/8QAHAAAAAcBAQAAAAAAAAAAAAAAAQIDBAUGBwAI/8QAPhAAAgEDAwIEBAQFAgUFAAMAAQIDAAQRBRIhBjETIkFRB2FxgRQykaEjQlKxwRXwFjNictEIJEPh8SZTgv/EABcBAQEBAQAAAAAAAAAAAAAAAAABAgT/xAAbEQEBAQEAAwEAAAAAAAAAAAAAARECEiExQf/aAAwDAQACEQMRAD8A2t0YoQpwT2qVzMV+N3UHgrDY2eoM0y58VEbgfp9K1yMRmnuJ5h40jyYHGSeKrWE8u2QAApOMdqGCsmT8h70TAJwMAZx249aKBy4c9vTNUC0zDCgmmmG7Ockjkj1PrUTAjcy5XP0ouCgHae4IomOJHhgIc55PHY0Uk5IXLMcUBQ27n96JYO2MYLebHtRBA7BcMx29sdxQJqwZRtIP+BQKpjHHc+xzigNGoAO/k+nPAoAYlee5oBiGeWySO9AJCgY5PHagFCADzj2GaA2N2TkjA/U0HMwbPPeiyBLDfkkj04FCl1cBMgn6URwYFGySR6D2oAeQDAxnHGKAhU4IbGc+tFwnwDj9aK7f8v2oNu+IHxNvJdXmt9EmKWSqArA/mPvxUxMZNe3Ml1dvNcMzSSEsxPOferJhht/OWyAPc0UfdgDcuM8n50AMCykZFARsngcY/egTcbjnJz9O9AB2kZGSQOcUCX8x83bntQCMruJ4B7D1oCyOGzxtJ9M80CAdg5UjFE0aFJrghLeNpHY4IRdx/QUNWCw6D6q1EZttEvirHAZ4ig/U4qw1b9H+CHVN3Mq6hJaWMJ5ZjJ4hA/7R3P3q3ET+pf8Ap/lWNm03XkkkA8qTW+3PHupP9qxopV78G+s7VSV0+OcAn/kzqSfscVvIKzqPTWu6XKE1LSL+Bhz5oDg/cd6lEZzGwLrtPqrA8frUCJfcw9gfegUjZsEAffNADyHt78UAjCjzDJxRcO5Pw3gwCGOVJQp8ZncMGOeNoxwMY96GCbQffFFcUXKjDDt2NEo+N3yyM5z3okKuqJgIzONoJyuMGi4QfGcqSfXBoYHJx659qKIRnnsfUGgJn/poJYoTIGLY+eDzQFlQK2G/KCTmgbspfO0qce/agPGcR7nHf9vnQFfBPlOc88Gg7uucc/M0Bd208YJJweKAYrea4kKQICRGW5IUYUZJ570DYqcknt3FE0VuVyDzj1oamOlulda6puvC0a0eZVIWSbtGn1Y1NNbX0x8ENH0qL8X1NdtqDoNxiQbIh8u+WpqL70Tc6fcxypouiRadbW8hhLFFXcB7Edz+tNFvEZxkmmgShbA9PlUA+Hgg/wBqDgmBkd6ArJuJBGR7VdEdqWgaVqMfh6hp9pcLj/5Ig2KaKJrvwW6S1EFoLaWwmPIe2fAz81ORTRm3UfwI1mzBbRL+K/ReyS/w3x/b+1Wexmev9O6xoE2zWdOubUDszr5T9G7H9auCJj2n3PPrUXTlGBB2kYx96GlQMjJJHuRRXBgDgk8DtRKH8w4OfYA0SUlIMsFXJ4oujHH8ufnRRGOSNoJNAeFC77F2jPucfvQFEqgY3nj/AKaCUY58wwq54AoCzOmVMke9QeRnGR7ZoEIF7pnaTk49KDpSSwQntQJsGKjgggZ9uDQc4OOe1Am2UCkHOR7dqA8t/cSW8MEkrGGEsUTPCk4zj9KJT3pzQtS6m1aPT9Jh8SVxlmJwqL/UfYURuuhfArR7f8NLrF1cXciKDJCrbI2b7c4+9NGtaRptrpdqltYW0VtAn5Y41wBUodvGjqUdQyn0YZqAIreOBFSFFRF7BQAKA1xcRwKplcJuOBn1NAR7y2ikWMzoZnGVQHJNAuQcD3oBKkD2FBy8jnvQFxnjjmg4rxwKBMqCBtPNA3vbCC+tngvYo54HGGSRQQR9DV0Y91n8DNOvFkuOmZmsrk5PgSNuiY98D1X+1XRhWu6DqWgX72er2j2069t/ZvmD2IoGG7jbnj1FFlB224PB+VClN4DYJHyAojmPGCck8cetCAxgjPp6UaAGKtx6+9ATAXO7nFBw8HHLN+goJhBuj2FeAcnmgNazW8U0vjweODGyqpYrsYjytx3x3oGa5LEEjH9XvQGlgmjjMmQq4HBPfPYgevagG5nhe3tkFuInQHxJQTmQntn0wKBKTlAeDx60DSY+U9zn+mgsnQvROr9Y3W2xi8KxV8SXUnCrjvj1Y/IUR6c6A6H03o6wMVgrSXMoBmuX/NIf8Djt/eiLfjJwO9ZBiOfmKDhktzQAzYBLZ8oyaDF+rOptVv8AUjNZL4tjA/lT+kr3wvqTQX/pi3Y+DqFxKXurmFWAaPaVzg4I/b0oHlxqV7penRTXFu93dPLsESYB2k8n7CgnradLq1WaIOFI/K42sPkRQCg3Kcd6Dgp3d6AdrGg5VxnjmgKWB8uQGxnFAUgKuSefSghuqNC0jXbAWGtxQyJKdsYc4YMf6T6GtDzR8S/hnqfSUz3NvuvNILYSZR5o+ezj/Pb6UGfLzyD/AJoFFySQVBHpQDJ5kGByPahAbWxn5+po0OF3D+XPtQJsNwOe+aAuygmMkebgHnHFALHYpJwSeGz2oGpOJWAI49BQEZlYAHkg4oARVOMvtBIJJ7AUAX6xxSOsUgmjViFcKRuHviiVfvhT8NZuqpk1LVFeHRkPlHZpznsP+n50qPS+mWVppdnFa2cEcFtGu1I41ChR8qyHVxK8cLPDD4kgGVQHBNAa0maaBJGTYzDJXOcUCy5JOaA2OMfoaArkheM7vlQNYNOtoWLJCgLHJwo5NApPKLaNpGRQB6j2oGmnRvcyNd3O/DkeErLhkWgklIdCyZOCRzxzQEeRxhdpUnncBkD5UCxXjJ7+tAlctMsIMLohz5mcZAH09aBQYdQwyAeaAuA7MAQxHH0oG1481nbGVInuWU5Kr+bHrgepoKB1u+o6jqlvBH05NevEBPBK0pQR4I4BHZj+1Bb9IS7lsFtNWtYwDGFYB/EXHqpJ7/WtQYx8VfhGbdZtV6Uh8gy81mpyR6koPb5UGKY4YkeYd88fbFAI5AC98c5oQBb+U9+9GnN5RgDgjOPWgAN3yMfWgAqc91/UUD2RSSRg9+49KCR6e0WfX9WS0icRwgb55WOFijH5nP0FBYNRi6dSR7HRNPmu0hOW1GaXaZMdwBwAP3oynE0XRYrFtV02wS4ECj8dp1wcsE7eJEf39qlFZ616ZttPu7Kbp9Zbi0vYzNCcgjHqoHuKsEp8LPh7P1PqjXerxywaXaviRSu1pWH8g+XuflQemIIY7S3SK3hVIo12pGoAAA7AClEL1N1RH0/oTalcwx+IACLaSQKx59Ppmshv0D1jH1ZbTubU27xkkAnKsuSMg/UUFluLlLaJXETyecKAg554zigXiubeRnSKeJ5FOGVXBIPsaBLULoWkIfw3kYsAqIOSTQJMbpm3oqlmwACeF9yfn+1A+Bx34oE5IY5P+YFbnPIzQKAckHuRQCAQOO1AL8r9KDhkZOT9M8UCcrxgAyYJzwD70CT3Itxm8kgi3fly+P7/AOKA9pskhEkZysnOfeg6RH8w3tgjAHtQRZ1uystSg0m5eRJ2UbHceV8fP3oJkBSAVII9xQFdSRwKDDvjN8L/AMSJte6chxcgFrm1QcSf9aj39x61YMH8Q+CkfhqpQncxBDH5H6VRwXJ/Ke1Am2QchuMYOaNFSAVznB9qAm8f10D2RmX8jDHP3oLbebtA6ej0m2LrfX6LcX7IMskf8kf6HcffIoG8yTadZxSTxCK3kRZUwSFfkruIJ78GhiS6Y1OS3160uZJFWO5bwZtxzuQ8bcfPNMZXvo2wsLnQ9R0q/maJNNv5Yo3bjCuMAHPzqA2jdUan0lF0/ZXcElxp9zE+5WVd/DE71IPPB7H2po1bSNXsdYthLp1ykyEcj+ZT817ioITrnoux6vs1gv5JYnjz4ckZ/Ln5etA+6N0BemdBttMina4WEFfFdQpIJJ7D60E5I4Vo9qnnsQO1A3k0yzeTxhCizZJ3qNpz9RQO449igMSxHGW5NAIwBtUAUAMORkfegMhG3jtQD8+fvQGXJz7UAHuRQA5YDI5FB0qCQA5yaCs2/SFit/Jd3AmvJ2bO64ctt5zwD2oLMilVAUDgcAelAJLbhgZz3oGN9HPIYmhtrWRw2czjt7Y+dA+h3mJS67W9gc0AvuLYANADpkZABHY85oPOnxy+Hx06Z+odGjC2jt/7qBRwjH+cY9D6/OrKMebcceHwfaqCYIyDgZ96GhHOFJI4/WjQpXnsaCz9J6fDqGvRC8OLO3Vri5PB/hqMkfc4H3oDT3UupapcXrKS9zISgDdhnAGPbsKC5aLLBHq9p01c6bbagPE23kpJYhmz5IySAAMj6nNGdRnT2lu3V9vaQQrJDHfCMFj5kAfufsMUFogu5H0jrLUYXK+Lq0aRse/lf/8AOKlFfudagvbnQpNQRmtILydCwPdCQcgMOMZFQanPoeiawBd9M6s9jeKPK1vKQp+RFA4septa6fuFtuqbRrmzx5b+BAdo927A+vsflQXfTr2z1O3W5025juIW/mjOR9KAZI914khaRNo4XdwT9KAl3b2+oWpjMoZWbOVfnI9sUCrXUNssUU8w3sQoJH5jQLvwQQC3NAKvuUPtK54waDg23v6UA7weBnNAIOBigMr+hoOjdZQdhBx3waAVG0Z7UBWfAOQSflQChyNxBAxQRutarb6bHALi9trSW4kEcJnGd7ewFA/j8QEK/IA/MBjmgWDDBB7igj9dupLTTbiaHZ4oQ7A7bQW9ATVgwXSNV6onl8azW6t45pWdxHIxWA/zNtz7A8Glg2S1u7fX+nt0J/H2c4MMhmQoW9GBUjj60g8sfEHpebpDqi4sHLG2Y77eQ486E8fcdvtVFekGW4UfegKVAAKgnFGhuDzxQXbpDTZF6a13UnUqrCOzQ5wGZmXIJ+lE0ppkEK6nJcRWcTW9hA08iKcjcowpye/mxQ0+6VRbC/jvLm48L8LG9y8pIOXxkDnuSTipqHXQMng3es9S3fhn8DbvcZI5Mr/lH700dc3Dad8NtPs4nU6jeXD6nMCwBRF5XOfU8YHrTNJFF1X8RawW1jc4GxTKNrZB385yPkBTFw1stSu7Ni9tPLGSQfK5Aphi8J8UNUm6fn0u72yvJ5fGbuF/39aYYtGgadp9/axXnRetzaXqnhqZI3bEcj4547Ak/X6UxFisPiXe6NMdO65057eQAr+LhUlHHbOPX07UwWXpQ6BqMo1LpgW0sioVI8Qgxk+684qC028M5890Y3kHKbUwF+lA4LDOzu2M4FAOG3DaoI9cntQdJxzQEyR259f/AKoGl5fSQRFo7ZpB/MhYIR9zxQdayyXKb7gqox5Yo2yB9WHc0DPUIWnhWKxkuYFRs5gcKWbPY59KBkx6isVeSGW31JNwHhyOUkA+o8v9qCfjkMo/LJFKqBmRvSgc2swnRyFcYODuXGfpQMtRsLK8vYJL+wjuGiUtHK6hghz6Z7H6UEmCsig84I9RigiruC9t0DaaVmIIHhTOQMeuGwT9qCJ1ywv9T0U29xFFiaVBJGHz5M5ODgYPY/arKJPTtLW1t44i7SKq48w8x+ZPrTRJoipGFQAAdgKgzX47dMJrXSrXkUe6807MykDkp/MP8/aro80FQyZ+tUJ7hvH0x270XQ7KGtXvIk0T4c9P2bIhkvpnvJVfjIxhf7qftRDXpu0/1DpzXltUlkvmWMBI+2zdnn64oYa6yX0XTm0i4jQ3t6wmuV53xov5UPpyeeKyLbpFtZ6Xpmn6TqNq7/ic6pqQRR/DVf8Alq2fTOP0FXBnXU+ox32o3lzeW+JrxlMXHKR9wfbJ/tVWK5f3AnaAjafCTwwcY4BOM/qKKSjA4Dg8j37UHZKkE5P0olSFlcLDdJPbTNBOigjxOVZu3+80Rbbnrq9l0t9I6isRd2rgKpPlZMdyre9An07oupoh1zo2+lea2fMlr+WZFx7ZwwqWDVug/ihDq7R6b1EPwmpMNokPlVj8xng1BqEUe1EAJOMDOc5oDSxq6YYeuaAJF4oCBUQ7mJ45zQHYB14wR86AVjBXyjge1AEcRTHlA9hQE8kbgEohJ5yQM0ETHNqMOr3IZQ9tIMQyEjKt7D3FBLqywRPJKTuxlj3zQI3Ut14e+yhWRj28Q7RjH60EfpF3rU/jLqFrHbS4/hqpJXH19aCRa8jgiVr1xGwXzYyf99qA9tc29/aRXFnKs1vINyOO2KByoxwe9AYocHGKBvdwLcWzxSLuR1KuD6gjBoPHXWujt071Nf6YSSkUnkJ4yp5H7f2rQgWAA3Y+1An4j/1t+tBrHxKuYS+gx24LRx6ZFtI/lz60FY0+/v8ASphNpd68EpXY5AGNvzFF1YOirZbzVrvX9dkNxZWH8eeaY5Lyj8qj7kcVlETqOqXd/HrPUNzcNE16Tbwxf1JkEgD2AA/etBte9R2Oq2cv+p6XHJfBFjgmjkMaRgAAEqO5o1FWfbgjsR8+9AlI5CgEggeoNAq0iug8uD7g80KKmCcZ7fPmjJzJfT/hWtjJvhOPK/OOe49u9A96X1W90/VrRtNkkSfxQF8I5yScdvX6UGidSLpfVFzcvbRiy6kgZBGysFW7B9T7HHNSjU+o9S1iz0e2uNLmX8RYxJ+KgYeVwVGTn5d6gjug/iU3UOt/6TewQpP59skL5B29x/8AYoNHPB78Ggb2l3bXO78PKsoyVyvIBHBFAoSkbfyhn4GfWgTnmWFN7ybAvc4Jz9hQRdx1dp0S3Dw+JJHbDdPIUZUjX3yRz9Bmrgzbqb4x9Oxho4bB751O5HPkXPsc80wQHT/xrJ1IHUbGKO0kdRiBiAgz+YjnsPpTKN/tLy3vLOK5t5klt5F3LKhyCPemAYLuK5XMDEj1OCP71ArGWLMPT0oIbU7h11u2t49OllWWNm/FIRsjI4AI/egfQ2ktpbww2XgxoDl9wJ49cUCHUGv2GixM13Mkcm0squwUH5/SrgxDW/jFcXOteHb3otrKEEiRISRM3zGc49v1qDT+gfiBpvV7y2unxTxywRhz4ozuHbOR2+9Bmf8A6kNIEWpaZqiooEqtBIR6kHI/atfRjDEt3AKjgVQjug9j+lQWh72e/htTOzyeCnhHPomeMYoJvQum7vVD47K9jpsQBkvZ5NoAHcgUAa7rKamE0Lp9Xh0G1OZZTwZSO8jn9cCsivdS38F9cJDZIY7G2URxKe5x/MT7nNaEKrENwAFPPlosFwS2cd/cc0UlIm3JOeKDo2LH+UA0SjgDk98URzPiJ2449e/NAbS7v8PdpKkpikQ5WQLkqccGgmYNQmXWLeQLG9wVRQVPlcj+Yn3xQa98OviAjz3WjdXSpFdliEuJCNjDtsJ7enepRdel+kdL0rqOTVdIsoYklV1dixO3nunpg9jUCnU3WMeka5b2EUcl3JInmigQs6ZPlJAHY8+vpQP9O1m3nthNo0cTwM2JDwoVj6H5gd6CbhtUiVn8TcXO4ktkZ+We1BAf8Z6fZ2uqXWpyxQrbStGseQzMB2IA961B59+IHXmodXal+HsPFh04HbHCo25+bY/zQWv4f/CCxvII73qC8iuXYb1tYZeF9txHf6U3BatX+DvSl86x6cr2dwjbnEUmcj6Enj6U8hLdJdEX/SmowJp2tTT6Oc+La3HO0442+3NBf1LmRUjjQAfmc+nyHvWQockYyQcY3CgaabaPZxGNnaUFi3mPb6f+KA2q3RstNurnBxDE0mPfCk1YPMemaP1L8RtYN9fJPc2aMUaVmCKg54H0z6VRYendf6Z6T1W56a6j6fgfwJyguhGJmPzbIzjHtSjTn0zSunbi01fSkt9Os5GAmWNCDOGxtXb6HnNZEZ8etOF90DPKFy1rKk3zAzg/3rXI8u7zvOTg4zVoTLDJ81QWDTb2SwuvFgcrkbXwM5H0PFGqsjpd6+kcT61Nc2ieb8OikFc/9PA+WfSjKA1nWBzpFlZ/hLWM4KH8zsPVj6mghN4IyQRk5NGo5BkFmyAfSgVjChdpGO/FAXYpOHLBe/FAQqoBJbA9sUBGxgtgEj/eaCf6DGjt1TZf8RNGumKS7mQZQkDIB+WaMrf8Ub/ovV7V20JIYL62K4khhCLOCcEcAdu9BmCuEQvxvyFUg42+v+/rQaj0zax/EXRY9Nns0t9TtM+BqCKAjEclXA98jn+1Si7Cz6u6O0tLjTrxLu2tQJJrDwcKE/m2M2SfeoLrpupDV9Mh1OytUS2vIN8m4BZQf6T7+vPpj50GfdK9L6rJqk1y1y0elRDKRqdjHHoyDhjx39e9BZr7fagW0j3kul3iETRqHkeF8ZBUjkZIxjtk5rQ86dW6r+O1OcW0UtvaRsY4oWfLKBxz7k/5NA46P6X1rqS6WPS7V9v88rAqi/f3oN46X6C1DSotkus+BIwKl8hn2+3PapROXPT2t20bPY6kJ5UGYmbIfIHGW5z68VBI6DrzzWSrrAjtrwFUbDja5OBlfuaCbluJLeNwIpLiVF3bVXAP0Pv8qBxLO8cYcW7vnuqkAigNFKs8CyxlwG/lcYI+1A31ayF/pt1auSFmiaM/LIxVgwfoO413o3qqfSLyUSwodogAyZVGcbPTPr71aNDvendJ6wtbu7Fi1lezK0bS4VZMjtnFZE0bC5u9Jh0qRAr2yw4uWx59vBI44PegN1tpbap0lqOk2sipLPB4aFsnHbBNOR5A1exFhqFxbeKkngyMhdOxIPcVuhiZFz/zBUEwcKvYnP6fWi0+6chjn6h062uATFLcRrIMnzAsO9EehNR+GvTV3GUh0+O2YsGaWHIf9amjIfib0no3S0VtFY3M000zMzLJtLKvvkenyx96oz0rwNjA8cj2osFLbVAbOc9jRQiXOAwxnj3oBlAxwDj37UDY+vHOQeTQBIdqjcPMfnQwJclWyBgCjJBFeefw4VaVycBUGST2wAKD0L8H9C1rSIILjWLSCytY1lZASVnlL4PI/wD8+vvUo1uwbxI5GkjdVc7isvOBjtj2qBWKFZiQ8CJCB5FHYj5jHFArDbQ20ey3RY1HOAOPsKCH1u61CPSLt9MtlXUHUrbCbJBbPdtvYetXR5T1y2udD6lni1ErJdJLvlK4wWOCePvVgsV/8Sr67UW1vA0NiowIonMe4+7FeT9ARQRmodWa9EYpPBhs1Tygw26rk9xknkn70EjonxZ17TXjAeKTkZ3L+YZ7N8vpSjX+lOpNM6umgkMG3EgBV1DYbG4kewz2NZGkC43CP8MPFBONysMAD50DaHVH8S6N1a+BaxMUjd280pA5wPb296DrXWLK9WNoJdtwybxDKPDcAnHIoJBifTBzzmgaz2UFzPFNNbwvLCcxuyglT7igdRRKg8qAZ5JAAzQEnuYoHiSWQIZW2ID/ADH2H6UERr12BY6hueIQJaO7SK/nHfnHtx3pyPGWoN4jynuCfU963RF+DL/UtQWTkjaWY/8ATnHFGql+j1VerdJY8r+KiJz/ANwoy9C/EjqSbpbRY723RJC8ojIcZ4IJ/wAVkecer9en1+9FzeLCCq4URjgDP7mtLhteadBY2kMczyHUpcO0YxtiUjgH/q9celAiLy1kjCX1ruyMLNGdrj0+h+lE0+t+kNQltJ7yKS3jgiTxUFw/hySp7qp70NV6YEBgWUNjBoaKeAODnHrRoVgDnBP0ozpxZ2f4y5trVeGuJFiBPpk4zQep9C0LTembS30fQbWP8ZsDyTugZgf6ix9fYZpbgmbXSmXULaa6kMzpltzcjJ//AGpaLCY1CDsF74PrUCgHY0HbSx7Z96BGUfxB2xjtQZ11t0Tb6jNfyw2wM18gV5AcBdpzyPnV0Yp1F0o/TEczXjXaTOQYpIk3QlT3B9Rj0zVl0VKbVppImheUSwbsgFfXHc0De0tri/ujFYQSSyfmKopPHqaDV/g9p+padr/gkSRTzKu0kZRlPLYPbOPf2pg9GWzRCMJAFxH5do4wayKX1z/G0CdzqLWRkiaTxQBLudclQvovbv3oMU/4Z67uwnUAt3u1Zw42yhmx3/Ln8v0oN86L1d00i3i1UiGQIocNnEbnkqT2xgiguEbI4DIysp7EHNAZnxQQ/Usksej3EsCl5EUthR5sY52/Mjigr6Qrp3R15LqEcIlmgdpFGAsY2navPJApyPJtwd8rnGBuJz6Gt0MzGSTyf0qCwSKA5ZsAjnn2otTXQYj/AOMNIDqCrXUZwf8AuGDRG6fF6Gyfo6+ub0CR4EPgIScLIeAcfc1keatN0661a+S3sYTPKzAbV9B7/StLrQ/iXp9pYLp8elWsUM11AzXMqt53I7g7j244oiB6W6Tn6j2TeAy2FspTeB+Z+/8AmgtnWlvpdl1Dp1pq07Ja20GFQpuDHHAwPf39KDHriVTKSPOCeBnHHtQGsrG5v5pfwcTOIlMjgEeVfck0XRIreS7uUigRpJXOEVe5PtRE/wBJ9HaxqvUcdhNFJp0lviaSWVcMgzxgdySeBipo9T6O8NppUJ1K4iW5KgSvIyqxb5jPH0paJm1NvKivE6Mp7MpyP1FQLRTwy58F0cjuAckfagOTtO3+Y8igMWCIWbOPlzQNhNBOWEbq5Q+YKc4+tAD7JEZgQfXj0oI/VtIttXsZLW5hRopByCP/ADVlGRa78Erae63aXK1tG3LAncM/Kmh10l8IZdBv4rxtTE0yggJsyoz6/P0po0zSNKEMdo9xGnjxuzkqMAEgjj7GmialjWQMgyCRyQcGoITqHT7q/a30+G2jFmwLSzl8GPBGFA9c5NBPRwJDbpHCipEi4CjtigqfWltqCaG8WhNbxyzOBIs8W8FcY4+dWQQ/wtuZdIGqadrknhy2u2QyOSEZOeRngY+XvTBZZevOmhC8janbqiZ53Zzj2FMFcs+sh1ZqsFrp8UkGkrlpbh+DNzhVX5Z5NQTfXyWUXSV2t+wW3EZ5I4HHt61eYPI0mA5C9snFaoLsPv8AvUEk5JcA8cZG480WnOlXX4PVLO4yQ0cyP244Yf8AiiPUfUump1B0/c2O8xfi4v8AmL3UcGpgw/SujNX0Trj8PpckimOMvHO/kEg9Rjs3PpV0aFq/Qqa1ZJ/qcrverEqNOwGM+uMfemiVtrKbQdMNjp9rvtkhPht6mU5yT8u1BkvXg1qXUtOvddgRY1R3j2YHiMvZSD27CgzSCyuNQ1KK0giL3Mz4VAOc/wDignoNNOnaHeiW8hgkku/Al2+Ziqgn09M0ETp0qpqSmGKOdFcEeLwMfPHag3JLuCRtPmQWsDhNphtVAcn1w3BPFSwDdWGpX1/OYdOtbbSrlQ80szHdn0GR24/c1AbWemdatLbTJdGvJIJypDQwMV3exwOPatSz9Ei/R+txy2mr3evyHV4miWIDhGwwyGA7nGRS2YNZAUBWYDdjGayEvxMYB3nYu4KCfU+woG93c2enWs1xcPFDCp8zEgDPzq4GGgz22saS1zZSZhkdsFePXt86YHWmySeLNDMYikZ4YNlvvUD+VARxQJqgwRQHUAAe2O1AWOFRM8mDlgB37fagb6reXFt4ItLZJnZsuWfaI0Hdjwcn2FAz0nWX1i4u4xY3VpFbv4eZ1x4vGdy/KgkriN2aMRlQoOW3DOR/5qwYr1P1tp2pdS3WnanKkGh24kRl2eaYgcb/AFxnnAqiv9Jno0dRLJPbtdQtkNPIALaMnODsPPpSjbdK0DTbWQXui+Gsco3BU5hPP5gPT7VkU74t6PZHpq/1N5ZZbwrtRnmOwDPOFJwPsK1xR5ybudw788VaC5X2WoJRULSBpAe5PA/aiinAZnHck4A70THq/Qr23/4Y0u4lmCpLBGA7epxjH60Du+WGOBvFlFuWOFcYyCfbPrUojri6k06xX8PFNfBUJ3ltzM3scVBjfVvVXVNit5dapNDZGQGK3shjeAe7YHIwAOT3zVggNTiu+orrR4p7m+upJFR7h3TPhggDaoBwRjnPH5hV0af0xotnoD3l5dWdrY2YjGLhwPEHoef996CC6m0HpuPpk3Wny2s9sJPHJ3AeI2D39T37UGU9QTDULuGPSLPwIyoVIYk2lj6/X70G2/DPp0hVudRuBLcwxhRGkeEjB9M+p96DSLprVHiieaAE+YxHkke4H1qUOIBawL4uAuc8nvj71AwjRtQ1eO78QNp9odyLju/qT8uf70Gb6r8SpLzryy0vp+4NxYSSCEswI2u2Rn3OOD9qC4dVamen9NlaC7tUaIFvCmnHiy4HJXJxnOeDVwed+rOvLnqSyWO4jZSru/kc7ck+30GKosXw2+KmqaDJDY3jR3OmqNoRhtZAP6SP7Ggtmt63qbTJ1XLazJpslwBFblypEOAA7L2OWANS+xrnR2vW3UmjJeWp8wJSRf6WHeoJdSPMCRmgMq8DmgBpNsgUIxBGSccD70DczmS8MDWoe28MN4+f588rj980CktuJZYpFdlKZ4B4OfegQ1hpIrVjbsRMBhBj8x9qsHnX/hm36y1O/u9V1ddPmS6aD8OkQdyxOSe4OMmqLUvwQsYY4Xjv7m4YEEhwFyMY7fXB5pRbvhp0jqfSMV7b6jqZvLGQAwxAEBDk54PuD6VkVb49a5DBpiaNaeF/FIaQDumOwpzMGDEZQZ5+VboR8In1I+9QWDY6gFn7jjHpQhtJEFbAGBnijT0P8H7qPVOh47a42yNaymPBOcDupoykep+m73V7g/8Av2itQowvJIx6j5/OpRjfUWrax051RPY6LqFy8YACkebO4Z7HjNWCY0ToW2utJbqPreW5na4O4R78cehY9+fQVKLX05p1ro97awC4kX8VFmJLeEKdoyfOxJPbHbHYVAz0rqKPWNauri9t1ktJgILYgEiNFJ/Op9STmrBBdeaFCo0y3jt444DI3jLE204Y5DD+9UPPhv0NaRtPq99mSLOy22nOfdh75oNC0vT7m1uJGvGiii3AW8UDbQAeDu9zUohLlhouqap1VciF4I1FtbxSthtobBIPuTn7VBJ2vUth1TYk2ULi9iALwyKQYz6Z9CM0Ft060/DWEcDHe2Mucdye9BFW3SekWt3LPb2cUTsd2UGCG9x7VYMzufhzdX/WmoXj+BPpx3I7XZMmXYckc8EVRKaP8I+nXikLQuxOQSTnBzj6UEjonw90XSrq3S3s7dplJcl1EhGDx396lFx1TQ4NVjaC7UNCU2lAO/8AvNWDCLp9X+E/WgWImXSp2LRq7eSRT3B9iP8AFSjd9P1+21TRodVsMS2rLmTbyUGOePXFQSltcLcW0c1vh4mXcjDswoDLdRm4FvISsgXeTghDzjAPbPyzmgVFxCzuiOC0WN3sM+5oDqySJmNg3rx7UFb60tNUubGJdFdEvhIdryflUFSM49TVgyTQenJemOorf/U4H1Fpp1edAh/hOQTuQ9375JA4q0bnbPBcxxT20wkjKkqYzlT9ayGWu38um2MbLEJ7iRtoUds+/wAgBzQeW/iHqi6j1PdzeL44HkL9txHtWhVUOVyvHNB2F9zQT8hUAhAdp5FCG0mSAzE4HGDRppvwL1bwOpJbEsFiuYyVX3deR98Zoy2ZtRgmjkSRZocEp51K7se3vUow/rfpFE124mVpfD4mk2MWdCc4A+VWCH1281/UmFnpklzPYRFBEG8uGC4yQfcn9alGgaJo95rRsbi53WaxwrHOm7BjYcHnvz/moJaw07pXSI5IW1K0CQnDhpAWB9R796CudY62msTRW+gadI8KnDXMkLLv9MA8HGOKC3dAXF1dRfh75f41moi4G0AdwcfTj7UFhv7RjqMBV5AJFZHkR8FRjIx6CgpXVNjJ1JqNn07p26CztSJLlpIydyj2J+fGaC+afplrazqLa3SKNIggx3IHYUEsBk4wQc4oK11L1z070/M9rql6wuVA3QopLcjNBDwfFboqeSO2W7kQNxuaEhQfnQLt8TuireVoV1UeXnckTFT9DigHRuv+mbu9ZV1W3Nyc4IRlVl9O47/KgtU+s6baw+JcX1umRkAuM/p3oK/1t0rYdX6cqXKESqN8Ug/Mp9P1qwZ702mo9GdUTWJsmOn3EY8CAORGXJAwScjJ5q0bJDNLb6YklxbKsgA3wwndg9sDtWQN3aw3ZKTwLLEQOGORn6ehoG1vYAw3FikRt7JSuH3Hc/GSc5P0oHn4aO2uGuYyiose044wBQIm6F1dwfh5ARs8R8L2BHGfnQHv9PS4PjxrGLtFKxysm4qD3oCxboIIo7e1jhQHzAYUJ8wP8VYM56j1ktaal1BMrS2sAaK1OQDD6eUepY9yfQVR5zv7hrmaSaRtzyHJY0DcE4BPIPb5UBwOO4oJYzFvzEYHAH9XvQhNZN7AEgDOSDRo/wBA1SXRdVtNQgb/AJUgfBHcZ/8AGaGPVlhPbarZ2t5CEeORBKje2RUrI1zYxTBhMinIwcjvUEcugWkO4AMisMEA8N69u3yoERrOhWNxNYy6hapcxAeJHM+D8u9ASLStLlm/EWdpZyxy+Z3RQ3I5B44oJKTT4blFWSNBEOeBg5+goFYbOK1TKhIxnIbGMH50Cpcyo6AMrIcM2OD68Ggb6Lbbllu5Cd88hYBu6rztWglSNkfm4P70Gaat8Rba96w0vp3R2mhufxyi4kO3YyDOV9+f8VYMw+P0cP8Ax4JVuEKzW8bEr5tuMj0+lUZ7Y2X4288GK+towRlZXYqv9uKCQi6YmbT2u11GzaJWKnYxbBB49KCFnhubdiwL+U8OhP60ElpXUFxY6nDdXQF0qYbZKxwT9vWg3npb42aHcmC11C3uLSQjEkpIdQfr3xUondP6x6e6tv7e101hczRzrNtaFiFC/wAxPYHtUF+lj8bYCTgMG59cUC4OBQQOo2eoXepFTeL/AKYQN1sEwWx6Fu+DQLX2kw3Ok3Vjas9qJ48Exd1PHb9KCE6R0G86Ut7mK71KK4gklM7TyKRIBjtjtjj96AOreudJsrMJbXksk8jBCbVdzRjONxBHP/3QQ9x1jcWGkERWWqXdpMPCt7x4wfFOOWPbA+fAqwZr8TJ9Qbp2ymvEjsrSTEVvawyHz45Lv6E4wPqaoyl8g91OKDlYEc8mgKW5PH7UE80f8PPHl7gDFAZkUjawUIQG8w5ouknAUbl9Dg59KK1X4Z9XXFvo8mlRXax3KHfBG8Rk3qe6jHOc54+dMZO7jr/qK8vWtba4tYu38TwvDOMc8N60wPLbrW10PS7pnvrnUtbAKobgBUUk9jg8f/lMC2rydMdRSaRqWoLEbx4UefwxkL2BVvvn9Klgv3Tp0lPxFno6wJ4IVmEOMEHsf2xUD2e4ks7n+NGDaCMu8q8lCMcEfPNA6tW/EwrMybEYZUHnI9Cf/FAzu7G4LXTWs38SRNqhs4Bz3z9KCO6x07UNT6altNMvEs7xkC7nPlI9R2/egwbrDT+r+kupLCeK9nu3KBYGRy+QvdWFWCU6avtA6h1iKDqLRhpmpvkxz2p8JGb3z7k557VRX77TdHteuPBut401CAouyXGcdvmASaC069030brYaay/CwPFwWspRErfUN7UGZX2hWSiY6ZrMc0CvhUlBUk/UcGgiLq2mtG8F54yDwfDfIoGkrRsSZXwOB2zmgsvw06XHVfUcFvI22xQ753Ze4H8v3OBUo9a6XodjpltHbabDHZIhVsQqBuA9DxznFQTQUe5oDYGMnn7UEbpV3JqDyz+BJFbBtsXiDBf/qx6CgDXL42cSRwGM3UzBQrHGFzy32oG2i2kKTSI80lzMow0rqQoyew+3tQO59KtJJRI9rEzgg7igz3z/egZ6paJdGGwW4eBXy7pGeXUdwT6A5qwebPjJrcOr9TvbWZQ2Onr+Gi2nIJHcj7+vyqigOuRk+vtxQAqEk4BU0ABj7j96CzzKxYD0GeM0CQG3OMAjkfOgbSZwzE4PJyfWi6caTdzaffW95akrPFIrLg/tRHpGzs9C6t0W31FrO3Y43MrcbH9c/eloZ6v0JpWoKlrHHBbScSFEHYc5Pz71NDXUoJrK1g0dvw9qsspW3nXaN6KMrHnH5ieSfan0U3Rr1uidaRbiwk8BUSS6naQkjc3ZcHaRnn70wbja6lZX+nw3NvMksM+FXnPJ9DUCeoXj2hSG2t2km7op4U/f/FAvHaNePb3N0jRzRA7VD8Akc9u/FAvcxnawZQ3HYtjJoKfDFAdeub6Vo1dSULIBtTbgYOfU8jNWUVvrm5ih0m1urixhlsI5HJliOwR5/LkkHHJPamjHdQ0HWdemlutN0+YWBYtC0rHDhjwVz3zWgx1n4e9U6QE8XT5Zd//APR5se9XBXbjS9S0zAvbO5tyWKAOhG4/KpQ3ZHXO5JFK98qRUGhfCbph77Uvx91pv463wVjR0LR7s483796WjW7rTrXpHWrSW2YK7lmXTbaIFpCRjjHOOSeeBipaNLtXuIre3R43lnkGXYADZnnmoH6Dkbzn6UDGWe9a/hKG3jsW8riQMJS3svp86B6zgMQmDtGT8qDNb6XUpOoPx72tzOkjFYowOduDwDjj70Gg6Wsq2KNeAJKRuKk52fIn5DvVkENrvW+iaSAsl0txI2Asdud5Yk4A4pgzv4l9ST6JZSXbyyprWpw+FFa5G21gz5icfzH3pgwCSQlh688+tUEwjjngZ7UHAHuWAHpn+1AXj5frQWXOGBZcKSe3c/rQIyAtnI27eBj/ADQIMAuH8vHBB9DQwVpPLjOckEZ/ahi9/Czqj/S9VhtLm6aG1uZFUsT5VOfX5Gpg9GiNJArxsrxsv1BHypYGF7pljeG3kvLZSlqzNGGxhSRjP6GoG1yLUWiWc2nSPA4KJGItyYHYHHarop3wu0jWYNUvzriNBp8ErraRMANxJ/N7nA7ZqDUHgSQLvAbacjI7H3oOuIFuYzGS68jJRyp4+lA0m0yDwGjiTw3bzBwTuDe+TQVbV+mLmW1NtbSok9weZiC2zPLEZ+/FBM6Xo40/TYdL8Jr21G4vJcuCck55HbFWUKQ/h4tR/DTz2o8TK21qmMgKOf8AfpmrokljG1i5BHI57D5VNorut9Lab1LA638W6H8sboNrqQckq3pntV0RWsfD6K7SGC3vTFahQJY2iVmkI9d+Mimie0Hp2DQ7AQacio3JZgqjcT3zxk1KHGldPWtnqMupS5uNTmGGnk5KjGNqf0r8qgmkhVGcquGblm96BDUZZYLGVrdN8+MIvux7UGKTdXdbaRrFvbaxbWN4d58BmwCjHPORycLx2q4LNe9S9TdN6I13qkWmzSXdwBCGlO4hiMKAB2A9ag0WySQwpLLtMjDcQBhVz6CgoHxF17XbnUYunulgsUsu4TTvjIUAEhR+x4qwZwtkOi7651PXJobm4tohHbQhdgecjnaPZeOfeqMy1vWLvWNQlvb+ZpJpWyT2A9gB6Cgjy5AO4A5oAGRgBR39aA7Z8MkFtxPY0AbV9UGfpQWhj5TkBQGxuBoEGG1iQCyHvj1oELgSkK6oRnIBIxzRdJ28Q3+fHiAds96LoH3AF1wCfyijNbF8JviI1rbQ6Pq/iSopxFOx5Uf0n3qUbWQk8II2SRyDPuCDUHMpSIiJQSBwDwKAgTxApnEbyIQ+APyn0+9A5B3AgfmoEWgcb3VlMpGFYjt+negSs7zxH/C3RWO9UElM8SAHG5fl/agNdXcEbJAZ1WadvDQDJO7Gf7c0ED1dqWv2enzw6Rb24nZfJd3EwREHqxyMZHzOKBbT7H8PZWTK5uZ9o3Xm1SzEry5PsT7UFF+JnUezSZ9LttRs2km2m5KSFWXDZI491AyBzVwK6J8T7CRtPjee0tbaGAtdNISdoXgLEo5JJxyfSmC6aF1fo2vELZXDJOxwkMybHYe4HtUFiJWJd8rKqjuTQcZV8SNI0dy43BlGVA+ZoBniE0RU7tp77Tg5zQUv4hNrU2tdNWOhylPEnaS5UHGYlAzn5cn74oHGt6l0z07k6nJC123HhKPFlbPptGTj9q0Kx0XMvU+ty6vqQtpWlZo4LOdGDWsak8Aflycgk+v2qC8a1q8OnaXLPOz2kCIWkZ+CqjgYx6n0xTBkmp9Sabp0KdRyI5vJkaGw08MVKIDw8jA557896QY1q2o3eqXr3N7O8skjnlnzgn5e1UMCGV/MOM0BJFOVwfX0oFtgZTjkg8UBtpOeO1B3hg85FBZXVMM+VJAA2+h96BO4IMJ/p7qvuKBKacmOKB5CYYx5UzgDPfHzoGwD5OApJHAHrQEAk8NWdNpx+XdkA0AIGhkGWOQcgg8UGw/DP4kmwhi07WCTZqAiSbstGc4+pFKNvs5o7q2Sa3kWaJxkOp4NZDOHUh/qL2k8LW78eG7kbZv+0+/yoEZp7fUpX/BXpgvYZTCSRtO7vtwe/vQdY6jeyatPp91FEPw8aSNMoYbi2cADt6Z70DS60KW7luJdV1JniJzBtURG2b0KN7+/vQKSWUWnLLqN3cSLP4ex5Y8jxiPykr23+nzzigpXUPVOu6Vqmmf8UWttb9OXDqkjRnfI3H849uRkDOKC0axLFr+nLB0rrUMM0bqCIGGGX1AH09qsGc9UfBiTV9Vhu9Pu5oPGLNeG6bczN7jHvVEr058Gre3sLeDVrmOdo3LmSFNjEH+XdntQXO51XQOl5YrCKGWa8SMYS3tzMyLjjJHb9alDqz1S5ktJ7nVdLmSVDiOONfEMiE4Xy+h9xUDm11CaTxEOn3VmpHFxKFCr9s5GPmKAus6jb9M6RJf3c88yxpjcxL7uM5OO3HrQVTSupoOuYdZMTSpptriNFtXKXDA/Pjhs9h2xQOJ7Xpnpa2S91WK2swqjbGw3ysfcnuxrQsGmapYvpwvra1FtDL52Mi+Gx49sZoMb+LXV0t+jWl3OYLGTO2zjx4h2nyszHsG4/Sgxt5ZJmEsjl3PB3GgSlyXBxkDnNADseB2PsaA8SoXQyFgmQCV70B5R/EIjYmPJxnvigEKcYDfrQF2/X9aCwqC7l2zwfT/FAJJ5747E5oGTqZArKOfccftQHZWwmOD23Z4NAEkTEBmwR7g5AoG7KSSE5HyFAMTyQsMHa/cEcEc5oL58P+v7rppdryPNAXx+GfsQe7Z9D2/Wg3zSdX0fqzT08F433eYwscOpHt9PcVkQPW632mX9vfWdrbXiRgrIdu2eHIwGD57+nIoKdc/ELVdC0u5afp27SUtta5vJMMzk+UDjzYHtQWDpj4gxXmif/wAitXZkGZzFGW8MehZO+PmM0Fibr/poWQmF6xXA2xmFg59sKRk0C2nQP1KFvdb0vwIUJNtDKcsVP8zD0Jx2oJDTNA0vR5p7qzs44pJOXkUc/SgNfa/pNvbF5L2JgTsCo2WJzjGKA1jcNcxOF/m/I0zbt4+gxgenNA5s7CCxWWYQxpNLgyMiY3nt2oHajcuexAoEL1C1uyFkVHO1ixHb17/KgwT4rdXWep6oul2OpywaTYqVLxDyySDjaM9x6Z+tWDPdB1TW7Wa9sumpGlursqMQRlpXwd3BA4571RcdN0i41G7h/wBSmNxqdkwn1O6u5/4cAXlYgcnngE/pQNvih8S211obHRyYbWInfJG/Ex9MD2+tBmNzcTXTtJcSSSSHH5jngDAH0oEdxbg5A9wKAzPwO+fegSLfLJoFoR5fUfegXOcHGAT8qAM+XaBzQCCwGDuyPlQWJpV37Q5TIweM7u/f9qA9vNYpFML2KaR8YiaJgAh55PvQRvnYoqA+MThcDnPai4PKWQlH3K6tggjnPaiEmz4ZznBPfFAVWG0AZDH1z2HzoE7lhv8AJIHI/mGRQI8AEeuOMGgndN6pu7V4RJLKY4WDLhypXj0oNL6d+MMS4ttetDdQgDNwAPEwPRh2NZGkabrvTXVZiexvba5aI+ILWZQG3Y4IDdvtQScvTdjK8chtFjkQ+VlYgqPXGKA17daV07apJrV9CsZbELTgbu3YY78UEHf9evJ4K9P6JqGoiR1XxjCUjAJ5OT3NBM9YdSWPTenwy3t7bWbSuBunUthfUhRyT+1BA2vXnS/jGdeo9LnIHljeLwSCe5zgmgejrOz1S3kGhazoaXYGAJ5Sw3e38uaCsJfX02rPD1XfXtvcCXdBJGjLbOO+EK88Y7nIoLB1H1Bb6WkN1ddSQ29io/5MZEjzt7DGTjj2FXNGUfEH4wRaxCtnp2kwGGM7llvBvIOO4XOAe/fNMwZbqusalfLBHfzSvFH+SIgKo+igYqiwWfWV30rpp03p6exJnUPJexQnxuR+Ulu2PkKCrT6jcSiTxZnbxCWcFidxPJJ96BBDlQ35fbFAbahBHJIGO+KAIwg5YnB455oDkKcbW7UAOowSMjOORQcCVXPp+9AqDkHcDmgMNpHPcUBTuzQWCJXcFvKR2Y0CMiqjnz4UcH/6oG8gKluwxyAfSjQ6ylEJBJfv37/OiYQMjbjkZXOSP/FEELAEkNn1waBCXdjORnPoc80CZeTb5wQe2BQAm4y7jlhjvQcWO3cW4GB7ZpgGC5a3uUeNyGQ5GCR+45pgt+l/EzqLTgxj1O5Zc4CSOXCj70wOE+Jd/Pq0V7qVvb3bISAWUBhnuc+/2pgvkHx0soLaNIdKkEiqR5yDg47cYpgresfELSNc1n8VrFtAw2ZBiiywwcgeb14x2xTBYNA13ozUo/GOqWVizDc1nf6crIh/7wOf1rOURvVupdE6ncpFeakiSWsZdbjSLfw1Zs+VVyMHA75xWsFDHU0idTJdf65rT28YKpPvHjKp9Bk49qYK/rGpXF/qU9zPdyzyyMSJJAAx9ifnVlwNZ7vxYEh8GAEHO8DDH5H5U0IPK8jHxSzFQAMnOKgJkFwPT6UBlAII5z3zQCjnA5OKBXeuAT9KABMA208DtxQHRhzgUC3KjJx9z2oAP6/L3NAHC8Hg/XNAcNtGe4oEy5yeaCdLk7yx2qQCAO1AmXZSSexHbPNAhJuLJkgjvzRonuAJy2cd8UCbyOi453Dj7GiYTZyVPPl74oYLJIyq68EH3Gf3oYTDEjLbiP1FEDHOUOdgOfXIBFAm77j5Mnng/WgLI5UE8Eg9iO9AnuJbuQx5wOBQFRxuIbOc54PrQK28ws76F722EyI4d4HJUOPb35yKBm8oeQsi4BPbPb71RyYIHmPGRg00GRsbsHIPY0Bg52AEEseBUCQJyOPXtQDtcdvvjtQCQ/GBwKAuXU4PrQBvZE5IGeO1AffjBJ57UBvEO045HagFWAAzktQKIzBeMg0C5kz5mOG/WgMrDJJ7jmgEnIyOccYoA3cEMRj05oC7/wDeBQTduzEoNxwcZGaAJOWfPNAlISVOT60aIQfkj+amgJ3bnnigKeFGPQUCf/x0Smw4V8exogX/AOY3+/SgKxKxeU459KAgJOckntQJkkcgkGgAAFFz/XQEmJaY7jnk96BM9yPQelAf/wCX7UBv/jagGP8AKB6ZoDf00HMfO/0oAH5TQA/5moECSMDPFAvGASMjPP8AigVX+b60BW7/AHoHEJJD55oDd4snv70CsSjCcDmgVAAbgYoGYJ3nk9qBUAYHAoP/2Q==</binary></FictionBook>
diff --git a/tests/writer.html b/tests/writer.html
index b56e81292..1357fa7c4 100644
--- a/tests/writer.html
+++ b/tests/writer.html
@@ -35,7 +35,8 @@
<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<br />here.</p>
+<p>There should be a hard line break<br />
+here.</p>
<hr />
<h1 id="block-quotes">Block Quotes</h1>
<p>E-mail style:</p>
@@ -419,13 +420,13 @@ Blah
<h1 id="latex">LaTeX</h1>
<ul>
<li></li>
-<li><span class="math">2 + 2 = 4</span></li>
-<li><span class="math"><em>x</em> ∈ <em>y</em></span></li>
-<li><span class="math"><em>α</em> ∧ <em>ω</em></span></li>
-<li><span class="math">223</span></li>
-<li><span class="math"><em>p</em></span>-Tree</li>
-<li>Here’s some display math: <br /><span class="math">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span><br /></li>
-<li>Here’s one that has a line break in it: <span class="math"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li>
+<li><span class="math inline">2 + 2 = 4</span></li>
+<li><span class="math inline"><em>x</em> ∈ <em>y</em></span></li>
+<li><span class="math inline"><em>α</em> ∧ <em>ω</em></span></li>
+<li><span class="math inline">223</span></li>
+<li><span class="math inline"><em>p</em></span>-Tree</li>
+<li>Here’s some display math: <br /><span class="math display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span><br /></li>
+<li>Here’s one that has a line break in it: <span class="math inline"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li>
</ul>
<p>These shouldn’t be math:</p>
<ul>
@@ -524,7 +525,8 @@ document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'" clas'+'s="em' + 'ail">'+e+'<\
<h1 id="images">Images</h1>
<p>From “Voyage dans la Lune” by Georges Melies (1902):</p>
<div class="figure">
-<img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" /><p class="caption">lalune</p>
+<img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" />
+<p class="caption">lalune</p>
</div>
<p>Here is a movie <img src="movie.jpg" alt="movie" /> icon.</p>
<hr />
diff --git a/tests/writer.icml b/tests/writer.icml
index 8922da7ed..968e84941 100644
--- a/tests/writer.icml
+++ b/tests/writer.icml
@@ -410,11 +410,6 @@
<Properties>
<BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
</Properties>
- </ParagraphStyle>
- <ParagraphStyle Self="ParagraphStyle/Rawblock" Name="Rawblock" LeftIndent="0">
- <Properties>
- <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
- </Properties>
</ParagraphStyle>
</RootParagraphStyleGroup>
<RootTableStyleGroup Self="pandoc_table_styles">
@@ -1389,21 +1384,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Content>Interpreted markdown in a table:</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;table&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;tr&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;td&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>This is </Content>
@@ -1412,16 +1392,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Content>emphasized</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;/td&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;td&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>And this is </Content>
@@ -1430,26 +1400,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Content>strong</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;/td&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;/tr&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;/table&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;script type=&quot;text/javascript&quot;&gt;document.write('This *should not* be interpreted as markdown');&lt;/script&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Here’s a simple block:</Content>
@@ -1497,31 +1447,11 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Content>This should just be an HTML comment:</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;!-- Comment --&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Multiline:</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;!--
-Blah
-Blah
---&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;!--
- This is another comment.
---&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Code block:</Content>
@@ -1537,11 +1467,6 @@ Blah
<Content>Just plain comment, with trailing spaces on the line:</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;!-- foo --&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Code:</Content>
@@ -1557,51 +1482,6 @@ Blah
<Content>Hr’s:</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr /&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr /&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr /&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr /&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot; /&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot; /&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>&lt;hr class=&quot;foo&quot; id=&quot;bar&quot;&gt;</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Inline Markup</Content>
@@ -1980,9 +1860,7 @@ Blah
</CharacterStyleRange><Br />
</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/BulList &gt; first" NumberingContinue="false">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>\cite[22-23]{smith.1899}</Content>
- </CharacterStyleRange><Br />
+ <Br />
</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/BulList">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
@@ -2097,15 +1975,6 @@ Blah
<Content>Here’s a LaTeX table:</Content>
</CharacterStyleRange><Br />
</ParagraphStyleRange>
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Rawblock">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>\begin{tabular}{|l|l|}\hline
-Animal &amp; Number \\ \hline
-Dog &amp; 2 \\
-Cat &amp; 1 \\ \hline
-\end{tabular}</Content>
- </CharacterStyleRange><Br />
-</ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Special Characters</Content>
diff --git a/tests/writer.latex b/tests/writer.latex
index 3b4f74b3c..63061649a 100644
--- a/tests/writer.latex
+++ b/tests/writer.latex
@@ -24,7 +24,8 @@
\UseMicrotypeSet[protrusion]{basicmath} % disable protrusion for tt fonts
}{}
\usepackage{fancyvrb}
-\usepackage{graphicx}
+\VerbatimFootnotes
+\usepackage{graphicx,grffile}
\makeatletter
\def\maxwidth{\ifdim\Gin@nat@width>\linewidth\linewidth\else\Gin@nat@width\fi}
\def\maxheight{\ifdim\Gin@nat@height>\textheight\textheight\else\Gin@nat@height\fi}
@@ -65,6 +66,12 @@
\author{John MacFarlane \and Anonymous}
\date{July 17, 2006}
+% Redefines (sub)paragraphs to behave more like sections
+\let\oldparagraph\paragraph
+\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}}
+\let\oldsubparagraph\subparagraph
+\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}}
+
\begin{document}
\maketitle
@@ -75,10 +82,11 @@ markdown test suite.
\section{Headers}\label{headers}
-\subsection{Level 2 with an \href{/url}{embedded
-link}}\label{level-2-with-an-embedded-link}
+\subsection{\texorpdfstring{Level 2 with an \href{/url}{embedded
+link}}{Level 2 with an embedded link}}\label{level-2-with-an-embedded-link}
-\subsubsection{Level 3 with \emph{emphasis}}\label{level-3-with-emphasis}
+\subsubsection{\texorpdfstring{Level 3 with
+\emph{emphasis}}{Level 3 with emphasis}}\label{level-3-with-emphasis}
\paragraph{Level 4}\label{level-4}
@@ -86,7 +94,8 @@ link}}\label{level-2-with-an-embedded-link}
\section{Level 1}\label{level-1}
-\subsection{Level 2 with \emph{emphasis}}\label{level-2-with-emphasis}
+\subsection{\texorpdfstring{Level 2 with
+\emph{emphasis}}{Level 2 with emphasis}}\label{level-2-with-emphasis}
\subsubsection{Level 3}\label{level-3}
@@ -108,7 +117,8 @@ item.
Here's one with a bullet. * criminey.
-There should be a hard line break\\here.
+There should be a hard line break\\
+here.
\begin{center}\rule{0.5\linewidth}{\linethickness}\end{center}
@@ -735,7 +745,7 @@ These shouldn't be math:
\begin{itemize}
\tightlist
\item
- To get the famous equation, write \texttt{\$e = mc\^{}2\$}.
+ To get the famous equation, write \texttt{\$e\ =\ mc\^{}2\$}.
\item
\$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if ``lot'' is
emphasized.)
diff --git a/tests/writer.markdown b/tests/writer.markdown
index ad97b15ef..7276b31c7 100644
--- a/tests/writer.markdown
+++ b/tests/writer.markdown
@@ -549,8 +549,8 @@ LaTeX
These shouldn’t be math:
- To get the famous equation, write `$e = mc^2$`.
-- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is
- emphasized.)
+- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot”
+ is emphasized.)
- Shoes (\$20) and socks (\$5).
- Escaped `$`: \$73 *this should be emphasized* 23\$.
diff --git a/tests/writer.mediawiki b/tests/writer.mediawiki
index efd43cb04..066606c00 100644
--- a/tests/writer.mediawiki
+++ b/tests/writer.mediawiki
@@ -36,7 +36,8 @@ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Beca
Here’s one with a bullet. * criminey.
-There should be a hard line break<br />here.
+There should be a hard line break<br />
+here.
-----
@@ -623,9 +624,9 @@ Auto-links should not occur here: <code>&lt;http://example.com/&gt;</code>
From “Voyage dans la Lune” by Georges Melies (1902):
-[[Image:lalune.jpg|frame|none|alt=Voyage dans la Lune|caption lalune]]
+[[File:lalune.jpg|frame|none|alt=Voyage dans la Lune|caption lalune]]
-Here is a movie [[Image:movie.jpg|movie]] icon.
+Here is a movie [[File:movie.jpg|movie]] icon.
-----
diff --git a/tests/writer.opendocument b/tests/writer.opendocument
index 81c793a62..944dc12f3 100644
--- a/tests/writer.opendocument
+++ b/tests/writer.opendocument
@@ -864,7 +864,7 @@
</office:automatic-styles>
<office:body>
<office:text>
-<text:h text:style-name="Title">Pandoc Test Suite</text:h>
+<text:p text:style-name="Title">Pandoc Test Suite</text:p>
<text:p text:style-name="Author">John MacFarlane</text:p>
<text:p text:style-name="Author">Anonymous</text:p>
<text:p text:style-name="Date">July 17, 2006</text:p>
@@ -896,7 +896,8 @@ of a paragraph looked like a list item.</text:p>
<text:p text:style-name="Text_20_body">Here’s one with a bullet. *
criminey.</text:p>
<text:p text:style-name="Text_20_body">There should be a hard line
-break<text:line-break />here.</text:p>
+break<text:line-break />
+here.</text:p>
<text:p text:style-name="Horizontal_20_Line" />
<text:h text:style-name="Heading_20_1" text:outline-level="1">Block
Quotes</text:h>
@@ -1576,7 +1577,8 @@ link in pointy braces</text:span></text:a>.</text:p>
<text:h text:style-name="Heading_20_1" text:outline-level="1">Images</text:h>
<text:p text:style-name="First_20_paragraph">From “Voyage dans la Lune” by
Georges Melies (1902):</text:p>
-<text:p text:style-name="Text_20_body"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p>
+<text:p text:style-name="FigureWithCaption"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p>
+<text:p text:style-name="FigureCaption">lalune</text:p>
<text:p text:style-name="Text_20_body">Here is a movie
<draw:frame draw:name="img2"><draw:image xlink:href="movie.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame>
icon.</text:p>
diff --git a/tests/writer.opml b/tests/writer.opml
index 54be4b671..8f79e842c 100644
--- a/tests/writer.opml
+++ b/tests/writer.opml
@@ -18,7 +18,7 @@
</outline>
<outline text="Level 1">
<outline text="Level 2 with &lt;em&gt;emphasis&lt;/em&gt;">
- <outline text="Level 3" _note="with no blank line&#10;">
+ <outline text="Level 3" _note="with no blank line">
</outline>
</outline>
<outline text="Level 2" _note="with no blank line&#10;&#10;------------------------------------------------------------------------">
@@ -33,7 +33,7 @@
<outline text="Lists">
<outline text="Unordered" _note="Asterisks tight:&#10;&#10;- asterisk 1&#10;- asterisk 2&#10;- asterisk 3&#10;&#10;Asterisks loose:&#10;&#10;- asterisk 1&#10;&#10;- asterisk 2&#10;&#10;- asterisk 3&#10;&#10;Pluses tight:&#10;&#10;- Plus 1&#10;- Plus 2&#10;- Plus 3&#10;&#10;Pluses loose:&#10;&#10;- Plus 1&#10;&#10;- Plus 2&#10;&#10;- Plus 3&#10;&#10;Minuses tight:&#10;&#10;- Minus 1&#10;- Minus 2&#10;- Minus 3&#10;&#10;Minuses loose:&#10;&#10;- Minus 1&#10;&#10;- Minus 2&#10;&#10;- Minus 3&#10;&#10;">
</outline>
- <outline text="Ordered" _note="Tight:&#10;&#10;1. First&#10;2. Second&#10;3. Third&#10;&#10;and:&#10;&#10;1. One&#10;2. Two&#10;3. Three&#10;&#10;Loose using tabs:&#10;&#10;1. First&#10;&#10;2. Second&#10;&#10;3. Third&#10;&#10;and using spaces:&#10;&#10;1. One&#10;&#10;2. Two&#10;&#10;3. Three&#10;&#10;Multiple paragraphs:&#10;&#10;1. Item 1, graf one.&#10;&#10; Item 1. graf two. The quick brown fox jumped over the lazy dog’s&#10; back.&#10;&#10;2. Item 2.&#10;&#10;3. Item 3.&#10;&#10;">
+ <outline text="Ordered" _note="Tight:&#10;&#10;1. First&#10;2. Second&#10;3. Third&#10;&#10;and:&#10;&#10;1. One&#10;2. Two&#10;3. Three&#10;&#10;Loose using tabs:&#10;&#10;1. First&#10;&#10;2. Second&#10;&#10;3. Third&#10;&#10;and using spaces:&#10;&#10;1. One&#10;&#10;2. Two&#10;&#10;3. Three&#10;&#10;Multiple paragraphs:&#10;&#10;1. Item 1, graf one.&#10;&#10; Item 1. graf two. The quick brown fox jumped over the lazy&#10; dog’s back.&#10;&#10;2. Item 2.&#10;&#10;3. Item 3.&#10;&#10;">
</outline>
<outline text="Nested" _note="- Tab&#10; - Tab&#10; - Tab&#10;&#10;Here’s another:&#10;&#10;1. First&#10;2. Second:&#10; - Fee&#10; - Fie&#10; - Foe&#10;&#10;3. Third&#10;&#10;Same thing but with paragraphs:&#10;&#10;1. First&#10;&#10;2. Second:&#10;&#10; - Fee&#10; - Fie&#10; - Foe&#10;&#10;3. Third&#10;&#10;">
</outline>
@@ -50,23 +50,23 @@
</outline>
<outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.”&#10;&#10;‘A’, ‘B’, and ‘C’ are letters.&#10;&#10;‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’&#10;&#10;‘He said, “I want to go.”’ Were you alive in the 70’s?&#10;&#10;Here is some quoted ‘`code`’ and a “[quoted&#10;link](http://example.com/?foo=1&amp;bar=2)”.&#10;&#10;Some dashes: one—two — three—four — five.&#10;&#10;Dashes between numbers: 5–7, 255–66, 1987–1999.&#10;&#10;Ellipses…and…and….&#10;&#10;------------------------------------------------------------------------">
</outline>
-<outline text="LaTeX" _note="- \cite[22-23]{smith.1899}&#10;- $2+2=4$&#10;- $x \in y$&#10;- $\alpha \wedge \omega$&#10;- $223$&#10;- $p$-Tree&#10;- Here’s some display math:&#10; $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$&#10;- Here’s one that has a line break in it:&#10; $\alpha + \omega \times x^2$.&#10;&#10;These shouldn’t be math:&#10;&#10;- To get the famous equation, write `$e = mc^2$`.&#10;- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is&#10; emphasized.)&#10;- Shoes (\$20) and socks (\$5).&#10;- Escaped `$`: \$73 *this should be emphasized* 23\$.&#10;&#10;Here’s a LaTeX table:&#10;&#10;\begin{tabular}{|l|l|}\hline&#10;Animal &amp; Number \\ \hline&#10;Dog &amp; 2 \\&#10;Cat &amp; 1 \\ \hline&#10;\end{tabular}&#10;&#10;------------------------------------------------------------------------">
+<outline text="LaTeX" _note="- \cite[22-23]{smith.1899}&#10;- $2+2=4$&#10;- $x \in y$&#10;- $\alpha \wedge \omega$&#10;- $223$&#10;- $p$-Tree&#10;- Here’s some display math:&#10; $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$&#10;- Here’s one that has a line break in it:&#10; $\alpha + \omega \times x^2$.&#10;&#10;These shouldn’t be math:&#10;&#10;- To get the famous equation, write `$e = mc^2$`.&#10;- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot”&#10; is emphasized.)&#10;- Shoes (\$20) and socks (\$5).&#10;- Escaped `$`: \$73 *this should be emphasized* 23\$.&#10;&#10;Here’s a LaTeX table:&#10;&#10;\begin{tabular}{|l|l|}\hline&#10;Animal &amp; Number \\ \hline&#10;Dog &amp; 2 \\&#10;Cat &amp; 1 \\ \hline&#10;\end{tabular}&#10;&#10;------------------------------------------------------------------------">
</outline>
<outline text="Special Characters" _note="Here is some unicode:&#10;&#10;- I hat: Î&#10;- o umlaut: ö&#10;- section: §&#10;- set membership: ∈&#10;- copyright: ©&#10;&#10;AT&amp;T has an ampersand in their name.&#10;&#10;AT&amp;T is another way to write it.&#10;&#10;This &amp; that.&#10;&#10;4 \&lt; 5.&#10;&#10;6 \&gt; 5.&#10;&#10;Backslash: \\&#10;&#10;Backtick: \`&#10;&#10;Asterisk: \*&#10;&#10;Underscore: \_&#10;&#10;Left brace: {&#10;&#10;Right brace: }&#10;&#10;Left bracket: [&#10;&#10;Right bracket: ]&#10;&#10;Left paren: (&#10;&#10;Right paren: )&#10;&#10;Greater-than: \&gt;&#10;&#10;Hash: \#&#10;&#10;Period: .&#10;&#10;Bang: !&#10;&#10;Plus: +&#10;&#10;Minus: -&#10;&#10;------------------------------------------------------------------------">
</outline>
<outline text="Links">
- <outline text="Explicit" _note="Just a [URL](/url/).&#10;&#10;[URL and title](/url/ &quot;title&quot;).&#10;&#10;[URL and title](/url/ &quot;title preceded by two spaces&quot;).&#10;&#10;[URL and title](/url/ &quot;title preceded by a tab&quot;).&#10;&#10;[URL and title](/url/ &quot;title with &quot;quotes&quot; in it&quot;)&#10;&#10;[URL and title](/url/ &quot;title with single quotes&quot;)&#10;&#10;[with\_underscore](/url/with_underscore)&#10;&#10;[Email link](mailto:nobody@nowhere.net)&#10;&#10;[Empty]().&#10;">
+ <outline text="Explicit" _note="Just a [URL](/url/).&#10;&#10;[URL and title](/url/ &quot;title&quot;).&#10;&#10;[URL and title](/url/ &quot;title preceded by two spaces&quot;).&#10;&#10;[URL and title](/url/ &quot;title preceded by a tab&quot;).&#10;&#10;[URL and title](/url/ &quot;title with &quot;quotes&quot; in it&quot;)&#10;&#10;[URL and title](/url/ &quot;title with single quotes&quot;)&#10;&#10;[with\_underscore](/url/with_underscore)&#10;&#10;[Email link](mailto:nobody@nowhere.net)&#10;&#10;[Empty]().">
</outline>
- <outline text="Reference" _note="Foo [bar](/url/).&#10;&#10;Foo [bar](/url/).&#10;&#10;Foo [bar](/url/).&#10;&#10;With [embedded [brackets]](/url/).&#10;&#10;[b](/url/) by itself should be a link.&#10;&#10;Indented [once](/url).&#10;&#10;Indented [twice](/url).&#10;&#10;Indented [thrice](/url).&#10;&#10;This should [not][] be a link.&#10;&#10; [not]: /url&#10;&#10;Foo [bar](/url/ &quot;Title with &quot;quotes&quot; inside&quot;).&#10;&#10;Foo [biz](/url/ &quot;Title with &quot;quote&quot; inside&quot;).&#10;">
+ <outline text="Reference" _note="Foo [bar](/url/).&#10;&#10;Foo [bar](/url/).&#10;&#10;Foo [bar](/url/).&#10;&#10;With [embedded [brackets]](/url/).&#10;&#10;[b](/url/) by itself should be a link.&#10;&#10;Indented [once](/url).&#10;&#10;Indented [twice](/url).&#10;&#10;Indented [thrice](/url).&#10;&#10;This should [not][] be a link.&#10;&#10; [not]: /url&#10;&#10;Foo [bar](/url/ &quot;Title with &quot;quotes&quot; inside&quot;).&#10;&#10;Foo [biz](/url/ &quot;Title with &quot;quote&quot; inside&quot;).">
</outline>
- <outline text="With ampersands" _note="Here’s a [link with an ampersand in the&#10;URL](http://example.com/?foo=1&amp;bar=2).&#10;&#10;Here’s a link with an amersand in the link text:&#10;[AT&amp;T](http://att.com/ &quot;AT&amp;T&quot;).&#10;&#10;Here’s an [inline link](/script?foo=1&amp;bar=2).&#10;&#10;Here’s an [inline link in pointy braces](/script?foo=1&amp;bar=2).&#10;">
+ <outline text="With ampersands" _note="Here’s a [link with an ampersand in the&#10;URL](http://example.com/?foo=1&amp;bar=2).&#10;&#10;Here’s a link with an amersand in the link text:&#10;[AT&amp;T](http://att.com/ &quot;AT&amp;T&quot;).&#10;&#10;Here’s an [inline link](/script?foo=1&amp;bar=2).&#10;&#10;Here’s an [inline link in pointy braces](/script?foo=1&amp;bar=2).">
</outline>
<outline text="Autolinks" _note="With an ampersand: &lt;http://example.com/?foo=1&amp;bar=2&gt;&#10;&#10;- In a list?&#10;- &lt;http://example.com/&gt;&#10;- It should.&#10;&#10;An e-mail address: &lt;nobody@nowhere.net&gt;&#10;&#10;&gt; Blockquoted: &lt;http://example.com/&gt;&#10;&#10;Auto-links should not occur here: `&lt;http://example.com/&gt;`&#10;&#10; or here: &lt;http://example.com/&gt;&#10;&#10;------------------------------------------------------------------------">
</outline>
</outline>
<outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902):&#10;&#10;![lalune](lalune.jpg &quot;Voyage dans la Lune&quot;)&#10;&#10;Here is a movie ![movie](movie.jpg) icon.&#10;&#10;------------------------------------------------------------------------">
</outline>
-<outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be&#10;a footnote reference, because it contains a space.[\^my note] Here is an&#10;inline note.[^3]&#10;&#10;&gt; Notes can go in quotes.[^4]&#10;&#10;1. And in list items.[^5]&#10;&#10;This paragraph should not be part of the note, as it is not indented.&#10;&#10;[^1]: Here is the footnote. It can go anywhere after the footnote&#10; reference. It need not be placed at the end of the document.&#10;&#10;[^2]: Here’s the long note. This one contains multiple blocks.&#10;&#10; Subsequent blocks are indented to show that they belong to the&#10; footnote (as with list items).&#10;&#10; { &lt;code&gt; }&#10;&#10; If you want, you can indent every line, but you can also be lazy and&#10; just indent the first line of each block.&#10;&#10;[^3]: This is *easier* to type. Inline notes may contain&#10; [links](http://google.com) and `]` verbatim characters, as well as&#10; [bracketed text].&#10;&#10;[^4]: In quote.&#10;&#10;[^5]: In list.&#10;">
+<outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be&#10;a footnote reference, because it contains a space.[\^my note] Here is an&#10;inline note.[^3]&#10;&#10;&gt; Notes can go in quotes.[^4]&#10;&#10;1. And in list items.[^5]&#10;&#10;This paragraph should not be part of the note, as it is not indented.&#10;&#10;[^1]: Here is the footnote. It can go anywhere after the footnote&#10; reference. It need not be placed at the end of the document.&#10;&#10;[^2]: Here’s the long note. This one contains multiple blocks.&#10;&#10; Subsequent blocks are indented to show that they belong to the&#10; footnote (as with list items).&#10;&#10; { &lt;code&gt; }&#10;&#10; If you want, you can indent every line, but you can also be lazy and&#10; just indent the first line of each block.&#10;&#10;[^3]: This is *easier* to type. Inline notes may contain&#10; [links](http://google.com) and `]` verbatim characters, as well as&#10; [bracketed text].&#10;&#10;[^4]: In quote.&#10;&#10;[^5]: In list.">
</outline>
</body>
</opml>
diff --git a/tests/writer.plain b/tests/writer.plain
index fab0489ac..0332a747b 100644
--- a/tests/writer.plain
+++ b/tests/writer.plain
@@ -499,8 +499,8 @@ LATEX
These shouldn’t be math:
- To get the famous equation, write $e = mc^2$.
-- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot” is
- emphasized.)
+- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot”
+ is emphasized.)
- Shoes ($20) and socks ($5).
- Escaped $: $73 _this should be emphasized_ 23$.
diff --git a/tests/writer.rst b/tests/writer.rst
index 1a998d2ae..1aeeacacb 100644
--- a/tests/writer.rst
+++ b/tests/writer.rst
@@ -10,6 +10,10 @@ Pandoc Test Suite
:format: html latex
..
+.. role:: raw-latex(raw)
+ :format: latex
+..
+
This is a set of tests for pandoc. Most of them are adapted from John Gruber’s
markdown test suite.
@@ -657,7 +661,7 @@ Ellipses…and…and….
LaTeX
=====
--
+- :raw-latex:`\cite[22-23]{smith.1899}`
- :math:`2+2=4`
- :math:`x \in y`
- :math:`\alpha \wedge \omega`
@@ -839,6 +843,7 @@ From “Voyage dans la Lune” by Georges Melies (1902):
:alt: Voyage dans la Lune
lalune
+
Here is a movie |movie| icon.
--------------
diff --git a/tests/writer.texinfo b/tests/writer.texinfo
index 7b59ea651..ca87da1a9 100644
--- a/tests/writer.texinfo
+++ b/tests/writer.texinfo
@@ -36,7 +36,8 @@ July 17, 2006
@node Top
@top Pandoc Test Suite
-This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite.
+This is a set of tests for pandoc. Most of them are adapted from John Gruber's
+markdown test suite.
@iftex
@bigskip@hrule@bigskip
@@ -125,11 +126,14 @@ with no blank line
@anchor{#paragraphs}
Here's a regular paragraph.
-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.
+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.
Here's one with a bullet. * criminey.
-There should be a hard line break@*here.
+There should be a hard line break@*
+here.
@iftex
@bigskip@hrule@bigskip
@@ -734,11 +738,14 @@ This is code: @code{>}, @code{$}, @code{\}, @code{\$}, @code{<html>}.
@textstrikeout{This is @emph{strikeout}.}
-Superscripts: a@textsuperscript{bc}d a@textsuperscript{@emph{hello}} a@textsuperscript{hello@ there}.
+Superscripts: a@textsuperscript{bc}d a@textsuperscript{@emph{hello}}
+a@textsuperscript{hello@ there}.
-Subscripts: H@textsubscript{2}O, H@textsubscript{23}O, H@textsubscript{many@ of@ them}O.
+Subscripts: H@textsubscript{2}O, H@textsubscript{23}O,
+H@textsubscript{many@ of@ them}O.
-These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.
+These should not be superscripts or subscripts, because of the unescaped
+spaces: a^b c^d, a~b c~d.
@iftex
@bigskip@hrule@bigskip
@@ -758,7 +765,8 @@ These should not be superscripts or subscripts, because of the unescaped spaces:
`He said, ``I want to go.''' Were you alive in the 70's?
-Here is some quoted `@code{code}' and a ``@uref{http://example.com/?foo=1&bar=2,quoted link}''.
+Here is some quoted `@code{code}' and a
+``@uref{http://example.com/?foo=1&bar=2,quoted link}''.
Some dashes: one---two --- three---four --- five.
@@ -792,7 +800,8 @@ Ellipses@dots{}and@dots{}and@dots{}.
@item
@math{p}-Tree
@item
-Here's some display math: @math{\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}}
+Here's some display math:
+@math{\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}}
@item
Here's one that has a line break in it: @math{\alpha + \omega \times x^2}.
@end itemize
@@ -803,7 +812,8 @@ These shouldn't be math:
@item
To get the famous equation, write @code{$e = mc^2$}.
@item
-$22,000 is a @emph{lot} of money. So is $34,000. (It worked if ``lot'' is emphasized.)
+$22,000 is a @emph{lot} of money. So is $34,000. (It worked if ``lot'' is
+emphasized.)
@item
Shoes ($20) and socks ($5).
@item
@@ -956,7 +966,8 @@ Foo @uref{/url/,biz}.
@node With ampersands
@section With ampersands
@anchor{#with-ampersands}
-Here's a @uref{http://example.com/?foo=1&bar=2,link with an ampersand in the URL}.
+Here's a @uref{http://example.com/?foo=1&bar=2,link with an ampersand in the
+URL}.
Here's a link with an amersand in the link text: @uref{http://att.com/,AT&T}.
@@ -1018,15 +1029,24 @@ Here is a movie @image{movie,,,movie,jpg} icon.
@node Footnotes
@chapter Footnotes
@anchor{#footnotes}
-Here is a footnote reference,@footnote{Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.} and another.@footnote{Here's the long note. This one contains multiple blocks.
+Here is a footnote reference,@footnote{Here is the footnote. It can go
+anywhere after the footnote reference. It need not be placed at the end of the
+document.} and another.@footnote{Here's the long note. This one contains
+multiple blocks.
-Subsequent blocks are indented to show that they belong to the footnote (as with list items).
+Subsequent blocks are indented to show that they belong to the footnote (as
+with list items).
@verbatim
{ <code> }
@end verbatim
-If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.} This should @emph{not} be a footnote reference, because it contains a space.[^my note] Here is an inline note.@footnote{This is @emph{easier} to type. Inline notes may contain @uref{http://google.com,links} and @code{]} verbatim characters, as well as [bracketed text].}
+If you want, you can indent every line, but you can also be lazy and just
+indent the first line of each block.} This should @emph{not} be a footnote
+reference, because it contains a space.[^my note] Here is an inline
+note.@footnote{This is @emph{easier} to type. Inline notes may contain
+@uref{http://google.com,links} and @code{]} verbatim characters, as well as
+[bracketed text].}
@quotation
Notes can go in quotes.@footnote{In quote.}