aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Lua.hs19
-rw-r--r--test/Tests/Readers/HTML.hs25
-rw-r--r--test/Tests/Readers/Markdown.hs12
-rw-r--r--test/Tests/Readers/Muse.hs85
-rw-r--r--test/Tests/Readers/Org/Block/Header.hs38
-rw-r--r--test/Tests/Readers/Org/Block/List.hs11
-rw-r--r--test/Tests/Readers/Org/Directive.hs23
-rw-r--r--test/Tests/Readers/Org/Inline.hs9
-rw-r--r--test/Tests/Readers/RST.hs16
-rw-r--r--test/Tests/Writers/HTML.hs5
-rw-r--r--test/Tests/Writers/Muse.hs94
-rw-r--r--test/Tests/Writers/RST.hs8
-rw-r--r--test/command/1126.md29
-rw-r--r--test/command/1710.md7
-rw-r--r--test/command/2118.md2
-rw-r--r--test/command/3407.md4
-rw-r--r--test/command/3432.md2
-rw-r--r--test/command/3534.md22
-rw-r--r--test/command/3558.md4
-rw-r--r--test/command/3716.md2
-rw-r--r--test/command/3804.md2
-rw-r--r--test/command/3947.md2
-rw-r--r--test/command/4016.md4
-rw-r--r--test/command/4056.md2
-rw-r--r--test/command/4159.md2
-rw-r--r--test/command/4284.md40
-rw-r--r--test/command/4528.md156
-rw-r--r--test/command/4545.md20
-rw-r--r--test/command/4553.md15
-rw-r--r--test/command/4624.md30
-rw-r--r--test/command/4653.md8
-rw-r--r--test/command/4667.md20
-rw-r--r--test/command/4669.md29
-rw-r--r--test/command/4677.md8
-rw-r--r--test/command/4690.md28
-rw-r--r--test/command/4722.md34
-rw-r--r--test/command/4742.md25
-rw-r--r--test/command/4743.md25
-rw-r--r--test/command/4748.md16
-rw-r--r--test/command/4768.md7
-rw-r--r--test/command/4781.md22
-rw-r--r--test/command/4794.md18
-rw-r--r--test/command/4811.md48
-rw-r--r--test/command/4817.md10
-rw-r--r--test/command/4819.md50
-rw-r--r--test/command/4832.md21
-rw-r--r--test/command/4833.md20
-rw-r--r--test/command/4842.md6
-rw-r--r--test/command/4845.md6
-rw-r--r--test/command/4848.md59
-rw-r--r--test/command/4860.md9
-rw-r--r--test/command/4877.md13
-rw-r--r--test/command/4885.md8
-rw-r--r--test/command/4908.md16
-rw-r--r--test/command/4913.md34
-rw-r--r--test/command/4919.md14
-rw-r--r--test/command/4928.md48
-rw-r--r--test/command/adjacent_latex_blocks.md4
-rw-r--r--test/command/ascii.md45
-rw-r--r--test/command/bar.tex1
-rw-r--r--test/command/emoji.md27
-rw-r--r--test/command/empty-inline-code.txt6
-rw-r--r--test/command/gfm.md2
-rw-r--r--test/command/hspace.md6
-rw-r--r--test/command/macros.md8
-rw-r--r--test/command/refs.md47
-rw-r--r--test/command/write18.md2
-rw-r--r--test/command/yaml-metadata-blocks.md63
-rw-r--r--test/command/yaml-metadata.yaml4
-rw-r--r--test/docbook-xref.native2
-rw-r--r--test/fb2/meta.fb22
-rw-r--r--test/lhs-test.html10
-rw-r--r--test/lhs-test.html+lhs10
-rw-r--r--test/lua/test-pandoc-utils.lua15
-rw-r--r--test/markdown-reader-more.native17
-rw-r--r--test/pptx/lists.native2
-rw-r--r--test/pptx/lists.pptxbin26765 -> 26765 bytes
-rw-r--r--test/pptx/lists_templated.pptxbin394091 -> 394091 bytes
-rw-r--r--test/rst-reader.native2
-rw-r--r--test/tables-rstsubset.native8
-rw-r--r--test/tables.opendocument194
-rw-r--r--test/tables.rst60
-rw-r--r--test/testsuite.native10
-rw-r--r--test/textile-reader.native2
-rw-r--r--test/textile-reader.textile2
-rw-r--r--test/tikiwiki-reader.native58
-rw-r--r--test/txt2tags.t2t2
-rw-r--r--test/writer.context6
-rw-r--r--test/writer.docbook46
-rw-r--r--test/writer.docbook56
-rw-r--r--test/writer.fb22
-rw-r--r--test/writer.haddock14
-rw-r--r--test/writer.html42
-rw-r--r--test/writer.html54
-rw-r--r--test/writer.jats13
-rw-r--r--test/writer.muse77
-rw-r--r--test/writer.native10
-rw-r--r--test/writer.opendocument855
-rw-r--r--test/writer.org8
-rw-r--r--test/writer.rst82
-rw-r--r--test/writer.tei4
-rw-r--r--test/writer.texinfo24
-rw-r--r--test/writer.textile2
103 files changed, 2355 insertions, 663 deletions
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 28a691715..3fe9c1121 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -7,7 +7,7 @@ import Control.Monad (when)
import Data.Version (Version (versionBranch))
import System.FilePath ((</>))
import Test.Tasty (TestTree, localOption)
-import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
+import Test.Tasty.HUnit (Assertion, assertEqual, assertFailure, testCase)
import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty)
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
@@ -109,7 +109,8 @@ tests = map (localOption (QuickCheckTests 20))
assertFilterConversion "pandoc.utils doesn't work as expected."
"test-pandoc-utils.lua"
(doc $ para "doesn't matter")
- (doc $ mconcat [ plain (str "hierarchicalize: OK")
+ (doc $ mconcat [ plain (str "blocks_to_inlines: OK")
+ , plain (str "hierarchicalize: OK")
, plain (str "normalize_date: OK")
, plain (str "pipe: OK")
, plain (str "failing pipe: OK")
@@ -129,7 +130,7 @@ tests = map (localOption (QuickCheckTests 20))
, testCase "Pandoc version is set" . runPandocLua' $ do
Lua.getglobal' "table.concat"
Lua.getglobal "PANDOC_VERSION"
- Lua.push ("." :: String) -- seperator
+ Lua.push ("." :: String) -- separator
Lua.call 2 1
Lua.liftIO . assertEqual "pandoc version is wrong" pandocVersion
=<< Lua.peek Lua.stackTop
@@ -163,11 +164,11 @@ tests = map (localOption (QuickCheckTests 20))
, testCase "informative error messages" . runPandocLua' $ do
Lua.pushboolean True
- err <- Lua.peekEither Lua.stackTop :: Lua.Lua (Either String Pandoc)
- case err of
+ err <- Lua.peekEither Lua.stackTop
+ case (err :: Either String Pandoc) of
Left msg -> do
let expectedMsg = "Could not get Pandoc value: "
- ++ "expected table but got boolean."
+ <> "table expected, got boolean"
Lua.liftIO $ assertEqual "unexpected error message" expectedMsg msg
Right _ -> error "Getting a Pandoc element from a bool should fail."
]
@@ -178,13 +179,13 @@ assertFilterConversion msg filterPath docIn docExpected = do
setUserDataDir (Just "../data")
runLuaFilter def ("lua" </> filterPath) [] docIn
case docEither of
- Left _ -> fail "lua filter failed"
+ Left exception -> assertFailure (show exception)
Right docRes -> assertEqual msg docExpected docRes
-roundtripEqual :: (Eq a, Lua.FromLuaStack a, Lua.ToLuaStack a) => a -> IO Bool
+roundtripEqual :: (Eq a, Lua.Peekable a, Lua.Pushable a) => a -> IO Bool
roundtripEqual x = (x ==) <$> roundtripped
where
- roundtripped :: (Lua.FromLuaStack a, Lua.ToLuaStack a) => IO a
+ roundtripped :: (Lua.Peekable a, Lua.Pushable a) => IO a
roundtripped = runPandocLua' $ do
oldSize <- Lua.gettop
Lua.push x
diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs
index f61f1f497..eedb99029 100644
--- a/test/Tests/Readers/HTML.hs
+++ b/test/Tests/Readers/HTML.hs
@@ -4,11 +4,14 @@ module Tests.Readers.HTML (tests) where
import Prelude
import Data.Text (Text)
+import qualified Data.Text as T
import Test.Tasty
+import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import Text.Pandoc.Walk (walk)
html :: Text -> Pandoc
html = purely $ readHtml def
@@ -16,6 +19,27 @@ html = purely $ readHtml def
htmlNativeDivs :: Text -> Pandoc
htmlNativeDivs = purely $ readHtml def { readerExtensions = enableExtension Ext_native_divs $ readerExtensions def }
+makeRoundTrip :: Block -> Block
+makeRoundTrip CodeBlock{} = Para [Str "code block was here"]
+makeRoundTrip LineBlock{} = Para [Str "line block was here"]
+makeRoundTrip RawBlock{} = Para [Str "raw block was here"]
+makeRoundTrip x = x
+
+removeRawInlines :: Inline -> Inline
+removeRawInlines RawInline{} = Str "raw inline was here"
+removeRawInlines x = x
+
+roundTrip :: Blocks -> Bool
+roundTrip b = d'' == d'''
+ where d = walk removeRawInlines $
+ walk makeRoundTrip $ Pandoc nullMeta $ toList b
+ d' = rewrite d
+ d'' = rewrite d'
+ d''' = rewrite d''
+ rewrite = html . T.pack . (++ "\n") . T.unpack .
+ purely (writeHtml5String def
+ { writerWrapText = WrapPreserve })
+
tests :: [TestTree]
tests = [ testGroup "base tag"
[ test html "simple" $
@@ -53,4 +77,5 @@ tests = [ testGroup "base tag"
, test htmlNativeDivs "<main> followed by text" $ "<main>main content</main>non-main content" =?>
doc (divWith ("", [], [("role", "main")]) (plain (text "main content")) <> plain (text "non-main content"))
]
+ , testProperty "Round trip" (withMaxSuccess 25 roundTrip)
]
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index e44c7fc19..be89e708e 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -39,7 +39,7 @@ testBareLink (inp, ils) =
(unpack inp) (inp, doc $ para ils)
autolink :: String -> Inlines
-autolink = autolinkWith nullAttr
+autolink = autolinkWith ("",["uri"],[])
autolinkWith :: Attr -> String -> Inlines
autolinkWith attr s = linkWith attr s "" (str s)
@@ -72,10 +72,12 @@ bareLinkTests =
, ("http://en.wikipedia.org/wiki/Sprite_(computer_graphics)",
autolink "http://en.wikipedia.org/wiki/Sprite_(computer_graphics)")
, ("http://en.wikipedia.org/wiki/Sprite_[computer_graphics]",
- link "http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" ""
+ linkWith ("",["uri"],[])
+ "http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" ""
(str "http://en.wikipedia.org/wiki/Sprite_[computer_graphics]"))
, ("http://en.wikipedia.org/wiki/Sprite_{computer_graphics}",
- link "http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" ""
+ linkWith ("",["uri"],[])
+ "http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" ""
(str "http://en.wikipedia.org/wiki/Sprite_{computer_graphics}"))
, ("http://example.com/Notification_Center-GitHub-20101108-140050.jpg",
autolink "http://example.com/Notification_Center-GitHub-20101108-140050.jpg")
@@ -199,7 +201,9 @@ tests = [ testGroup "inline code"
]
, testGroup "emoji"
[ test markdownGH "emoji symbols" $
- ":smile: and :+1:" =?> para (text "😄 and 👍")
+ ":smile: and :+1:" =?> para (spanWith ("", ["emoji"], [("data-emoji", "smile")]) "😄" <>
+ space <> str "and" <> space <>
+ spanWith ("", ["emoji"], [("data-emoji", "+1")]) "👍")
]
, "unbalanced brackets" =:
"[[[[[[[[[[[[hi" =?> para (text "[[[[[[[[[[[[hi")
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index ecdd5fdb0..958a74915 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -39,9 +39,9 @@ makeRoundTrip x = x
-- Demand that any AST produced by Muse reader and written by Muse writer can be read back exactly the same way.
-- Currently we remove tables and compare first rewrite to the second.
-roundTrip :: Block -> Bool
+roundTrip :: Blocks -> Bool
roundTrip b = d' == d''
- where d = walk makeRoundTrip $ Pandoc nullMeta [b]
+ where d = walk makeRoundTrip $ Pandoc nullMeta $ toList b
d' = rewrite d
d'' = rewrite d'
rewrite = amuse . T.pack . (++ "\n") . T.unpack .
@@ -62,6 +62,14 @@ tests =
"*Foo bar*" =?>
para (emph . spcSep $ ["Foo", "bar"])
+ -- Emacs Muse allows this
+ , "Newline in the beginning of emphasis" =:
+ "*\nFoo bar*" =?>
+ para (emph ("Foo" <> space <> "bar"))
+ , "Newline in the end of emphasis" =:
+ "*Foo bar\n*" =?>
+ para (emph ("Foo" <> space <> "bar"))
+
, "Comma after closing *" =:
"Foo *bar*, baz" =?>
para ("Foo " <> emph "bar" <> ", baz")
@@ -74,6 +82,10 @@ tests =
"Foo x*bar* baz" =?>
para "Foo x*bar* baz"
+ , "Digit after closing *" =:
+ "Foo *bar*0 baz" =?>
+ para "Foo *bar*0 baz"
+
, "Emphasis tag" =:
"<em>Foo bar</em>" =?>
para (emph . spcSep $ ["Foo", "bar"])
@@ -138,6 +150,10 @@ tests =
"Foo =bar=, baz" =?>
para (text "Foo " <> code "bar" <> text ", baz")
+ , "Not code if followed by digit" =:
+ "Foo =bar=0 baz" =?>
+ para (text "Foo =bar=0 baz")
+
, "One character code" =: "=c=" =?> para (code "c")
, "Three = characters is not a code" =: "===" =?> para "==="
@@ -194,9 +210,27 @@ tests =
, "Image" =:
"[[image.jpg]]" =?>
para (image "image.jpg" "" mempty)
+ , "Closing bracket is not allowed in image filename" =:
+ "[[foo]bar.jpg]]" =?>
+ para (text "[[foo]bar.jpg]]")
, "Image with description" =:
"[[image.jpg][Image]]" =?>
para (image "image.jpg" "" (text "Image"))
+ , "Image with space in filename" =:
+ "[[image name.jpg]]" =?>
+ para (image "image name.jpg" "" mempty)
+ , "Image with width" =:
+ "[[image.jpg 60]]" =?>
+ para (imageWith ("", [], [("width", "60%")]) "image.jpg" mempty mempty)
+ , "At least one space is required between image filename and width" =:
+ "[[image.jpg60]]" =?>
+ para (link "image.jpg60" mempty (str "image.jpg60"))
+ , "Left-aligned image with width" =:
+ "[[image.png 60 l][Image]]" =?>
+ para (imageWith ("", ["align-left"], [("width", "60%")]) "image.png" "" (str "Image"))
+ , "Right-aligned image with width" =:
+ "[[image.png 60 r][Image]]" =?>
+ para (imageWith ("", ["align-right"], [("width", "60%")]) "image.png" "" (str "Image"))
, "Image link" =:
"[[URL:image.jpg]]" =?>
para (link "image.jpg" "" (str "image.jpg"))
@@ -225,8 +259,8 @@ tests =
]
]
- , testGroup "Blocks" $
- [ testProperty "Round trip" roundTrip
+ , testGroup "Blocks"
+ [ testProperty "Round trip" (withMaxSuccess 25 roundTrip)
, "Block elements end paragraphs" =:
T.unlines [ "First paragraph"
, "----"
@@ -385,6 +419,12 @@ tests =
, "</verse>"
] =?>
lineBlock [ "" ]
+ , "Verse tag with verbatim close tag inside" =:
+ T.unlines [ "<verse>"
+ , "<verbatim></verse></verbatim>"
+ , "</verse>"
+ ] =?>
+ lineBlock [ "</verse>" ]
, testGroup "Example"
[ "Braces on separate lines" =:
T.unlines [ "{{{"
@@ -589,6 +629,18 @@ tests =
T.unlines [ "* Foo"
, "bar"
] =?> header 1 "Foo\nbar"
+ , test (purely $ readMuse def { readerExtensions = extensionsFromList [Ext_amuse, Ext_auto_identifiers]})
+ "Auto identifiers"
+ (T.unlines [ "* foo"
+ , "** Foo"
+ , "* bar"
+ , "** foo"
+ , "* foo"
+ ] =?> headerWith ("foo",[],[]) 1 "foo" <>
+ headerWith ("foo-1",[],[]) 2 "Foo" <>
+ headerWith ("bar",[],[]) 1 "bar" <>
+ headerWith ("foo-2",[],[]) 2 "foo" <>
+ headerWith ("foo-3",[],[]) 1 "foo")
]
, testGroup "Directives"
[ "Title" =:
@@ -710,6 +762,13 @@ tests =
, " > Baz"
] =?>
para ("Foo" <> note (para "Bar" <> lineBlock ["Baz"]))
+ , "Footnote ending in self-terminating element and followed by paragraph" =:
+ T.unlines [ "Foo[1]"
+ , ""
+ , "[1] > bar"
+ , "baz"
+ ] =?>
+ para (str "Foo" <> note (lineBlock ["bar"])) <> para (str "baz")
, test emacsMuse "Emacs multiparagraph footnotes"
(T.unlines
[ "First footnote reference[1] and second footnote reference[2]."
@@ -798,6 +857,14 @@ tests =
[plain "Foo", plain "bar", plain "baz"]
[[plain "First", plain "row", plain "here"],
[plain "Second", plain "row", plain "there"]]
+ , "Table caption with +" =:
+ T.unlines
+ [ "Foo | bar"
+ , "|+ Table + caption +|"
+ ] =?>
+ table (text "Table + caption") (replicate 2 (AlignDefault, 0.0))
+ []
+ [[plain "Foo", plain "bar"]]
, "Caption without table" =:
"|+ Foo bar baz +|" =?>
table (text "Foo bar baz") [] [] []
@@ -972,7 +1039,7 @@ tests =
, para "c"
]
]
- , "List continuation afeter nested list" =:
+ , "List continuation after nested list" =:
T.unlines
[ " - - foo"
, ""
@@ -1118,6 +1185,11 @@ tests =
] =?>
bulletList [ lineBlock [ "foo" ] ] <> bulletList [ para "bar" ]
]
+ , "List ending in self-terminating element and followed by paragraph" =:
+ T.unlines [ " - > Foo"
+ , "bar"
+ ] =?>
+ bulletList [lineBlock ["Foo"]] <> para (str "bar")
-- Test that definition list requires a leading space.
-- Emacs Muse does not require a space, we follow Amusewiki here.
, "Not a definition list" =:
@@ -1335,7 +1407,8 @@ tests =
, " <verse>"
, " </quote>"
, " </verse>"
+ , "</quote>"
] =?>
- para "<quote>" <> bulletList [ para "Foo" <> para "</quote>" <> para "bar" <> lineBlock [ "</quote>" ] ]
+ blockQuote (bulletList [ para "Foo" <> para "</quote>" <> para "bar" <> lineBlock [ "</quote>" ] ])
]
]
diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs
index 3b0d7dda9..913c830d6 100644
--- a/test/Tests/Readers/Org/Block/Header.hs
+++ b/test/Tests/Readers/Org/Block/Header.hs
@@ -181,4 +181,42 @@ tests =
, " :END:"
] =?>
headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered"
+
+ , testGroup "planning information"
+ [ "Planning info is not included in output" =:
+ T.unlines [ "* important"
+ , T.unwords
+ [ "CLOSED: [2018-09-05 Wed 13:58]"
+ , "DEADLINE: <2018-09-17 Mon>"
+ , "SCHEDULED: <2018-09-10 Mon>"
+ ]
+ ] =?>
+ headerWith ("important", [], []) 1 "important"
+
+ , "Properties after planning info are recognized" =:
+ T.unlines [ "* important "
+ , " " <> T.unwords
+ [ "CLOSED: [2018-09-05 Wed 13:58]"
+ , "DEADLINE: <2018-09-17 Mon>"
+ , "SCHEDULED: <2018-09-10 Mon>"
+ ]
+ , " :PROPERTIES:"
+ , " :custom_id: look"
+ , " :END:"
+ ] =?>
+ headerWith ("look", [], []) 1 "important"
+
+ , "Planning info followed by test" =:
+ T.unlines [ "* important "
+ , " " <> T.unwords
+ [ "CLOSED: [2018-09-05 Wed 13:58]"
+ , "DEADLINE: <2018-09-17 Mon>"
+ , "SCHEDULED: <2018-09-10 Mon>"
+ ]
+ , " :PROPERTIES:"
+ , " :custom_id: look"
+ , " :END:"
+ ] =?>
+ headerWith ("look", [], []) 1 "important"
+ ]
]
diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs
index f273b684d..bdab01404 100644
--- a/test/Tests/Readers/Org/Block/List.hs
+++ b/test/Tests/Readers/Org/Block/List.hs
@@ -243,4 +243,15 @@ tests =
mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]"
, bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ]
]
+
+ , "Markup after header and list" =:
+ T.unlines [ "* headline"
+ , "- list"
+ , ""
+ , "~variable name~"
+ ] =?>
+ mconcat [ headerWith ("headline", [], []) 1 "headline"
+ , bulletList [ plain "list" ]
+ , para (code "variable name")
+ ]
]
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index bb9c52e69..87abb714d 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -150,6 +150,29 @@ tests =
, "* Headline :hello:world:"
] =?>
headerWith ("headline", [], mempty) 1 "Headline"
+
+ , testGroup "planning information"
+ [ "include planning info after headlines" =:
+ T.unlines [ "#+OPTIONS: p:t"
+ , "* important"
+ , " DEADLINE: <2018-10-01 Mon> SCHEDULED: <2018-09-15 Sat>"
+ ] =?>
+ mconcat [ headerWith ("important", mempty, mempty) 1 "important"
+ , plain $ strong "DEADLINE:"
+ <> space
+ <> emph (str "<2018-10-01 Mon>")
+ <> space
+ <> strong "SCHEDULED:"
+ <> space
+ <> emph (str "<2018-09-15 Sat>")
+ ]
+
+ , "empty planning info is not included" =:
+ T.unlines [ "#+OPTIONS: p:t"
+ , "* Wichtig"
+ ] =?>
+ headerWith ("wichtig", mempty, mempty) 1 "Wichtig"
+ ]
]
, testGroup "Include"
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index 07fe2d2e9..9cfcda79f 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -96,7 +96,7 @@ tests =
"[fn::Schreib mir eine E-Mail]" =?>
para (note $ para "Schreib mir eine E-Mail")
- , "Markup-chars not occuring on word break are symbols" =:
+ , "Markup-chars not occurring on word break are symbols" =:
T.unlines [ "this+that+ +so+on"
, "seven*eight* nine*"
, "+not+funny+"
@@ -280,6 +280,13 @@ tests =
)
"echo 'Hello, World'")
+ , "Inline code block with a blank argument array" =:
+ "src_sh[]{echo 'Hello, World'}" =?>
+ para (codeWith ( ""
+ , [ "bash" ]
+ , [ ("org-language", "sh") ])
+ "echo 'Hello, World'")
+
, "Inline code block with toggle" =:
"src_sh[:toggle]{echo $HOME}" =?>
para (codeWith ( ""
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index 906ed4ff9..963e7530d 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -177,7 +177,7 @@ tests = [ "line block with blank line" =:
=: ".. role:: haskell(code)\n.. role:: lhs(haskell)\n\n:lhs:`text`"
=?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text")
, "unknown role" =: ":unknown:`text`" =?>
- para (spanWith ("",[],[("role","unknown")]) (str "text"))
+ para (codeWith ("",["interpreted-text"],[("role","unknown")]) "text")
]
, testGroup "footnotes"
[ "remove space before note" =: T.unlines
@@ -188,4 +188,18 @@ tests = [ "line block with blank line" =:
] =?>
para ("foo" <> note (para "bar"))
]
+ , testGroup "inlines"
+ [ "links can contain an URI without being parsed twice (#4581)" =:
+ "`http://loc <http://loc>`__" =?>
+ para (link "http://loc" "" "http://loc")
+ , "inline markup cannot be nested" =:
+ "**a*b*c**" =?>
+ para (strong "a*b*c")
+ , "bare URI parsing disabled inside emphasis (#4561)" =:
+ "*http://location*" =?>
+ para (emph (text "http://location"))
+ , "include newlines" =:
+ "**before\nafter**" =?>
+ para (strong (text "before\nafter"))
+ ]
]
diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs
index e771255b3..dfacda608 100644
--- a/test/Tests/Writers/HTML.hs
+++ b/test/Tests/Writers/HTML.hs
@@ -43,4 +43,9 @@ tests = [ testGroup "inline code"
image "/url" "title" ("my " <> emph "image")
=?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
]
+ , testGroup "blocks"
+ [ "definition list with empty <dt>" =:
+ definitionList [(mempty, [para $ text "foo bar"])]
+ =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
+ ]
]
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index 50c0e78eb..f7287d57d 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -275,7 +275,7 @@ tests = [ testGroup "block elements"
unlines [ "#bar"
, "** Foo"
]
- , "empty heading" =: header 4 (mempty) =?> "**** <verbatim></verbatim>"
+ , "empty heading" =: header 4 mempty =?> "**** <verbatim></verbatim>"
]
, "horizontal rule" =: horizontalRule =?> "----"
, "escape horizontal rule" =: para (text "----") =?> "<verbatim></verbatim>----"
@@ -283,6 +283,7 @@ tests = [ testGroup "block elements"
, "don't escape horizontal inside paragraph" =: para (text "foo ---- bar") =?> "foo ---- bar"
, "escape nonbreaking space" =: para (text "~~") =?> "<verbatim>~~</verbatim>"
, "escape > in the beginning of line" =: para (text "> foo bar") =?> "<verbatim></verbatim>> foo bar"
+ , "escape string with > and space in the beginning of line" =: para (str "> foo bar") =?> "<verbatim></verbatim>> foo bar"
, testGroup "tables"
[ "table without header" =:
let rows = [[para $ text "Para 1.1", para $ text "Para 1.2"]
@@ -341,36 +342,95 @@ tests = [ testGroup "block elements"
, "do not escape colon" =: str ":" =?> ":"
, "escape - to avoid accidental unordered lists" =: text " - foo" =?> "<verbatim></verbatim> - foo"
, "escape - inside a list to avoid accidental nested unordered lists" =:
- bulletList [ (para $ text "foo") <>
- (para $ text "- bar")
+ bulletList [ para (text "foo") <>
+ para (text "- bar")
] =?>
unlines [ " - foo"
, ""
, " <verbatim></verbatim>- bar"
]
+ , "escape strings starting with - inside a list" =:
+ bulletList [ para (str "foo") <>
+ para (str "- bar")
+ ] =?>
+ unlines [ " - foo"
+ , ""
+ , " <verbatim></verbatim>- bar"
+ ]
+ , "escape - inside a note" =:
+ note (para (text "- foo")) =?>
+ unlines [ "[1]"
+ , ""
+ , "[1] <verbatim></verbatim>- foo"
+ ]
+ , "escape - after softbreak in note" =:
+ note (para (str "foo" <> softbreak <> str "- bar")) =?>
+ unlines [ "[1]"
+ , ""
+ , "[1] foo"
+ , " <verbatim></verbatim>- bar"
+ ]
, "escape ; to avoid accidental comments" =: text "; foo" =?> "<verbatim></verbatim>; foo"
+ , "escape strings starting with ; and space" =: str "; foo" =?> "<verbatim></verbatim>; foo"
, "escape ; after softbreak" =: text "foo" <> softbreak <> text "; bar" =?> "foo\n<verbatim></verbatim>; bar"
, "escape ; after linebreak" =: text "foo" <> linebreak <> text "; bar" =?> "foo<br>\n<verbatim></verbatim>; bar"
, "do not escape ; inside paragraph" =: text "foo ; bar" =?> "foo ; bar"
+ , "escape newlines" =: str "foo\nbar" =?> "foo bar"
]
, testGroup "emphasis"
- [ "emph" =: emph (text "foo") =?> "<em>foo</em>"
- , "strong" =: strong (text "foo") =?> "<strong>foo</strong>"
+ [ "emphasis" =: emph (text "foo") =?> "*foo*"
+ , "emphasis inside word" =: text "foo" <> emph (text "bar") <> text "baz" =?> "foo<em>bar</em>baz"
+ , "emphasis before comma" =: emph (text "foo") <> text ", bar" =?> "*foo*, bar"
+ , "emphasis before period" =: emph (text "foobar") <> text "." =?> "*foobar*."
+ , "empty emphasis" =: emph mempty =?> "<em></em>"
+ , "empty strong" =: strong mempty =?> "<strong></strong>"
+ , "empty strong emphasis" =: strong (emph mempty) =?> "**<em></em>**"
+ , "empty emphasized strong" =: emph (strong mempty) =?> "*<strong></strong>*"
+ , "emphasized empty string" =: emph (str "") =?> "<em></em>"
+ , "strong empty string" =: strong (str "") =?> "<strong></strong>"
+ , "strong emphasized empty string" =: strong (emph (str "")) =?> "**<em></em>**"
+ , "emphasized strong empty string" =: emph (strong (str "")) =?> "*<strong></strong>*"
+ , "emphasized string with space" =: emph (str " ") =?> "<em> </em>"
+ , "emphasized string ending with space" =: emph (str "foo ") =?> "<em>foo </em>"
+ , "emphasized string with tab" =: emph (str "\t") =?> "<em>\t</em>"
+ , "emphasized space between empty strings" =: emph (str "" <> space <> str "") =?> "<em> </em>"
+ , "strong" =: strong (text "foo") =?> "**foo**"
+ , "strong inside word" =: text "foo" <> strong (text "bar") <> text "baz" =?> "foo<strong>bar</strong>baz"
+ , "strong emphasis" =: strong (emph (text "foo")) =?> "***foo***"
+ , "strong after emphasis" =: emph (text "foo") <> strong (text "bar") =?> "*foo*<strong>bar</strong>"
+ , "strong emphasis after emphasis" =: emph (text "foo") <> strong (emph (text "bar")) =?> "*foo*<strong>*bar*</strong>"
+ , "strong in the end of emphasis" =: emph (text "foo" <> strong (text "bar")) =?> "*foo<strong>bar</strong>*"
, "strikeout" =: strikeout (text "foo") =?> "<del>foo</del>"
+ , "space at the beginning of emphasis" =: emph (text " foo") =?> "<em> foo</em>"
+ , "space at the end of emphasis" =: emph (text "foo ") =?> "<em>foo </em>"
+ , "space at the beginning of strong" =: strong (text " foo") =?> "<strong> foo</strong>"
+ , "space at the end of strong" =: strong (text "foo ") =?> "<strong>foo </strong>"
+ , "space at the beginning of strong emphasis" =: strong (emph (text " foo")) =?> "**<em> foo</em>**"
+ , "space at the end of strong emphasis" =: strong (emph (text "foo ")) =?> "**<em>foo </em>**"
+ , "space at the beginning of emphasiszed strong" =: emph (strong (text " foo")) =?> "*<strong> foo</strong>*"
+ , "space at the end of emphasized strong" =: emph (strong (text "foo ")) =?> "*<strong>foo </strong>*"
]
, "superscript" =: superscript (text "foo") =?> "<sup>foo</sup>"
, "subscript" =: subscript (text "foo") =?> "<sub>foo</sub>"
- , "smallcaps" =: smallcaps (text "foo") =?> "<em>foo</em>"
- , "smallcaps near emphasis" =: emph (str "foo") <> smallcaps (str "bar") =?> "<em>foobar</em>"
+ , "smallcaps" =: smallcaps (text "foo") =?> "*foo*"
+ , "smallcaps near emphasis" =: emph (str "foo") <> smallcaps (str "bar") =?> "*foobar*"
, "single quoted" =: singleQuoted (text "foo") =?> "‘foo’"
, "double quoted" =: doubleQuoted (text "foo") =?> "“foo”"
-- Cite is trivial
, testGroup "code"
- [ "simple" =: code "foo" =?> "<code>foo</code>"
+ [ "simple" =: code "foo" =?> "=foo="
+ , "empty" =: code "" =?> "<code></code>"
+ , "space" =: code " " =?> "<code> </code>"
+ , "space at the beginning" =: code " foo" =?> "<code> foo</code>"
+ , "space at the end" =: code "foo " =?> "<code>foo </code>"
+ , "use tags for =" =: code "foo = bar" =?> "<code>foo = bar</code>"
, "escape tag" =: code "<code>foo = bar</code> baz" =?> "<code><code>foo = bar<</code><code>/code> baz</code>"
- , "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "<code>foobar</code>"
- , "normalization" =: code "</co" <> code "de>" =?> "<code><</code><code>/code></code>"
- , "normalization with empty string" =: code "</co" <> str "" <> code "de>" =?> "<code><</code><code>/code></code>"
+ , "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "=foobar="
+ , "code tag" =: code "<code>foo</code>" =?> "=<code>foo</code>="
+ , "normalization" =: code "</co" <> code "de>" <> code "=" =?> "<code><</code><code>/code>=</code>"
+ , "normalization with empty string" =: code "</co" <> str "" <> code "de>" <> code "=" =?> "<code><</code><code>/code>=</code>"
+ , "emphasized code" =: emph (code "foo") =?> "*=foo=*"
+ , "strong code" =: strong (code "foo") =?> "**=foo=**"
]
, testGroup "spaces"
[ "space" =: text "a" <> space <> text "b" =?> "a b"
@@ -385,7 +445,7 @@ tests = [ testGroup "block elements"
, testGroup "math"
[ "inline math" =: math "2^3" =?> "2<sup>3</sup>"
, "display math" =: displayMath "2^3" =?> "2<sup>3</sup>"
- , "multiple letters in inline math" =: math "abc" =?> "<em>abc</em>"
+ , "multiple letters in inline math" =: math "abc" =?> "*abc*"
, "expand math before normalization" =: math "[" <> str "2]" =?> "<verbatim>[2]</verbatim>"
, "multiple math expressions inside one inline list" =: math "5_4" <> text ", " <> displayMath "3^2" =?> "5<sub>4</sub>, 3<sup>2</sup>"
]
@@ -441,11 +501,11 @@ tests = [ testGroup "block elements"
=?> "<class name=\"foobar\">Some text</class>"
, "span without class" =: spanWith ("",[],[]) (text "Some text")
=?> "<class>Some text</class>"
- , "span with anchor" =: spanWith ("anchor", [], []) (mempty) <> (text "Foo bar")
+ , "span with anchor" =: spanWith ("anchor", [], []) mempty <> text "Foo bar"
=?> "#anchor Foo bar"
- , "empty span with anchor" =: spanWith ("anchor", [], []) (mempty)
+ , "empty span with anchor" =: spanWith ("anchor", [], []) mempty
=?> "#anchor"
- , "empty span without class and anchor" =: spanWith ("", [], []) (mempty)
+ , "empty span without class and anchor" =: spanWith ("", [], []) mempty
=?> "<class></class>"
, "span with class and anchor" =: spanWith ("anchor", ["foo"], []) (text "bar")
=?> "#anchor <class name=\"foo\">bar</class>"
@@ -461,7 +521,7 @@ tests = [ testGroup "block elements"
"<em>foo</em>bar"
, "emph quoted" =:
para (doubleQuoted (emph (text "foo"))) =?>
- "“<em>foo</em>”"
+ "“*foo*”"
, "strong word before" =:
para (text "foo" <> strong (text "bar")) =?>
"foo<strong>bar</strong>"
@@ -470,7 +530,7 @@ tests = [ testGroup "block elements"
"<strong>foo</strong>bar"
, "strong quoted" =:
para (singleQuoted (strong (text "foo"))) =?>
- "‘<strong>foo</strong>’"
+ "‘**foo**’"
]
]
]
diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs
index a1a4510e0..0d5b7c38a 100644
--- a/test/Tests/Writers/RST.hs
+++ b/test/Tests/Writers/RST.hs
@@ -16,6 +16,11 @@ infix 4 =:
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeRST def . toPandoc))
+testTemplate :: (ToString a, ToString c, ToPandoc a) =>
+ String -> String -> (a, c) -> TestTree
+testTemplate t =
+ test (purely (writeRST def{ writerTemplate = Just t }) . toPandoc)
+
tests :: [TestTree]
tests = [ testGroup "rubrics"
[ "in list item" =:
@@ -156,4 +161,7 @@ tests = [ testGroup "rubrics"
, "Header 2"
, "--------"]
]
+ , testTemplate "$subtitle$\n" "subtitle" $
+ (setMeta "subtitle" ("subtitle" :: Inlines) $ doc $ plain "") =?>
+ ("subtitle" :: String)
]
diff --git a/test/command/1126.md b/test/command/1126.md
new file mode 100644
index 000000000..014a8ae2d
--- /dev/null
+++ b/test/command/1126.md
@@ -0,0 +1,29 @@
+```
+% pandoc -f html -t latex
+\begin{eqnarray}
+A&=&B,\\
+C&=&D
+\end{eqnarray}
+^D
+\textbackslash{}begin\{eqnarray\}
+A\&=\&B,\textbackslash{}\textbackslash{} C\&=\&D
+\textbackslash{}end\{eqnarray\}
+```
+
+```
+% pandoc -f html+raw_tex -t latex
+<p>See \eqref{myeq}.</p>
+\begin{eqnarray}
+A&=&B,\\
+C&amp;=&amp;D
+\\label{myeq}
+\end{eqnarray}
+^D
+See \eqref{myeq}.
+
+\begin{eqnarray}
+A&=&B,\\
+C&=&D
+\\label{myeq}
+\end{eqnarray}
+```
diff --git a/test/command/1710.md b/test/command/1710.md
index d20dfe191..4d9c64b30 100644
--- a/test/command/1710.md
+++ b/test/command/1710.md
@@ -58,7 +58,7 @@ ok
\protect\hypertarget{slide-one}{}
\begin{columns}[T]
-\begin{column}{0.40\textwidth}
+\begin{column}{0.4\textwidth}
\begin{itemize}
\tightlist
\item
@@ -68,7 +68,7 @@ ok
\end{itemize}
\end{column}
-\begin{column}{0.40\textwidth}
+\begin{column}{0.4\textwidth}
\begin{itemize}
\tightlist
\item
@@ -78,11 +78,10 @@ ok
\end{itemize}
\end{column}
-\begin{column}{0.10\textwidth}
+\begin{column}{0.1\textwidth}
ok
\end{column}
\end{columns}
\end{frame}
```
-
diff --git a/test/command/2118.md b/test/command/2118.md
index 27b3723d3..9730dd383 100644
--- a/test/command/2118.md
+++ b/test/command/2118.md
@@ -7,5 +7,5 @@
\label{fig:setminus}
\end{figure}
^D
-[Para [Image ("",[],[("width","80%")]) [Str "Set",Space,Str "subtraction",Span ("",[],[("label","fig:setminus")]) []] ("setminus.png","fig:")]]
+[Para [Image ("fig:setminus",[],[("width","80%")]) [Str "Set",Space,Str "subtraction",Span ("",[],[("label","fig:setminus")]) []] ("setminus.png","fig:")]]
```
diff --git a/test/command/3407.md b/test/command/3407.md
index 3160d1263..aec253ff5 100644
--- a/test/command/3407.md
+++ b/test/command/3407.md
@@ -1,6 +1,6 @@
```
% pandoc -f native -t rst
-[Para [Span ("",[],[("role","foo")]) [Str "text"]]]
+[Para [Code ("",["interpreted-text"],[("role","foo")]) "text"]]
^D
:foo:`text`
```
@@ -9,5 +9,5 @@
% pandoc -f rst -t native
:foo:`text`
^D
-[Para [Span ("",[],[("role","foo")]) [Str "text"]]]
+[Para [Code ("",["interpreted-text"],[("role","foo")]) "text"]]
```
diff --git a/test/command/3432.md b/test/command/3432.md
index 7264d22c3..381f8af87 100644
--- a/test/command/3432.md
+++ b/test/command/3432.md
@@ -195,7 +195,7 @@ List-table without header-rows.
</table>
```
-List-table with empty cells. You need a space after '-', otherwise the row will disapear. Parser for Bulletlists causes this ristriction.
+List-table with empty cells. You need a space after '-', otherwise the row will disappear. Parser for Bulletlists causes this restriction.
```
% pandoc -f rst
diff --git a/test/command/3534.md b/test/command/3534.md
index 89224551b..cd0915d88 100644
--- a/test/command/3534.md
+++ b/test/command/3534.md
@@ -21,3 +21,25 @@ I want to explain the interface of \lstinline[language=Java]{public class MyClas
[Para [Str "I",Space,Str "want",Space,Str "to",Space,Str "explain",Space,Str "the",Space,Str "interface",Space,Str "of",Space,Code ("",["java"],[]) "public class MyClass",Str "."]]
```
+```
+% pandoc -f latex -t html
+I want to explain the interface of \mintinline{java}{public class MyClass}.
+^D
+<p>I want to explain the interface of <code class="sourceCode java"><span class="kw">public</span> <span class="kw">class</span> MyClass</code>.</p>
+
+```
+
+```
+% pandoc -f latex -t html
+I want to explain the interface of \mintinline{java}|public class MyClass|.
+^D
+<p>I want to explain the interface of <code class="sourceCode java"><span class="kw">public</span> <span class="kw">class</span> MyClass</code>.</p>
+
+```
+
+```
+% pandoc -f latex -t native
+I want to explain the interface of \mintinline[linenos]{java}{public class MyClass}.
+^D
+[Para [Str "I",Space,Str "want",Space,Str "to",Space,Str "explain",Space,Str "the",Space,Str "interface",Space,Str "of",Space,Code ("",["java"],[]) "public class MyClass",Str "."]]
+```
diff --git a/test/command/3558.md b/test/command/3558.md
index 795858b78..956b09e57 100644
--- a/test/command/3558.md
+++ b/test/command/3558.md
@@ -6,7 +6,7 @@ hello
\endmulti
^D
-[RawBlock (Format "latex") "\\multi"
+[RawBlock (Format "tex") "\\multi"
,Para [Str "hello"]
-,RawBlock (Format "latex") "\\endmulti"]
+,RawBlock (Format "tex") "\\endmulti"]
```
diff --git a/test/command/3716.md b/test/command/3716.md
index 7e00819da..81e4a9568 100644
--- a/test/command/3716.md
+++ b/test/command/3716.md
@@ -2,5 +2,5 @@
% pandoc
<http://example.com>{.foo}
^D
-<p><a href="http://example.com" class="uri foo">http://example.com</a></p>
+<p><a href="http://example.com" class="foo">http://example.com</a></p>
```
diff --git a/test/command/3804.md b/test/command/3804.md
index c13c2ef42..520d408df 100644
--- a/test/command/3804.md
+++ b/test/command/3804.md
@@ -2,5 +2,5 @@
% pandoc -t native
\titleformat{\chapter}[display]{\normalfont\large\bfseries}{第\thechapter{}章}{20pt}{\Huge}
^D
-[RawBlock (Format "latex") "\\titleformat{\\chapter}[display]{\\normalfont\\large\\bfseries}{\31532\\thechapter{}\31456}{20pt}{\\Huge}"]
+[RawBlock (Format "tex") "\\titleformat{\\chapter}[display]{\\normalfont\\large\\bfseries}{\31532\\thechapter{}\31456}{20pt}{\\Huge}"]
```
diff --git a/test/command/3947.md b/test/command/3947.md
index 7ce0be171..b1d695fbd 100644
--- a/test/command/3947.md
+++ b/test/command/3947.md
@@ -6,6 +6,6 @@
Another Code block
^D
-[RawBlock (Format "latex") "\\newpage"
+[RawBlock (Format "tex") "\\newpage"
,CodeBlock ("",[],[]) "Code block\n\nAnother Code block"]
```
diff --git a/test/command/4016.md b/test/command/4016.md
index 3918251c6..5e4e35e0d 100644
--- a/test/command/4016.md
+++ b/test/command/4016.md
@@ -17,7 +17,7 @@ pandoc -t beamer
\protect\hypertarget{level-2-blocks}{}
\begin{columns}[T]
-\begin{column}{0.40\textwidth}
+\begin{column}{0.4\textwidth}
\begin{block}{Block one}
\begin{itemize}
@@ -29,7 +29,7 @@ pandoc -t beamer
\end{block}
\end{column}
-\begin{column}{0.60\textwidth}
+\begin{column}{0.6\textwidth}
\begin{block}{Block two}
\begin{itemize}
diff --git a/test/command/4056.md b/test/command/4056.md
index eed4f6d6a..e972931dd 100644
--- a/test/command/4056.md
+++ b/test/command/4056.md
@@ -5,7 +5,7 @@
\end{shaded}
}
^D
-[RawBlock (Format "latex") "\\parbox[t]{0.4\\textwidth}{\n\\begin{shaded}\n\\end{shaded}\n}"]
+[RawBlock (Format "tex") "\\parbox[t]{0.4\\textwidth}{\n\\begin{shaded}\n\\end{shaded}\n}"]
```
```
diff --git a/test/command/4159.md b/test/command/4159.md
index 4881edcc5..d61959950 100644
--- a/test/command/4159.md
+++ b/test/command/4159.md
@@ -3,6 +3,6 @@
\newcommand{\gen}{a\ Gen\ b}
abc
^D
-[RawBlock (Format "latex") "\\newcommand{\\gen}{a\\ Gen\\ b}"
+[RawBlock (Format "tex") "\\newcommand{\\gen}{a\\ Gen\\ b}"
,Para [Str "abc"]]
```
diff --git a/test/command/4284.md b/test/command/4284.md
new file mode 100644
index 000000000..eddd1b03a
--- /dev/null
+++ b/test/command/4284.md
@@ -0,0 +1,40 @@
+```
+% pandoc -f org -t native
+#+EXCLUDE_TAGS:apple cat bye dog %
+
+* This should not appear :apple:
+* NOEXPORT should appear if not specified in EXCLUDE_TAGS :noexport:
+* This should not appear :cat:hi:laptop:
+** Children of headers with excluded tags should not appear :xylophone:
+* This should not appear :%:
+^D
+[Header 1 ("noexport-should-appear-if-not-specified-in-excludetags",[],[]) [Str "NOEXPORT",Space,Str "should",Space,Str "appear",Space,Str "if",Space,Str "not",Space,Str "specified",Space,Str "in",Space,Str "EXCLUDE",Subscript [Str "TAGS"],Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
+```
+
+```
+% pandoc -f org -t native
+#+EXCLUDE_TAGS:elephant
+* This should not appear :elephant:
+* This should appear :fawn:
+^D
+[Header 1 ("this-should-appear",[],[]) [Str "This",Space,Str "should",Space,Str "appear",Space,Span ("",["tag"],[("tag-name","fawn")]) [SmallCaps [Str "fawn"]]]]
+```
+
+```
+% pandoc -f org -t native
+#+EXCLUDE_TAGS: giraffe
+#+EXCLUDE_TAGS: hippo
+* This should not appear :giraffe:
+* This should not appear :hippo:
+* This should appear :noexport:
+^D
+[Header 1 ("this-should-appear",[],[]) [Str "This",Space,Str "should",Space,Str "appear",Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
+```
+
+```
+% pandoc -f org -t native
+#+EXCLUDE_TAGS:
+* NOEXPORT should appear if not specified in EXCLUDE_TAGS :noexport:
+^D
+[Header 1 ("noexport-should-appear-if-not-specified-in-excludetags",[],[]) [Str "NOEXPORT",Space,Str "should",Space,Str "appear",Space,Str "if",Space,Str "not",Space,Str "specified",Space,Str "in",Space,Str "EXCLUDE",Subscript [Str "TAGS"],Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
+```
diff --git a/test/command/4528.md b/test/command/4528.md
new file mode 100644
index 000000000..a60f6decf
--- /dev/null
+++ b/test/command/4528.md
@@ -0,0 +1,156 @@
+# Rendering small caps, superscripts and subscripts with and without `raw_html`
+
+## Small caps
+
+```
+% pandoc --wrap=none -f latex -t commonmark-raw_html
+This has \textsc{small caps} in it.
+^D
+This has SMALL CAPS in it.
+```
+
+```
+% pandoc --wrap=none -f latex -t commonmark+raw_html
+This has \textsc{small caps} in it.
+^D
+This has <span class="smallcaps">small caps</span> in it.
+```
+```
+
+```
+% pandoc --wrap=none -f latex -t markdown_strict+raw_html
+This has \textsc{small caps} in it.
+^D
+This has <span class="smallcaps">small caps</span> in it.
+```
+
+## Strikeout
+
+```
+% pandoc --wrap=none -f html -t commonmark-raw_html-strikeout
+This has <s>strikeout</s> in it.
+^D
+This has strikeout in it.
+
+```
+% pandoc --wrap=none -f html -t commonmark+raw_html-strikeout
+This has <s>strikeout</s> in it.
+^D
+This has <s>strikeout</s> in it.
+```
+
+```
+% pandoc --wrap=none -f html -t commonmark-raw_html+strikeout
+This has <s>strikeout</s> in it.
+^D
+This has ~~strikeout~~ in it.
+```
+
+```
+% pandoc --wrap=none -f html -t commonmark+raw_html+strikeout
+This has <s>strikeout</s> in it.
+^D
+This has ~~strikeout~~ in it.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict-raw_html-strikeout
+This has <s>strikeout</s> in it.
+^D
+This has strikeout in it.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict+raw_html-strikeout
+This has <s>strikeout</s> in it.
+^D
+This has <s>strikeout</s> in it.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict-raw_html+strikeout
+This has <s>strikeout</s> in it.
+^D
+This has ~~strikeout~~ in it.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict+raw_html+strikeout
+This has <s>strikeout</s> in it.
+^D
+This has ~~strikeout~~ in it.
+```
+
+## Superscript
+
+```
+% pandoc --wrap=none -f html -t commonmark-raw_html
+This has <sup>superscript</sup> in it and <sup>2 3</sup> again. With emphasis: <sup><em>2</em> 3</sup>. With letters: <sup>foo</sup>. With a span: <sup><span class=foo>2</span></sup>.
+^D
+This has ^(superscript) in it and ² ³ again. With emphasis: ^(*2* 3). With letters: ^(foo). With a span: ².
+```
+
+```
+% pandoc --wrap=none -f html -t commonmark+raw_html
+This has <sup>superscript</sup> in it and <sup>2</sup> again.
+^D
+This has <sup>superscript</sup> in it and <sup>2</sup> again.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict-raw_html-superscript
+This has <sup>superscript</sup> in it and <sup>2</sup> again.
+^D
+This has ^(superscript) in it and ² again.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict+raw_html-superscript
+This has <sup>superscript</sup> in it and <sup>2</sup> again.
+^D
+This has <sup>superscript</sup> in it and <sup>2</sup> again.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict+raw_html+superscript
+This has <sup>superscript</sup> in it and <sup>2</sup> again.
+^D
+This has ^superscript^ in it and ^2^ again.
+```
+
+## Subscript
+
+```
+% pandoc --wrap=none -f html -t commonmark-raw_html
+This has <sub>subscript</sub> in it and <sub>2 3</sub> again. With emphasis: <sub><em>2</em> 3</sub>. With letters: <sub>foo</sub>. With a span: <sub><span class=foo>2</span></sub>.
+^D
+This has \_(subscript) in it and ₂ ₃ again. With emphasis: \_(*2* 3). With letters: \_(foo). With a span: ₂.
+```
+
+```
+% pandoc --wrap=none -f html -t commonmark+raw_html
+This has <sub>subscript</sub> in it and <sub>2</sub> again.
+^D
+This has <sub>subscript</sub> in it and <sub>2</sub> again.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict-raw_html-subscript
+This has <sub>subscript</sub> in it and <sub>2</sub> again.
+^D
+This has _(subscript) in it and ₂ again.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict+raw_html-subscript
+This has <sub>subscript</sub> in it and <sub>2</sub> again.
+^D
+This has <sub>subscript</sub> in it and <sub>2</sub> again.
+```
+
+```
+% pandoc --wrap=none -f html -t markdown_strict+raw_html+subscript
+This has <sub>subscript</sub> in it and <sub>2</sub> again.
+^D
+This has ~subscript~ in it and ~2~ again.
+```
diff --git a/test/command/4545.md b/test/command/4545.md
new file mode 100644
index 000000000..e5fc6e244
--- /dev/null
+++ b/test/command/4545.md
@@ -0,0 +1,20 @@
+```
+% pandoc -t asciidoc
+Test 1
+
+[my text]
+
+Test 2
+^D
+Test 1
+
+{empty}[my text]
+
+Test 2
+```
+```
+% pandoc -t asciidoc
+4\. foo
+^D
+{empty}4. foo
+```
diff --git a/test/command/4553.md b/test/command/4553.md
new file mode 100644
index 000000000..e5122d4d9
--- /dev/null
+++ b/test/command/4553.md
@@ -0,0 +1,15 @@
+```
+pandoc -f latex -t native
+foo \include{command/bar}
+^D
+[Para [Str "foo"]
+,Para [Emph [Str "hi",Space,Str "there"]]]
+```
+
+```
+pandoc -f latex -t native
+foo \input{command/bar}
+^D
+[Para [Str "foo",Space,Emph [Str "hi",Space,Str "there"]]]
+```
+
diff --git a/test/command/4624.md b/test/command/4624.md
new file mode 100644
index 000000000..f9aa45596
--- /dev/null
+++ b/test/command/4624.md
@@ -0,0 +1,30 @@
+```
+% pandoc -f latex -t native
+\begin{Verbatim}[key1=value1]
+code1
+
+\end{Verbatim}
+
+
+\begin{lstlisting}[key2=value2]
+code2
+
+\end{lstlisting}
+
+\begin{verbatim}
+code3
+\end{verbatim}
+
+\begin{verbatim}
+code4
+ \end{verbatim}
+
+\begin{verbatim}
+code5\end{verbatim}
+^D
+[CodeBlock ("",[],[("key1","value1")]) "code1\n"
+,CodeBlock ("",[],[("key2","value2")]) "code2\n "
+,CodeBlock ("",[],[]) "code3"
+,CodeBlock ("",[],[]) "code4"
+,CodeBlock ("",[],[]) "code5"]
+```
diff --git a/test/command/4653.md b/test/command/4653.md
new file mode 100644
index 000000000..24a706e89
--- /dev/null
+++ b/test/command/4653.md
@@ -0,0 +1,8 @@
+```
+% pandoc -t latex
+\let\tex\TeX
+\renewcommand{\TeX}{\tex\xspace}
+^D
+\let\tex\TeX
+\renewcommand{\TeX}{\tex\xspace}
+```
diff --git a/test/command/4667.md b/test/command/4667.md
new file mode 100644
index 000000000..1fff3708d
--- /dev/null
+++ b/test/command/4667.md
@@ -0,0 +1,20 @@
+```
+pandoc -t latex
+---
+header-includes:
+- \newcommand{\blandscape}{\begin{landscape}}
+- \newcommand{\elandscape}{\end{landscape}}
+...
+
+\blandscape
+
+testing
+
+\elandscape
+^D
+\begin{landscape}
+
+testing
+
+\end{landscape}
+```
diff --git a/test/command/4669.md b/test/command/4669.md
new file mode 100644
index 000000000..b9db45b17
--- /dev/null
+++ b/test/command/4669.md
@@ -0,0 +1,29 @@
+```
+% pandoc -f latex -t native
+{\tt <-}
+
+\begin{verbatim}
+ while (n > 0) {
+\end{verbatim}
+^D
+[Para [Span ("",[],[]) [Str "<-"]]
+,CodeBlock ("",[],[]) " while (n > 0) {"]
+```
+
+```
+% pandoc -f latex -t native
+\begin{itemize}
+\item<1> one
+\item<2-3,5> two
+\item<2| @alert> three
+\item<handout> four
+\item<beamer:2> five
+\end{itemize}
+^D
+[BulletList
+ [[Para [Str "one"]]
+ ,[Para [Str "two"]]
+ ,[Para [Str "three"]]
+ ,[Para [Str "four"]]
+ ,[Para [Str "five"]]]]
+```
diff --git a/test/command/4677.md b/test/command/4677.md
new file mode 100644
index 000000000..0343cf42a
--- /dev/null
+++ b/test/command/4677.md
@@ -0,0 +1,8 @@
+```
+% pandoc --to "markdown-bracketed_spans-fenced_divs-link_attributes-simple_tables-multiline_tables-grid_tables-pipe_tables-fenced_code_attributes-markdown_in_html_blocks-table_captions-smart"
+![Caption](img.png){#img:1}
+^D
+<figure>
+<img src="img.png" alt="Caption" id="img:1" /><figcaption>Caption</figcaption>
+</figure>
+```
diff --git a/test/command/4690.md b/test/command/4690.md
new file mode 100644
index 000000000..deccfba13
--- /dev/null
+++ b/test/command/4690.md
@@ -0,0 +1,28 @@
+```
+% pandoc -t beamer
+# title
+
+:::: {.columns}
+::: {.column width="8%"}
+content
+:::
+::: {.column width="84%"}
+content2
+:::
+::::
+^D
+\begin{frame}{title}
+\protect\hypertarget{title}{}
+
+\begin{columns}[T]
+\begin{column}{0.08\textwidth}
+content
+\end{column}
+
+\begin{column}{0.84\textwidth}
+content2
+\end{column}
+\end{columns}
+
+\end{frame}
+```
diff --git a/test/command/4722.md b/test/command/4722.md
new file mode 100644
index 000000000..6c8c14716
--- /dev/null
+++ b/test/command/4722.md
@@ -0,0 +1,34 @@
+```
+% pandoc -f tikiwiki -t native
+*Level 1
+*Level 1
+**Level 2
+***Level 3
+*Level 1
+^D
+[BulletList
+ [[Plain [Str "Level",Space,Str "1"]]
+ ,[Plain [Str "Level",Space,Str "1"]
+ ,BulletList
+ [[Plain [Str "Level",Space,Str "2"]
+ ,BulletList
+ [[Plain [Str "Level",Space,Str "3"]]]]]]
+ ,[Plain [Str "Level",Space,Str "1"]]]]
+```
+```
+% pandoc -f tikiwiki -t native
+#Level 1
+#Level 1
+##Level 2
+###Level 3
+#Level 1
+^D
+[OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "Level",Space,Str "1"]]
+ ,[Plain [Str "Level",Space,Str "1"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "Level",Space,Str "2"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Plain [Str "Level",Space,Str "3"]]]]]]
+ ,[Plain [Str "Level",Space,Str "1"]]]]
+```
diff --git a/test/command/4742.md b/test/command/4742.md
new file mode 100644
index 000000000..72751d727
--- /dev/null
+++ b/test/command/4742.md
@@ -0,0 +1,25 @@
+Check that the commonmark reader handles the `ascii_identifiers`
+extension properly.
+
+```
+% pandoc -f commonmark+gfm_auto_identifiers+ascii_identifiers -t native
+# non ascii ⚠️ räksmörgås
+^D
+[Header 1 ("non-ascii--raksmorgas",[],[]) [Str "non",Space,Str "ascii",Space,Str "\9888\65039",Space,Str "r\228ksm\246rg\229s"]]
+```
+
+```
+% pandoc -f commonmark+gfm_auto_identifiers-ascii_identifiers -t native
+# non ascii ⚠️ räksmörgås
+^D
+[Header 1 ("non-ascii-\65039-r\228ksm\246rg\229s",[],[]) [Str "non",Space,Str "ascii",Space,Str "\9888\65039",Space,Str "r\228ksm\246rg\229s"]]
+```
+
+`gfm` should have `ascii_identifiers` enabled by default.
+
+```
+% pandoc -f gfm -t native
+# non ascii ⚠️ räksmörgås
+^D
+[Header 1 ("non-ascii--raksmorgas",[],[]) [Str "non",Space,Str "ascii",Space,Str "\9888\65039",Space,Str "r\228ksm\246rg\229s"]]
+```
diff --git a/test/command/4743.md b/test/command/4743.md
new file mode 100644
index 000000000..49b4b6d59
--- /dev/null
+++ b/test/command/4743.md
@@ -0,0 +1,25 @@
+Test that emojis are wrapped in Span
+
+```
+% pandoc -f commonmark+emoji -t native
+My:thumbsup:emoji:heart:
+^D
+[Para [Str "My",Span ("",["emoji"],[("data-emoji","thumbsup")]) [Str "\128077"],Str "emoji",Span ("",["emoji"],[("data-emoji","heart")]) [Str "\10084\65039"]]]
+```
+
+```
+% pandoc -f markdown+emoji -t native
+My:thumbsup:emoji:heart:
+^D
+[Para [Str "My",Span ("",["emoji"],[("data-emoji","thumbsup")]) [Str "\128077"],Str "emoji",Span ("",["emoji"],[("data-emoji","heart")]) [Str "\10084\65039"]]]
+```
+
+```
+% pandoc -f commonmark+emoji -t html
+:zero: header
+=============
+My:thumbsup:emoji:heart:x :hearts: xyz
+^D
+<h1><span class="emoji" data-emoji="zero">0️⃣</span> header</h1>
+<p>My<span class="emoji" data-emoji="thumbsup">👍</span>emoji<span class="emoji" data-emoji="heart">❤️</span>x <span class="emoji" data-emoji="hearts">♥️</span> xyz</p>
+```
diff --git a/test/command/4748.md b/test/command/4748.md
new file mode 100644
index 000000000..1de0fa9ed
--- /dev/null
+++ b/test/command/4748.md
@@ -0,0 +1,16 @@
+```
+% pandoc -f org -t rst
+Before example block.
+#+begin_example
+This is in an example block.
+#+end_example
+After example block.
+^D
+Before example block.
+
+::
+
+ This is in an example block.
+
+After example block.
+```
diff --git a/test/command/4768.md b/test/command/4768.md
new file mode 100644
index 000000000..60d407d8b
--- /dev/null
+++ b/test/command/4768.md
@@ -0,0 +1,7 @@
+```
+% pandoc -f latex -t plain
+\def\foo#1!#2!#3{#1 or #2 and #3}
+\foo aa!bbb bbb!{ccc}
+^D
+aa or bbb bbb and ccc
+```
diff --git a/test/command/4781.md b/test/command/4781.md
new file mode 100644
index 000000000..8a75e09a0
--- /dev/null
+++ b/test/command/4781.md
@@ -0,0 +1,22 @@
+```
+% pandoc -t native
+Markdown parsed *here*
+
+\include{command/bar}
+
+*But not here*
+^D
+[Para [Str "Markdown",Space,Str "parsed",Space,Emph [Str "here"]]
+,RawBlock (Format "tex") "\\include{command/bar}"
+,Para [Emph [Str "But",Space,Str "not",Space,Str "here"]]]
+```
+
+```
+% pandoc -t native
+*here* \input{command/bar}
+
+*But not here*
+^D
+[Para [Emph [Str "here"],Space,RawInline (Format "tex") "\\input{command/bar}"]
+,Para [Emph [Str "But",Space,Str "not",Space,Str "here"]]]
+```
diff --git a/test/command/4794.md b/test/command/4794.md
new file mode 100644
index 000000000..8356d2157
--- /dev/null
+++ b/test/command/4794.md
@@ -0,0 +1,18 @@
+```
+% pandoc -f markdown -t mediawiki
+| Column1 | Column2 | Column3 |
+| ------- | ------- | ------- |
+| text | | text |
+^D
+{|
+! Column1
+! Column2
+! Column3
+|-
+| text
+|
+| text
+|}
+
+
+```
diff --git a/test/command/4811.md b/test/command/4811.md
new file mode 100644
index 000000000..9c8bea7ce
--- /dev/null
+++ b/test/command/4811.md
@@ -0,0 +1,48 @@
+No blank lines in inline interpreted roles:
+
+```
+% pandoc -f rst -t native
+`no
+
+blank`:myrole:
+^D
+[Para [Str "`no"]
+,Para [Str "blank`:myrole:"]]
+```
+
+Backslash escape behaves properly in interpreted roles:
+
+```
+% pandoc -f rst -t native
+`hi\ there`:sup:
+
+`hi\ there`:code:
+^D
+[Para [Superscript [Str "hithere"]]
+,Para [Code ("",["sourceCode"],[]) "hi\\ there"]]
+```
+
+Backtick followed by alphanumeric doesn't end the span:
+```
+% pandoc -f rst -t native
+`hi`there`:myrole:
+^D
+[Para [Code ("",["interpreted-text"],[("role","myrole")]) "hi`there"]]
+```
+
+Newline is okay, as long as not blank:
+```
+% pandoc -f rst -t native
+`hi
+there`:myrole:
+^D
+[Para [Code ("",["interpreted-text"],[("role","myrole")]) "hi\nthere"]]
+```
+
+Use span for title-reference:
+```
+% pandoc -f rst -t native
+`default`
+^D
+[Para [Span ("",["title-ref"],[]) [Str "default"]]]
+```
diff --git a/test/command/4817.md b/test/command/4817.md
new file mode 100644
index 000000000..7718e3b3a
--- /dev/null
+++ b/test/command/4817.md
@@ -0,0 +1,10 @@
+```
+% pandoc -t native -s
+---
+foo:
+- bar: bam
+...
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaList [MetaMap (fromList [("bar",MetaInlines [Str "bam"])])])]})
+[]
+```
diff --git a/test/command/4819.md b/test/command/4819.md
new file mode 100644
index 000000000..548583387
--- /dev/null
+++ b/test/command/4819.md
@@ -0,0 +1,50 @@
+```
+% pandoc -f markdown -t native -s
+---
+foo: 42
+...
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaInlines [Str "42"])]})
+[]
+```
+
+```
+% pandoc -f markdown -t native -s
+---
+foo: true
+...
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaBool True)]})
+[]
+```
+
+```
+% pandoc -f markdown -t native -s
+---
+foo: True
+...
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaBool True)]})
+[]
+```
+
+```
+% pandoc -f markdown -t native -s
+---
+foo: FALSE
+...
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaBool False)]})
+[]
+```
+
+```
+% pandoc -f markdown -t native -s
+---
+foo: no
+...
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaInlines [Str "no"])]})
+[]
+```
+
diff --git a/test/command/4832.md b/test/command/4832.md
new file mode 100644
index 000000000..9ba40804c
--- /dev/null
+++ b/test/command/4832.md
@@ -0,0 +1,21 @@
+```
+% pandoc -f latex -t native
+\url{http://example.com/foo%20bar.htm}
+^D
+[Para [Link ("",[],[]) [Str "http://example.com/foo%20bar.htm"] ("http://example.com/foo%20bar.htm","")]]
+```
+
+```
+% pandoc -f latex -t native
+\url{http://example.com/foo{bar}.htm}
+^D
+[Para [Link ("",[],[]) [Str "http://example.com/foo{bar}.htm"] ("http://example.com/foo{bar}.htm","")]]
+```
+
+```
+% pandoc -f latex -t native
+\href{http://example.com/foo%20bar}{Foobar}
+^D
+[Para [Link ("",[],[]) [Str "Foobar"] ("http://example.com/foo%20bar","")]]
+```
+
diff --git a/test/command/4833.md b/test/command/4833.md
new file mode 100644
index 000000000..ed6de606b
--- /dev/null
+++ b/test/command/4833.md
@@ -0,0 +1,20 @@
+```
+pandoc -f native -t rst
+[Div ("",["warning"],[])
+ [Div ("",["admonition-title"],[])
+ [Para [Str "Warning"]]
+ ,Para [Str "Hi"]]]
+^D
+.. warning::
+
+ Hi
+```
+```
+pandoc -f native -t rst
+[Div ("",["unknown"],[])
+ [Para [Str "Hi"]]]
+^D
+.. container:: unknown
+
+ Hi
+```
diff --git a/test/command/4842.md b/test/command/4842.md
new file mode 100644
index 000000000..a311739b7
--- /dev/null
+++ b/test/command/4842.md
@@ -0,0 +1,6 @@
+```
+pandoc -f latex -t native
+\l
+^D
+[Para [Str "\322"]]
+```
diff --git a/test/command/4845.md b/test/command/4845.md
new file mode 100644
index 000000000..093161ac7
--- /dev/null
+++ b/test/command/4845.md
@@ -0,0 +1,6 @@
+```
+% pandoc -f html -t native
+x<a href="/foo"> leading trailing space </a>x
+^D
+[Plain [Str "x",Space,Link ("",[],[]) [Str "leading",Space,Str "trailing",Space,Str "space"] ("/foo",""),Space,Str "x"]]
+```
diff --git a/test/command/4848.md b/test/command/4848.md
new file mode 100644
index 000000000..2cd2bab34
--- /dev/null
+++ b/test/command/4848.md
@@ -0,0 +1,59 @@
+```
+% pandoc -f latex -t native
+\enquote*{hi}
+^D
+[Para [Quoted SingleQuote [Str "hi"]]]
+```
+
+```
+% pandoc -f latex -t native
+\foreignquote{italian}{hi}
+^D
+[Para [Quoted DoubleQuote [Span ("",[],[("lang","it")]) [Str "hi"]]]]
+```
+
+```
+% pandoc -f latex -t native
+\hyphenquote*{italian}{hi}
+^D
+[Para [Quoted SingleQuote [Span ("",[],[("lang","it")]) [Str "hi"]]]]
+```
+
+```
+% pandoc -f latex -t native
+Lorem ipsum
+\blockquote{dolor sit amet}
+consectetuer.
+^D
+[Para [Str "Lorem",Space,Str "ipsum"]
+,BlockQuote
+ [Para [Str "dolor",Space,Str "sit",Space,Str "amet"]]
+,Para [Str "consectetuer."]]
+```
+
+```
+% pandoc -f latex -t native
+Lorem ipsum
+\blockcquote[198]{Knu86}{dolor sit amet}
+consectetuer.
+^D
+[Para [Str "Lorem",Space,Str "ipsum"]
+,BlockQuote
+ [Para [Str "dolor",Space,Str "sit",Space,Str "amet"]
+ ,Para [Cite [Citation {citationId = "Knu86", citationPrefix = [], citationSuffix = [Str "198"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] []]]
+,Para [Str "consectetuer."]]
+```
+
+```
+% pandoc -f latex -t native
+Lorem ipsum
+\foreignblockquote{italian}{dolor sit amet}
+consectetuer.
+^D
+[Para [Str "Lorem",Space,Str "ipsum"]
+,BlockQuote
+ [Div ("",[],[("lang","it")])
+ [Para [Str "dolor",Space,Str "sit",Space,Str "amet"]]]
+,Para [Str "consectetuer."]]
+```
+
diff --git a/test/command/4860.md b/test/command/4860.md
new file mode 100644
index 000000000..9198f68d7
--- /dev/null
+++ b/test/command/4860.md
@@ -0,0 +1,9 @@
+```
+% pandoc -f rst -t native
+This is broken_.
+
+.. ***** REFERENCES FOLLOW *****
+.. _broken: http://google.com
+^D
+[Para [Str "This",Space,Str "is",Space,Link ("",[],[]) [Str "broken"] ("http://google.com",""),Str "."]]
+```
diff --git a/test/command/4877.md b/test/command/4877.md
new file mode 100644
index 000000000..070687345
--- /dev/null
+++ b/test/command/4877.md
@@ -0,0 +1,13 @@
+```
+% pandoc -f html -t native
+My <script type="math/tex">\mathcal{D}</script>
+^D
+[Plain [Str "My",Space,Math InlineMath "\\mathcal{D}"]]
+```
+
+```
+% pandoc -f html -t native
+<script type="math/tex; mode=display">\mathcal{D}</script>
+^D
+[Plain [Math DisplayMath "\\mathcal{D}"]]
+```
diff --git a/test/command/4885.md b/test/command/4885.md
new file mode 100644
index 000000000..8611097c2
--- /dev/null
+++ b/test/command/4885.md
@@ -0,0 +1,8 @@
+```
+% pandoc -f org -t markdown
+This won't show the command.
+src_maxima[:exports none :results raw]{tex('integrate(sin((e^x)/pi),x,0,inf));} $$\int_{0}^{\infty }{\sin \left({{e^{x}}\over{\pi}}\right)\;dx}$$
+^D
+This won\'t show the command.
+$$\int_{0}^{\infty }{\sin \left({{e^{x}}\over{\pi}}\right)\;dx}$$
+```
diff --git a/test/command/4908.md b/test/command/4908.md
new file mode 100644
index 000000000..2ff1a4603
--- /dev/null
+++ b/test/command/4908.md
@@ -0,0 +1,16 @@
+```
+% pandoc -f markdown_mmd+fancy_lists+example_lists -t native -t plain
+(@) Example one
+(@) Example two
+
+some text
+
+(@) Example three
+^D
+(1) Example one
+(2) Example two
+
+some text
+
+(3) Example three
+```
diff --git a/test/command/4913.md b/test/command/4913.md
new file mode 100644
index 000000000..6492b80ce
--- /dev/null
+++ b/test/command/4913.md
@@ -0,0 +1,34 @@
+```
+% pandoc -f markdown -t html
+[https://pandoc.org](https://pandoc.org)
+^D
+<p><a href="https://pandoc.org">https://pandoc.org</a></p>
+```
+
+```
+% pandoc -f markdown -t markdown
+[https://pandoc.org](https://pandoc.org)
+^D
+<https://pandoc.org>
+```
+
+```
+% pandoc -f markdown -t html
+<https://pandoc.org>
+^D
+<p><a href="https://pandoc.org" class="uri">https://pandoc.org</a></p>
+```
+
+```
+% pandoc -f markdown -t html
+<https://pandoc.org>{.foo}
+^D
+<p><a href="https://pandoc.org" class="foo">https://pandoc.org</a></p>
+```
+
+```
+% pandoc -f markdown -t html
+<me@example.com>
+^D
+<p><a href="mailto:me@example.com" class="email">me@example.com</a></p>
+```
diff --git a/test/command/4919.md b/test/command/4919.md
new file mode 100644
index 000000000..029d1beff
--- /dev/null
+++ b/test/command/4919.md
@@ -0,0 +1,14 @@
+```
+% pandoc -f rst -t native
+.. _`tgtmath`:
+
+ .. math::
+ :name:
+
+ V = \frac{K}{r^2}
+^D
+[Div ("tgtmath",[],[])
+ [BlockQuote
+ [Para [Math DisplayMath "V = \\frac{K}{r^2}"]]]]
+```
+
diff --git a/test/command/4928.md b/test/command/4928.md
new file mode 100644
index 000000000..d1e2b6db7
--- /dev/null
+++ b/test/command/4928.md
@@ -0,0 +1,48 @@
+```
+% pandoc -f latex -t native
+\cites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}
+^D
+[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote",Space,Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}"]]]
+```
+
+```
+% pandoc -f latex -t native
+\cites(Multiprenote)()[23][42]{Knu86}[65]{Nie72}
+^D
+[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote",Space,Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(Multiprenote)()[23][42]{Knu86}[65]{Nie72}"]]]
+```
+
+```
+% pandoc -f latex -t native
+\cites()(multipostnote)[23][42]{Knu86}[65]{Nie72}
+^D
+[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites()(multipostnote)[23][42]{Knu86}[65]{Nie72}"]]]
+```
+
+```
+% pandoc -f latex -t native
+\cites()()[23][42]{Knu86}[65]{Nie72}
+^D
+[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites()()[23][42]{Knu86}[65]{Nie72}"]]]
+```
+
+```
+% pandoc -f latex -t native
+\cites(multipostnote)[23][42]{Knu86}[65]{Nie72}
+^D
+[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(multipostnote)[23][42]{Knu86}[65]{Nie72}"]]]
+```
+
+```
+% pandoc -f latex -t native
+\cites(Multiprenote)(multipostnote){Knu86}
+^D
+[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote"], citationSuffix = [Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(Multiprenote)(multipostnote){Knu86}"]]]
+```
+
+```
+% pandoc -f latex -t native
+\footcites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}
+^D
+[Para [Note [Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote",Space,Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\footcites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}"],Str "."]]]]
+```
diff --git a/test/command/adjacent_latex_blocks.md b/test/command/adjacent_latex_blocks.md
index 3e72f1d4f..e7dc6d895 100644
--- a/test/command/adjacent_latex_blocks.md
+++ b/test/command/adjacent_latex_blocks.md
@@ -4,6 +4,6 @@
\listoftables
^D
-[RawBlock (Format "latex") "\\listoffigures"
-,RawBlock (Format "latex") "\\listoftables"]
+[RawBlock (Format "tex") "\\listoffigures"
+,RawBlock (Format "tex") "\\listoftables"]
```
diff --git a/test/command/ascii.md b/test/command/ascii.md
new file mode 100644
index 000000000..523baa46c
--- /dev/null
+++ b/test/command/ascii.md
@@ -0,0 +1,45 @@
+```
+pandoc -t html --ascii
+äéıå
+^D
+<p>&#228;&#233;&#305;&#229;</p>
+```
+
+```
+pandoc -t latex --ascii
+äéıå
+^D
+\"{a}\'{e}\i \r{a}
+```
+
+```
+pandoc -t man --ascii
+äéıå
+^D
+.PP
+\[u00E4]\[u00E9]\[u0131]\[u00E5]
+```
+
+```
+pandoc -t ms --ascii
+äéıå
+^D
+.LP
+\[u00E4]\[u00E9]\[u0131]\[u00E5]
+```
+
+```
+pandoc -t docbook --ascii
+äéıå
+^D
+<para>
+ &#228;&#233;&#305;&#229;
+</para>
+```
+
+```
+pandoc -t jats --ascii
+äéıå
+^D
+<p>&#228;&#233;&#305;&#229;</p>
+```
diff --git a/test/command/bar.tex b/test/command/bar.tex
new file mode 100644
index 000000000..e2113ab93
--- /dev/null
+++ b/test/command/bar.tex
@@ -0,0 +1 @@
+\emph{hi there}
diff --git a/test/command/emoji.md b/test/command/emoji.md
new file mode 100644
index 000000000..b5c573b3f
--- /dev/null
+++ b/test/command/emoji.md
@@ -0,0 +1,27 @@
+```
+% pandoc -t markdown+emoji -f markdown+emoji
+:smile:
+^D
+:smile:
+```
+
+```
+% pandoc -t markdown-emoji -f markdown+emoji
+:smile:
+^D
+😄
+```
+
+```
+% pandoc -t gfm -f markdown+emoji
+:smile:
+^D
+:smile:
+```
+
+```
+% pandoc -t gfm-emoji -f markdown+emoji
+:smile:
+^D
+😄
+```
diff --git a/test/command/empty-inline-code.txt b/test/command/empty-inline-code.txt
new file mode 100644
index 000000000..b57072a44
--- /dev/null
+++ b/test/command/empty-inline-code.txt
@@ -0,0 +1,6 @@
+```
+% pandoc -t native
+` `
+^D
+[Code ("",[],[]) ""]
+```
diff --git a/test/command/gfm.md b/test/command/gfm.md
index 670f3cd6e..7a7098989 100644
--- a/test/command/gfm.md
+++ b/test/command/gfm.md
@@ -38,7 +38,7 @@ gfm tests:
% pandoc -f gfm -t native
My:thumbsup:emoji:heart:
^D
-[Para [Str "My\128077emoji\10084\65039"]]
+[Para [Str "My",Span ("",["emoji"],[("data-emoji","thumbsup")]) [Str "\128077"],Str "emoji",Span ("",["emoji"],[("data-emoji","heart")]) [Str "\10084\65039"]]]
```
```
diff --git a/test/command/hspace.md b/test/command/hspace.md
index ec1669ca5..a8b97b8bc 100644
--- a/test/command/hspace.md
+++ b/test/command/hspace.md
@@ -8,7 +8,7 @@ Here they need to be inline:
\caption{lalune \hspace{2em} \vspace{1em} bloo}
\end{figure}
^D
-[RawBlock (Format "latex") "\\begin{figure}\n\\includegraphics{lalune.jpg}\n\\caption{lalune \\hspace{2em} \\vspace{1em} bloo}\n\\end{figure}"]
+[RawBlock (Format "tex") "\\begin{figure}\n\\includegraphics{lalune.jpg}\n\\caption{lalune \\hspace{2em} \\vspace{1em} bloo}\n\\end{figure}"]
```
Here block:
@@ -32,7 +32,7 @@ F & T &\\
F & F &\\
\end{tabular}
^D
-[RawBlock (Format "latex") "\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\wedge Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}\n\\hspace{1em}\n\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\vee Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}"]
+[RawBlock (Format "tex") "\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\wedge Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}\n\\hspace{1em}\n\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\vee Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}"]
```
```
@@ -51,6 +51,6 @@ hi
there
^D
[Para [Str "hi"]
-,RawBlock (Format "latex") "\\hspace{1em}"
+,RawBlock (Format "tex") "\\hspace{1em}"
,Para [Str "there"]]
```
diff --git a/test/command/macros.md b/test/command/macros.md
index 9de87e7a0..d091c2191 100644
--- a/test/command/macros.md
+++ b/test/command/macros.md
@@ -24,18 +24,18 @@ expanded at point of use:
% pandoc -f latex -t latex
\let\a\b
\newcommand{\b}{\emph{ouk}}
-\a
+\a a
^D
-\b
+a̱
```
```
% pandoc -f latex -t latex
\newcommand{\a}{\b}
\newcommand{\b}{\emph{ouk}}
-\a
+\a a
^D
-\emph{ouk}
+\emph{ouk}a
```
```
diff --git a/test/command/refs.md b/test/command/refs.md
index 66959e5c3..8b58ea6d7 100644
--- a/test/command/refs.md
+++ b/test/command/refs.md
@@ -42,12 +42,55 @@ Accuracy~\eqref{eq:Accuracy} is the proportion, measuring true results among all
Figure \ref{fig:Logo} illustrated the SVG logo
^D
-[Para [Image ("",[],[]) [Str "Logo",Span ("",[],[("label","fig:Logo")]) []] ("command/SVG_logo.svg","fig:")]
-,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo")]) [Str "[fig:Logo]"] ("#fig:Logo",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]]
+[Para [Image ("fig:Logo",[],[]) [Str "Logo",Span ("",[],[("label","fig:Logo")]) []] ("command/SVG_logo.svg","fig:")]
+,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo")]) [Str "1"] ("#fig:Logo",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]]
```
```
% pandoc -f latex -t native
+\chapter{One}
+\begin{figure}
+ \includegraphics{command/SVG_logo.svg}
+ \caption{Logo}
+ \label{fig:Logo}
+\end{figure}
+
+\begin{figure}
+ \includegraphics{command/SVG_logo2.svg}
+ \caption{Logo2}
+ \label{fig:Logo2}
+\end{figure}
+
+\chapter{Two}
+
+\section{Subone}
+
+\begin{figure}
+ \includegraphics{command/SVG_logo3.svg}
+ \caption{Logo3}
+ \label{fig:Logo3}
+\end{figure}
+
+Figure \ref{fig:Logo} illustrated the SVG logo
+
+Figure \ref{fig:Logo2} illustrated the SVG logo
+
+Figure \ref{fig:Logo3} illustrated the SVG logo
+^D
+[Header 1 ("one",[],[]) [Str "One"]
+,Para [Image ("fig:Logo",[],[]) [Str "Logo",Span ("",[],[("label","fig:Logo")]) []] ("command/SVG_logo.svg","fig:")]
+,Para [Image ("fig:Logo2",[],[]) [Str "Logo2",Span ("",[],[("label","fig:Logo2")]) []] ("command/SVG_logo2.svg","fig:")]
+,Header 1 ("two",[],[]) [Str "Two"]
+,Header 2 ("subone",[],[]) [Str "Subone"]
+,Para [Image ("fig:Logo3",[],[]) [Str "Logo3",Span ("",[],[("label","fig:Logo3")]) []] ("command/SVG_logo3.svg","fig:")]
+,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo")]) [Str "1.1"] ("#fig:Logo",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]
+,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo2")]) [Str "1.2"] ("#fig:Logo2",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]
+,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo3")]) [Str "2.1"] ("#fig:Logo3",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]]
+```
+
+
+```
+% pandoc -f latex -t native
\label{section} Section \ref{section}
^D
[Para [Span ("section",[],[("label","section")]) [Str "[section]"],Space,Str "Section",Space,Link ("",[],[("reference-type","ref"),("reference","section")]) [Str "[section]"] ("#section","")]]
diff --git a/test/command/write18.md b/test/command/write18.md
index 344dfc8cf..5000c298b 100644
--- a/test/command/write18.md
+++ b/test/command/write18.md
@@ -3,7 +3,7 @@ Handle \write18{..} as raw tex:
% pandoc -t native
\write18{git --version}
^D
-[RawBlock (Format "latex") "\\write18{git --version}"]
+[RawBlock (Format "tex") "\\write18{git --version}"]
```
```
diff --git a/test/command/yaml-metadata-blocks.md b/test/command/yaml-metadata-blocks.md
new file mode 100644
index 000000000..5b73cff72
--- /dev/null
+++ b/test/command/yaml-metadata-blocks.md
@@ -0,0 +1,63 @@
+```
+% pandoc -s -t native
+---
+foobar_: this should be ignored
+foo:
+ bar_: as should this
+---
+^D
+Pandoc (Meta {unMeta = fromList [("foo",MetaMap (fromList []))]})
+[]
+```
+```
+% pandoc -s -t native
+---
+# For precedence, see multiple-metadata-blocks.md and vars-and-metadata.md
+# For Bools, see also 4819.md
+# For Multiline strings, see yaml-with-chomp.md
+int: 7
+float: 1.5
+scientific: 3.7e-5
+bool: true
+more: False
+nothing: null
+emtpy: []
+nested:
+ int: 8
+ float: 2.5
+ bool: true
+ more: False
+ nothing: null
+ emtpy: []
+ scientific: 3.7e-5
+---
+^D
+Pandoc (Meta {unMeta = fromList [("bool",MetaBool True),("emtpy",MetaList []),("float",MetaInlines [Str "1.5"]),("int",MetaInlines [Str "7"]),("more",MetaBool False),("nested",MetaMap (fromList [("bool",MetaBool True),("emtpy",MetaList []),("float",MetaInlines [Str "2.5"]),("int",MetaInlines [Str "8"]),("more",MetaBool False),("nothing",MetaInlines [Str "null"]),("scientific",MetaInlines [Str "3.7e-5"])])),("nothing",MetaInlines [Str "null"]),("scientific",MetaInlines [Str "3.7e-5"])]})
+[]
+```
+```
+% pandoc -s -t native
+---
+array:
+ - foo: bar
+ - bool: True
+---
+^D
+Pandoc (Meta {unMeta = fromList [("array",MetaList [MetaMap (fromList [("foo",MetaInlines [Str "bar"])]),MetaMap (fromList [("bool",MetaBool True)])])]})
+[]
+```
+```
+% pandoc -s -t native --metadata-file command/yaml-metadata.yaml
+---
+title: document
+---
+^D
+Pandoc (Meta {unMeta = fromList [("other",MetaInlines [Emph [Str "markdown"],Space,Str "value"]),("title",MetaInlines [Str "document"])]})
+[]
+```
+```
+% pandoc -s -t native --metadata-file command/yaml-metadata.yaml -M title=cmdline
+^D
+Pandoc (Meta {unMeta = fromList [("other",MetaInlines [Emph [Str "markdown"],Space,Str "value"]),("title",MetaString "cmdline")]})
+[]
+```
diff --git a/test/command/yaml-metadata.yaml b/test/command/yaml-metadata.yaml
new file mode 100644
index 000000000..9cd0043d3
--- /dev/null
+++ b/test/command/yaml-metadata.yaml
@@ -0,0 +1,4 @@
+---
+title: file
+other: _markdown_ value
+---
diff --git a/test/docbook-xref.native b/test/docbook-xref.native
index 23bc497b2..54a63768e 100644
--- a/test/docbook-xref.native
+++ b/test/docbook-xref.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList []})
+Pandoc (Meta {unMeta = fromList [("title",MetaInlines [Str "An",Space,Str "Example",Space,Str "Book"])]})
[Header 1 ("ch01",[],[]) [Str "XRef",Space,Str "Samples"]
,Para [Str "This",Space,Str "paragraph",Space,Str "demonstrates",Space,Str "several",Space,Str "features",Space,Str "of",SoftBreak,Str "XRef."]
,BulletList
diff --git a/test/fb2/meta.fb2 b/test/fb2/meta.fb2
index 04bd5f3c5..1db48c068 100644
--- a/test/fb2/meta.fb2
+++ b/test/fb2/meta.fb2
@@ -1,3 +1,3 @@
<?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><genre>unrecognised</genre><book-title>Book title</book-title><annotation><p>This is the abstract.</p>It consists of two paragraphs.</annotation></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p>Book title</p></title></body></FictionBook>
+<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info><genre>unrecognised</genre><book-title>Book title</book-title><annotation><p>This is the abstract.</p><p>It consists of two paragraphs.</p></annotation></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p>Book title</p></title></body></FictionBook>
diff --git a/test/lhs-test.html b/test/lhs-test.html
index c9777ea7b..5fce225df 100644
--- a/test/lhs-test.html
+++ b/test/lhs-test.html
@@ -14,7 +14,7 @@
<style type="text/css">
a.sourceLine { display: inline-block; line-height: 1.25; }
a.sourceLine { pointer-events: none; color: inherit; text-decoration: inherit; }
-a.sourceLine:empty { height: 1.2em; position: absolute; }
+a.sourceLine:empty { height: 1.2em; }
.sourceCode { overflow: visible; }
code.sourceCode { white-space: pre; position: relative; }
div.sourceCode { margin: 1em 0; }
@@ -27,13 +27,11 @@ code.sourceCode { white-space: pre-wrap; }
a.sourceLine { text-indent: -1em; padding-left: 1em; }
}
pre.numberSource a.sourceLine
- { position: relative; }
-pre.numberSource a.sourceLine:empty
- { position: absolute; }
+ { position: relative; left: -4em; }
pre.numberSource a.sourceLine::before
{ content: attr(data-line-number);
- position: absolute; left: -5em; text-align: right; vertical-align: baseline;
- border: none; pointer-events: all;
+ position: relative; left: -1em; text-align: right; vertical-align: baseline;
+ border: none; pointer-events: all; display: inline-block;
-webkit-touch-callout: none; -webkit-user-select: none;
-khtml-user-select: none; -moz-user-select: none;
-ms-user-select: none; user-select: none;
diff --git a/test/lhs-test.html+lhs b/test/lhs-test.html+lhs
index 4a121e0d1..78bc1d426 100644
--- a/test/lhs-test.html+lhs
+++ b/test/lhs-test.html+lhs
@@ -14,7 +14,7 @@
<style type="text/css">
a.sourceLine { display: inline-block; line-height: 1.25; }
a.sourceLine { pointer-events: none; color: inherit; text-decoration: inherit; }
-a.sourceLine:empty { height: 1.2em; position: absolute; }
+a.sourceLine:empty { height: 1.2em; }
.sourceCode { overflow: visible; }
code.sourceCode { white-space: pre; position: relative; }
div.sourceCode { margin: 1em 0; }
@@ -27,13 +27,11 @@ code.sourceCode { white-space: pre-wrap; }
a.sourceLine { text-indent: -1em; padding-left: 1em; }
}
pre.numberSource a.sourceLine
- { position: relative; }
-pre.numberSource a.sourceLine:empty
- { position: absolute; }
+ { position: relative; left: -4em; }
pre.numberSource a.sourceLine::before
{ content: attr(data-line-number);
- position: absolute; left: -5em; text-align: right; vertical-align: baseline;
- border: none; pointer-events: all;
+ position: relative; left: -1em; text-align: right; vertical-align: baseline;
+ border: none; pointer-events: all; display: inline-block;
-webkit-touch-callout: none; -webkit-user-select: none;
-khtml-user-select: none; -moz-user-select: none;
-ms-user-select: none; user-select: none;
diff --git a/test/lua/test-pandoc-utils.lua b/test/lua/test-pandoc-utils.lua
index 21f937edb..4421603ec 100644
--- a/test/lua/test-pandoc-utils.lua
+++ b/test/lua/test-pandoc-utils.lua
@@ -1,5 +1,19 @@
utils = require 'pandoc.utils'
+-- Squash blocks to inlines
+------------------------------------------------------------------------
+function test_blocks_to_inlines ()
+ local blocks = {
+ pandoc.Para{ pandoc.Str 'Paragraph1' },
+ pandoc.Para{ pandoc.Emph 'Paragraph2' }
+ }
+ local inlines = utils.blocks_to_inlines(blocks, {pandoc.LineBreak()})
+ return #inlines == 3
+ and inlines[1].text == "Paragraph1"
+ and inlines[2].t == 'LineBreak'
+ and inlines[3].content[1].text == "Paragraph2"
+end
+
-- hierarchicalize
------------------------------------------------------------------------
function test_hierarchicalize ()
@@ -110,6 +124,7 @@ end
function Para (el)
return {
+ pandoc.Plain{pandoc.Str("blocks_to_inlines: " .. run(test_blocks_to_inlines))},
pandoc.Plain{pandoc.Str("hierarchicalize: " .. run(test_hierarchicalize))},
pandoc.Plain{pandoc.Str("normalize_date: " .. run(test_normalize_date))},
pandoc.Plain{pandoc.Str("pipe: " .. run(test_pipe))},
diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native
index 17e91bb89..9c128ab94 100644
--- a/test/markdown-reader-more.native
+++ b/test/markdown-reader-more.native
@@ -3,10 +3,11 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
,Para [Link ("",[],[]) [Str "foo"] ("/url",""),Space,Str "and",Space,Link ("",[],[]) [Str "bar"] ("/url","title")]
,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]
-,RawBlock (Format "context") "\\placeformula \\startformula\n L_{1} = L_{2}\n \\stopformula"
-,RawBlock (Format "context") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
+,RawBlock (Format "tex") "\\placeformula \\startformula"
+,Para [Str "L_{1}",Space,Str "=",Space,Str "L_{2}",SoftBreak,RawInline (Format "tex") "\\stopformula"]
+,RawBlock (Format "tex") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
,Header 2 ("raw-latex-environments",[],[]) [Str "Raw",Space,Str "LaTeX",Space,Str "environments"]
-,RawBlock (Format "latex") "\\begin{center}\n\\begin{tikzpicture}[baseline={([yshift=+-.5ex]current bounding box.center)}, level distance=24pt]\n\\Tree [.{S} [.NP John\\index{i} ] [.VP [.V likes ] [.NP himself\\index{i,*j} ]]]\n\\end{tikzpicture}\n\\end{center}"
+,RawBlock (Format "tex") "\\begin{center}\n\\begin{tikzpicture}[baseline={([yshift=+-.5ex]current bounding box.center)}, level distance=24pt]\n\\Tree [.{S} [.NP John\\index{i} ] [.VP [.V likes ] [.NP himself\\index{i,*j} ]]]\n\\end{tikzpicture}\n\\end{center}"
,Header 2 ("urls-with-spaces-and-punctuation",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "punctuation"]
,Para [Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),SoftBreak,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),SoftBreak,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),SoftBreak,Link ("",[],[]) [Str "foo"] ("bar%20baz","title")]
,Para [Link ("",[],[]) [Str "baz"] ("/foo%20foo",""),Space,Link ("",[],[]) [Str "bam"] ("/foo%20fee",""),Space,Link ("",[],[]) [Str "bork"] ("/foo/zee%20zob","title")]
@@ -44,9 +45,9 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
,Para [Str "`hi"]
,Para [Str "there`"]
,Header 2 ("multilingual-urls",[],[]) [Str "Multilingual",Space,Str "URLs"]
-,Para [Link ("",[],[]) [Str "http://\27979.com?\27979=\27979"] ("http://\27979.com?\27979=\27979","")]
+,Para [Link ("",["uri"],[]) [Str "http://\27979.com?\27979=\27979"] ("http://\27979.com?\27979=\27979","")]
,Para [Link ("",[],[]) [Str "foo"] ("/bar/\27979?x=\27979","title")]
-,Para [Link ("",[],[]) [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")]
+,Para [Link ("",["email"],[]) [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")]
,Header 2 ("numbered-examples",[],[]) [Str "Numbered",Space,Str "examples"]
,OrderedList (1,Example,TwoParens)
[[Plain [Str "First",Space,Str "example."]]
@@ -55,7 +56,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
,OrderedList (3,Example,TwoParens)
[[Plain [Str "Third",Space,Str "example."]]]
,Header 2 ("macros",[],[]) [Str "Macros"]
-,RawBlock (Format "latex") "\\newcommand{\\tuple}[1]{\\langle #1 \\rangle}"
+,RawBlock (Format "tex") "\\newcommand{\\tuple}[1]{\\langle #1 \\rangle}"
,Para [Math InlineMath "\\langle x,y \\rangle"]
,Header 2 ("case-insensitive-references",[],[]) [Str "Case-insensitive",Space,Str "references"]
,Para [Link ("",[],[]) [Str "Fum"] ("/fum","")]
@@ -175,8 +176,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
,[]]]
,Header 2 ("entities-in-links-and-titles",[],[]) [Str "Entities",Space,Str "in",Space,Str "links",Space,Str "and",Space,Str "titles"]
,Para [Link ("",[],[]) [Str "link"] ("/\252rl","\246\246!")]
-,Para [Link ("",[],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")]
-,Para [Link ("",[],[]) [Str "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")]
+,Para [Link ("",["uri"],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")]
+,Para [Link ("",["email"],[]) [Str "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")]
,Para [Link ("",[],[]) [Str "foobar"] ("/\252rl","\246\246!")]
,Header 2 ("parentheses-in-urls",[],[]) [Str "Parentheses",Space,Str "in",Space,Str "URLs"]
,Para [Link ("",[],[]) [Str "link"] ("/hi(there)","")]
diff --git a/test/pptx/lists.native b/test/pptx/lists.native
index e08580cd5..61249c7fe 100644
--- a/test/pptx/lists.native
+++ b/test/pptx/lists.native
@@ -1,7 +1,7 @@
[Header 1 ("lists",[],[]) [Str "Lists"]
,BulletList
[[Para [Str "Bulleted",Space,Str "bulleted",Space,Str "lists."]]
- ,[Para [Str "And",Space,Str "go",Space,Str "to",Space,Str "aribtrary",Space,Str "depth."]
+ ,[Para [Str "And",Space,Str "go",Space,Str "to",Space,Str "arbitrary",Space,Str "depth."]
,BulletList
[[Para [Str "Like",Space,Str "this"]
,BulletList
diff --git a/test/pptx/lists.pptx b/test/pptx/lists.pptx
index acb0841ce..c28e840f1 100644
--- a/test/pptx/lists.pptx
+++ b/test/pptx/lists.pptx
Binary files differ
diff --git a/test/pptx/lists_templated.pptx b/test/pptx/lists_templated.pptx
index a25feaff1..74505454e 100644
--- a/test/pptx/lists_templated.pptx
+++ b/test/pptx/lists_templated.pptx
Binary files differ
diff --git a/test/rst-reader.native b/test/rst-reader.native
index b0e51bd3f..89dde7396 100644
--- a/test/rst-reader.native
+++ b/test/rst-reader.native
@@ -326,7 +326,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Math DisplayMath "\\alpha = beta",Math DisplayMath "E = mc^2"]
,Para [Str "Some",Space,Superscript [Str "of"],Space,Str "these",Space,Superscript [Str "words"],Space,Str "are",Space,Str "in",Space,Superscript [Str "superscript"],Str "."]
,Para [Str "Reset",Space,Str "default-role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default."]
-,Para [Str "And",Space,Str "now",Space,Str "some-invalid-string-3231231",Space,Str "is",Space,Str "nonsense."]
+,Para [Str "And",Space,Str "now",Space,Span ("",["title-ref"],[]) [Str "some-invalid-string-3231231"],Space,Str "is",Space,Str "nonsense."]
,Para [Str "And",Space,Str "now",Space,Str "with",Space,RawInline (Format "html") "<b>inline</b> <span id=\"test\">HTML</span>",Str "."]
,Para [Str "And",Space,Str "some",Space,Str "inline",Space,Str "haskell",Space,Code ("",["haskell","sourceCode"],[]) "fmap id [1,2..10]",Str "."]
,Para [Str "Indirect",Space,Str "python",Space,Str "role",Space,Code ("",["py","python","indirect","sourceCode"],[]) "[x*x for x in [1,2,3,4,5]]",Str "."]
diff --git a/test/tables-rstsubset.native b/test/tables-rstsubset.native
index 5ea520d7c..a4f801b1c 100644
--- a/test/tables-rstsubset.native
+++ b/test/tables-rstsubset.native
@@ -1,5 +1,5 @@
[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."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,8.75e-2,0.1125,0.125]
+,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0]
[[Plain [Str "Right"]]
,[Plain [Str "Left"]]
,[Plain [Str "Center"]]
@@ -17,7 +17,7 @@
,[Plain [Str "1"]]
,[Plain [Str "1"]]]]
,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"]
-,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,8.75e-2,0.1125,0.125]
+,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0]
[[Plain [Str "Right"]]
,[Plain [Str "Left"]]
,[Plain [Str "Center"]]
@@ -35,7 +35,7 @@
,[Plain [Str "1"]]
,[Plain [Str "1"]]]]
,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"]
-,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,8.75e-2,0.1125,0.125]
+,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0]
[[Plain [Str "Right"]]
,[Plain [Str "Left"]]
,[Plain [Str "Center"]]
@@ -81,7 +81,7 @@
,[Plain [Str "5.0"]]
,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]
,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
-,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [7.5e-2,7.5e-2,7.5e-2,7.5e-2]
+,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0]
[[]
,[]
,[]
diff --git a/test/tables.opendocument b/test/tables.opendocument
index c331ecc43..5c68476b8 100644
--- a/test/tables.opendocument
+++ b/test/tables.opendocument
@@ -6,64 +6,65 @@
<table:table-column table:style-name="Table1.D" />
<table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P1">Right</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Left</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P2">Center</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Default</text:p>
</table:table-cell>
</table:table-row>
</table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P3">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P4">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P3">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P4">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P3">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P4">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table1.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
</table:table-row>
</table:table>
-<text:p text:style-name="Table">Demonstration of simple table syntax.</text:p>
+<text:p text:style-name="Table">Table <text:sequence text:ref-name="refTable0" text:name="Table" text:formula="ooow:Table+1" style:num-format="1">1</text:sequence>: Demonstration
+of simple table syntax.</text:p>
<text:p text:style-name="First_20_paragraph">Simple table without
caption:</text:p>
<table:table table:name="Table2" table:style-name="Table2">
@@ -73,59 +74,59 @@ caption:</text:p>
<table:table-column table:style-name="Table2.D" />
<table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P5">Right</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Left</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P6">Center</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Default</text:p>
</table:table-cell>
</table:table-row>
</table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P7">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P8">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P7">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P8">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P7">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P8">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table2.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
</table:table-row>
@@ -139,64 +140,65 @@ spaces:</text:p>
<table:table-column table:style-name="Table3.D" />
<table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P9">Right</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Left</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P10">Center</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Default</text:p>
</table:table-cell>
</table:table-row>
</table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P11">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P12">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P11">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P12">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P11">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P12">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table3.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
</table:table-row>
</table:table>
-<text:p text:style-name="Table">Demonstration of simple table syntax.</text:p>
+<text:p text:style-name="Table">Table <text:sequence text:ref-name="refTable1" text:name="Table" text:formula="ooow:Table+1" style:num-format="1">2</text:sequence>: Demonstration
+of simple table syntax.</text:p>
<text:p text:style-name="First_20_paragraph">Multiline table with
caption:</text:p>
<table:table table:name="Table4" table:style-name="Table4">
@@ -206,53 +208,53 @@ caption:</text:p>
<table:table-column table:style-name="Table4.D" />
<table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P13">Centered Header</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Left Aligned</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P14">Right Aligned</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Default aligned</text:p>
</table:table-cell>
</table:table-row>
</table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P15">First</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">row</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P16">12.0</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">Example of a row that spans
multiple lines.</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P15">Second</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">row</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P16">5.0</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table4.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">Here’s another one. Note the
blank line between rows.</text:p>
</table:table-cell>
</table:table-row>
</table:table>
-<text:p text:style-name="Table">Here’s the caption. It may span multiple
-lines.</text:p>
+<text:p text:style-name="Table">Table <text:sequence text:ref-name="refTable2" text:name="Table" text:formula="ooow:Table+1" style:num-format="1">3</text:sequence>: 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">
@@ -262,46 +264,46 @@ caption:</text:p>
<table:table-column table:style-name="Table5.D" />
<table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P17">Centered Header</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Left Aligned</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="P18">Right Aligned</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableHeaderRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Heading">Default aligned</text:p>
</table:table-cell>
</table:table-row>
</table:table-header-rows>
<table:table-row>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P19">First</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">row</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P20">12.0</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">Example of a row that spans
multiple lines.</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P19">Second</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">row</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P20">5.0</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table5.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">Here’s another one. Note the
blank line between rows.</text:p>
</table:table-cell>
@@ -315,44 +317,44 @@ headers:</text:p>
<table:table-column table:style-name="Table6.C" />
<table:table-column table:style-name="Table6.D" />
<table:table-row>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P24">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P25">12</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P26">12</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P24">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P25">123</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P26">123</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P24">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P25">1</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table6.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P26">1</text:p>
</table:table-cell>
</table:table-row>
@@ -365,31 +367,31 @@ headers:</text:p>
<table:table-column table:style-name="Table7.C" />
<table:table-column table:style-name="Table7.D" />
<table:table-row>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P29">First</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">row</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P30">12.0</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">Example of a row that spans
multiple lines.</text:p>
</table:table-cell>
</table:table-row>
<table:table-row>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P29">Second</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">row</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="P30">5.0</text:p>
</table:table-cell>
- <table:table-cell table:style-name="Table7.A1" office:value-type="string">
+ <table:table-cell table:style-name="TableRowCell" office:value-type="string">
<text:p text:style-name="Table_20_Contents">Here’s another one. Note the
blank line between rows.</text:p>
</table:table-cell>
diff --git a/test/tables.rst b/test/tables.rst
index 4559883cd..660df61d4 100644
--- a/test/tables.rst
+++ b/test/tables.rst
@@ -2,41 +2,35 @@ Simple table with caption:
.. table:: Demonstration of simple table syntax.
- +-------+------+--------+---------+
- | Right | Left | Center | Default |
- +=======+======+========+=========+
- | 12 | 12 | 12 | 12 |
- +-------+------+--------+---------+
- | 123 | 123 | 123 | 123 |
- +-------+------+--------+---------+
- | 1 | 1 | 1 | 1 |
- +-------+------+--------+---------+
+ ===== ==== ====== =======
+ Right Left Center Default
+ ===== ==== ====== =======
+ 12 12 12 12
+ 123 123 123 123
+ 1 1 1 1
+ ===== ==== ====== =======
Simple table without caption:
-+-------+------+--------+---------+
-| Right | Left | Center | Default |
-+=======+======+========+=========+
-| 12 | 12 | 12 | 12 |
-+-------+------+--------+---------+
-| 123 | 123 | 123 | 123 |
-+-------+------+--------+---------+
-| 1 | 1 | 1 | 1 |
-+-------+------+--------+---------+
+===== ==== ====== =======
+Right Left Center Default
+===== ==== ====== =======
+12 12 12 12
+123 123 123 123
+1 1 1 1
+===== ==== ====== =======
Simple table indented two spaces:
.. table:: Demonstration of simple table syntax.
- +-------+------+--------+---------+
- | Right | Left | Center | Default |
- +=======+======+========+=========+
- | 12 | 12 | 12 | 12 |
- +-------+------+--------+---------+
- | 123 | 123 | 123 | 123 |
- +-------+------+--------+---------+
- | 1 | 1 | 1 | 1 |
- +-------+------+--------+---------+
+ ===== ==== ====== =======
+ Right Left Center Default
+ ===== ==== ====== =======
+ 12 12 12 12
+ 123 123 123 123
+ 1 1 1 1
+ ===== ==== ====== =======
Multiline table with caption:
@@ -70,13 +64,11 @@ Multiline table without caption:
Table without column headers:
-+-----+-----+-----+-----+
-| 12 | 12 | 12 | 12 |
-+-----+-----+-----+-----+
-| 123 | 123 | 123 | 123 |
-+-----+-----+-----+-----+
-| 1 | 1 | 1 | 1 |
-+-----+-----+-----+-----+
+=== === === ===
+12 12 12 12
+123 123 123 123
+1 1 1 1
+=== === === ===
Multiline table without column headers:
diff --git a/test/testsuite.native b/test/testsuite.native
index 0587bddb8..73fcc0633 100644
--- a/test/testsuite.native
+++ b/test/testsuite.native
@@ -324,7 +324,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "Shoes",Space,Str "($20)",Space,Str "and",Space,Str "socks",Space,Str "($5)."]]
,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
-,RawBlock (Format "latex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
+,RawBlock (Format "tex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,HorizontalRule
,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
@@ -384,14 +384,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,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 ("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","")]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",["uri"],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list?"]]
- ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+ ,[Plain [Link ("",["uri"],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should."]]]
-,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
+,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",["email"],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote
- [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+ [Para [Str "Blockquoted:",Space,Link ("",["uri"],[]) [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/>"
,HorizontalRule
diff --git a/test/textile-reader.native b/test/textile-reader.native
index 10bf2c857..16b5a87e8 100644
--- a/test/textile-reader.native
+++ b/test/textile-reader.native
@@ -2,7 +2,7 @@ Pandoc (Meta {unMeta = fromList []})
[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 "Textile",Space,Str "Reader.",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"]
-,Header 2 ("level-2-with-an-embeded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embeded",Space,Str "link"] ("http://www.example.com","")]
+,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"] ("http://www.example.com","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Strong [Str "emphasis"]]
,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
diff --git a/test/textile-reader.textile b/test/textile-reader.textile
index cca0b83f7..d02310b3d 100644
--- a/test/textile-reader.textile
+++ b/test/textile-reader.textile
@@ -5,7 +5,7 @@ from John Gruber's markdown test suite.
h1. Headers
-h2. Level 2 with an "embeded link":http://www.example.com
+h2. Level 2 with an "embedded link":http://www.example.com
h3. Level 3 with *emphasis*
diff --git a/test/tikiwiki-reader.native b/test/tikiwiki-reader.native
index 2ab053217..79dc4b708 100644
--- a/test/tikiwiki-reader.native
+++ b/test/tikiwiki-reader.native
@@ -43,52 +43,52 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "info@example.org"]
,Header 1 ("lists",[],[]) [Str "lists"]
,BulletList
- [[Plain [Str "Start",Space,Str "each",Space,Str "line",Space]]
- ,[Plain [Str "with",Space,Str "an",Space,Str "asterisk",Space,Str "(*).",Space]
+ [[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",Space]
+ [[Plain [Str "More",Space,Str "asterisks",Space,Str "gives",Space,Str "deeper"]
,BulletList
- [[Plain [Str "and",Space,Str "deeper",Space,Str "levels.",Space]]]]]]
- ,[Plain [Str "Line",Space,Str "breaks",LineBreak,Str "don't",Space,Str "break",Space,Str "levels.",Space]]
- ,[Plain [Str "Continuations",Space,Str "are",Space,Str "also",Space,Str "possible",Space]
+ [[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",Space]]]]
- ,[Plain [Str "Level",Space,Str "one",Space]]]
+ [[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",Space]]
- ,[Plain [Str "with",Space,Str "a",Space,Str "number",Space,Str "(1.).",Space]
+ [[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",Space]
+ [[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",Space]]
- ,[Plain [Str "levels.",Space]]]]]]
- ,[Plain [Str "Line",Space,Str "breaks",LineBreak,Str "don't",Space,Str "break",Space,Str "levels.",Space]]
- ,[Plain [Str "Blank",Space,Str "lines",Space]]]
+ [[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.",Space]]]
+ [[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",Space]]])
+ [[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",Space]]])
+ [[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"],Space]]])]
+ [[Plain [Str "definition",Space,Emph [Str "3"]]]])]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Plain [Str "one",Space]]
- ,[Plain [Str "two",Space]
+ [[Plain [Str "one"]]
+ ,[Plain [Str "two"]
,BulletList
- [[Plain [Str "two",Space,Str "point",Space,Str "one",Space]]
- ,[Plain [Str "two",Space,Str "point",Space,Str "two",Space]]]]
- ,[Plain [Str "three",Space]]
- ,[Plain [Str "four",Space]]
- ,[Plain [Str "five",Space]
+ [[Plain [Str "two",Space,Str "point",Space,Str "one"]]
+ ,[Plain [Str "two",Space,Str "point",Space,Str "two"]]]]
+ ,[Plain [Str "three"]]
+ ,[Plain [Str "four"]]
+ ,[Plain [Str "five"]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Plain [Str "five",Space,Str "sub",Space,Str "1",Space]
+ [[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",Space]]]]
- ,[Plain [Str "five",Space,Str "sub",Space,Str "2",Space]]]]]
+ [[Plain [Str "five",Space,Str "sub",Space,Str "1",Space,Str "sub",Space,Str "1"]]]]
+ ,[Plain [Str "five",Space,Str "sub",Space,Str "2"]]]]]
,Header 1 ("tables",[],[]) [Str "tables"]
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
[[Plain [Str ""]]
diff --git a/test/txt2tags.t2t b/test/txt2tags.t2t
index d374b7a85..f736cfa93 100644
--- a/test/txt2tags.t2t
+++ b/test/txt2tags.t2t
@@ -136,7 +136,7 @@ i) ***bold*** ///ital/// ___undr___ ---strk--- ```mono``` """raw"
%%% Syntax: Repetition is greedy
%% When the mark character is repeated many times,
%% the contents are expanded to the largest possible.
-%% Thats why they are greedy, the outer marks are
+%% That's why they are greedy, the outer marks are
%% the ones used.
i) ***** ///// _____ ----- ````` """"" '''''
diff --git a/test/writer.context b/test/writer.context
index bb69f4e43..d6a36f0dd 100644
--- a/test/writer.context
+++ b/test/writer.context
@@ -706,6 +706,12 @@ These shouldn't be math:
Here's a LaTeX table:
+\begin{tabular}{|l|l|}\hline
+Animal & Number \\ \hline
+Dog & 2 \\
+Cat & 1 \\ \hline
+\end{tabular}
+
\thinrule
\section[title={Special Characters},reference={special-characters}]
diff --git a/test/writer.docbook4 b/test/writer.docbook4
index 163255974..38b3cc1ee 100644
--- a/test/writer.docbook4
+++ b/test/writer.docbook4
@@ -1298,7 +1298,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<title>Autolinks</title>
<para>
With an ampersand:
- <ulink url="http://example.com/?foo=1&amp;bar=2">http://example.com/?foo=1&amp;bar=2</ulink>
+ <ulink url="http://example.com/?foo=1&amp;bar=2" role="uri">http://example.com/?foo=1&amp;bar=2</ulink>
</para>
<itemizedlist spacing="compact">
<listitem>
@@ -1308,7 +1308,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{
</listitem>
<listitem>
<para>
- <ulink url="http://example.com/">http://example.com/</ulink>
+ <ulink url="http://example.com/" role="uri">http://example.com/</ulink>
</para>
</listitem>
<listitem>
@@ -1323,7 +1323,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<blockquote>
<para>
Blockquoted:
- <ulink url="http://example.com/">http://example.com/</ulink>
+ <ulink url="http://example.com/" role="uri">http://example.com/</ulink>
</para>
</blockquote>
<para>
diff --git a/test/writer.docbook5 b/test/writer.docbook5
index 992cd8b63..9a9eff0c5 100644
--- a/test/writer.docbook5
+++ b/test/writer.docbook5
@@ -1273,7 +1273,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<title>Autolinks</title>
<para>
With an ampersand:
- <link xlink:href="http://example.com/?foo=1&amp;bar=2">http://example.com/?foo=1&amp;bar=2</link>
+ <link xlink:href="http://example.com/?foo=1&amp;bar=2" role="uri">http://example.com/?foo=1&amp;bar=2</link>
</para>
<itemizedlist spacing="compact">
<listitem>
@@ -1283,7 +1283,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{
</listitem>
<listitem>
<para>
- <link xlink:href="http://example.com/">http://example.com/</link>
+ <link xlink:href="http://example.com/" role="uri">http://example.com/</link>
</para>
</listitem>
<listitem>
@@ -1298,7 +1298,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<blockquote>
<para>
Blockquoted:
- <link xlink:href="http://example.com/">http://example.com/</link>
+ <link xlink:href="http://example.com/" role="uri">http://example.com/</link>
</para>
</blockquote>
<para>
diff --git a/test/writer.fb2 b/test/writer.fb2
index b2d002230..6940e6217 100644
--- a/test/writer.fb2
+++ b/test/writer.fb2
@@ -3,7 +3,6 @@
<description>
<title-info>
<genre>unrecognised</genre>
-<book-title>Pandoc Test Suite</book-title>
<author>
<first-name>John</first-name>
<last-name>MacFarlane</last-name>
@@ -11,6 +10,7 @@
<author>
<nickname>Anonymous</nickname>
</author>
+<book-title>Pandoc Test Suite</book-title>
<date>July 17, 2006</date>
</title-info>
<document-info>
diff --git a/test/writer.haddock b/test/writer.haddock
index 7f783abd1..13f22021d 100644
--- a/test/writer.haddock
+++ b/test/writer.haddock
@@ -455,14 +455,14 @@ ______________________________________________________________________________
#latex#
-
-- 2 + 2 = 4
-- /x/ ∈ /y/
-- /α/ ∧ /ω/
-- 223
-- /p/-Tree
+- \(2+2=4\)
+- \(x \in y\)
+- \(\alpha \wedge \omega\)
+- \(223\)
+- \(p\)-Tree
- Here’s some display math:
- $$\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}$$
-- Here’s one that has a line break in it: /α/ + /ω/ × /x/2.
+ \[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\]
+- Here’s one that has a line break in it: \(\alpha + \omega \times x^2\).
These shouldn’t be math:
diff --git a/test/writer.html4 b/test/writer.html4
index dc889f07a..bed6617a0 100644
--- a/test/writer.html4
+++ b/test/writer.html4
@@ -508,7 +508,7 @@ Blah
<li><a href="http://example.com/" class="uri">http://example.com/</a></li>
<li>It should.</li>
</ul>
-<p>An e-mail address: <a href="mailto:nobody@nowhere.net">nobody@nowhere.net</a></p>
+<p>An e-mail address: <a href="mailto:nobody@nowhere.net" class="email">nobody@nowhere.net</a></p>
<blockquote>
<p>Blockquoted: <a href="http://example.com/" class="uri">http://example.com/</a></p>
</blockquote>
diff --git a/test/writer.html5 b/test/writer.html5
index 53fcb84e2..46105d0a6 100644
--- a/test/writer.html5
+++ b/test/writer.html5
@@ -19,7 +19,7 @@
<![endif]-->
</head>
<body>
-<header>
+<header id="title-block-header">
<h1 class="title">Pandoc Test Suite</h1>
<p class="author">John MacFarlane</p>
<p class="author">Anonymous</p>
@@ -511,7 +511,7 @@ Blah
<li><a href="http://example.com/" class="uri">http://example.com/</a></li>
<li>It should.</li>
</ul>
-<p>An e-mail address: <a href="mailto:nobody@nowhere.net">nobody@nowhere.net</a></p>
+<p>An e-mail address: <a href="mailto:nobody@nowhere.net" class="email">nobody@nowhere.net</a></p>
<blockquote>
<p>Blockquoted: <a href="http://example.com/" class="uri">http://example.com/</a></p>
</blockquote>
diff --git a/test/writer.jats b/test/writer.jats
index b51addf3b..f87b2325a 100644
--- a/test/writer.jats
+++ b/test/writer.jats
@@ -583,7 +583,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</preformat>
</boxed-text>
<p>Interpreted markdown in a table:</p>
<p>This is <italic>emphasized</italic></p>
- <p>And this is <bold role="strong">strong</bold></p>
+ <p>And this is <bold>strong</bold></p>
<p>Here’s a simple block:</p>
<boxed-text>
<p>foo</p>
@@ -614,14 +614,13 @@ These should not be escaped: \$ \\ \&gt; \[ \{</preformat>
<sec id="inline-markup">
<title>Inline Markup</title>
<p>This is <italic>emphasized</italic>, and so <italic>is this</italic>.</p>
- <p>This is <bold role="strong">strong</bold>, and so <bold role="strong">is
- this</bold>.</p>
+ <p>This is <bold>strong</bold>, and so <bold>is this</bold>.</p>
<p>An <italic><ext-link ext-link-type="uri" xlink:href="/url">emphasized
link</ext-link></italic>.</p>
- <p><bold role="strong"><italic>This is strong and em.</italic></bold></p>
- <p>So is <bold role="strong"><italic>this</italic></bold> word.</p>
- <p><bold role="strong"><italic>This is strong and em.</italic></bold></p>
- <p>So is <bold role="strong"><italic>this</italic></bold> word.</p>
+ <p><bold><italic>This is strong and em.</italic></bold></p>
+ <p>So is <bold><italic>this</italic></bold> word.</p>
+ <p><bold><italic>This is strong and em.</italic></bold></p>
+ <p>So is <bold><italic>this</italic></bold> word.</p>
<p>This is code: <monospace>&gt;</monospace>, <monospace>$</monospace>,
<monospace>\</monospace>, <monospace>\$</monospace>,
<monospace>&lt;html&gt;</monospace>.</p>
diff --git a/test/writer.muse b/test/writer.muse
index 9492a5517..35d43a751 100644
--- a/test/writer.muse
+++ b/test/writer.muse
@@ -11,7 +11,7 @@ markdown test suite.
** Level 2 with an [[/url][embedded link]]
-*** Level 3 with <em>emphasis</em>
+*** Level 3 with *emphasis*
**** Level 4
@@ -19,7 +19,7 @@ markdown test suite.
* Level 1
-** Level 2 with <em>emphasis</em>
+** Level 2 with *emphasis*
*** Level 3
@@ -271,18 +271,18 @@ Loose:
Multiple blocks with italics:
- <em>apple</em> :: red fruit
+ *apple* :: red fruit
- contains seeds, crisp, pleasant to taste
- <em>orange</em> :: orange fruit
+ contains seeds, crisp, pleasant to taste
+ *orange* :: orange fruit
- <example>
- { orange code block }
- </example>
+ <example>
+ { orange code block }
+ </example>
- <quote>
- orange block quote
- </quote>
+ <quote>
+ orange block quote
+ </quote>
Multiple definitions, tight:
@@ -331,7 +331,7 @@ Interpreted markdown in a table:
<td>
</literal>
-This is <em>emphasized</em>
+This is *emphasized*
<literal style="html">
</td>
@@ -341,7 +341,7 @@ This is <em>emphasized</em>
<td>
</literal>
-And this is <strong>strong</strong>
+And this is **strong**
<literal style="html">
</td>
@@ -461,27 +461,25 @@ Hr’s:
* Inline Markup
-This is <em>emphasized</em>, and so <em>is this</em>.
+This is *emphasized*, and so *is this*.
-This is <strong>strong</strong>, and so <strong>is this</strong>.
+This is **strong**, and so **is this**.
-An <em>[[/url][emphasized link]]</em>.
+An *[[/url][emphasized link]]*.
-<strong><em>This is strong and em.</em></strong>
+***This is strong and em.***
-So is <strong><em>this</em></strong> word.
+So is ***this*** word.
-<strong><em>This is strong and em.</em></strong>
+***This is strong and em.***
-So is <strong><em>this</em></strong> word.
+So is ***this*** word.
-This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>,
-<code><html></code>.
+This is code: =>=, =$=, =\=, =\$=, =<html>=.
-<del>This is <em>strikeout</em>.</del>
+<del>This is *strikeout*.</del>
-Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup>
-a<sup>hello there</sup>.
+Superscripts: a<sup>bc</sup>d a<sup>*hello*</sup> a<sup>hello there</sup>.
Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.
@@ -500,8 +498,8 @@ spaces: a^b c^d, a~b c~d.
‘He said, “I want to go.”’ Were you alive in the 70’s?
-Here is some quoted ‘<code>code</code>’ and a
-“[[http://example.com/?foo=1&bar=2][quoted link]]”.
+Here is some quoted ‘=code=’ and a “[[http://example.com/?foo=1&bar=2][quoted
+link]]”.
Some dashes: one—two — three—four — five.
@@ -515,26 +513,25 @@ Ellipses…and…and….
- <literal style="tex">\cite[22-23]{smith.1899}</literal>
- <verbatim>2 + 2 = 4</verbatim>
- - <em>x</em> ∈ <em>y</em>
- - <em>α</em> ∧ <em>ω</em>
+ - *x* ∈ *y*
+ - *α* ∧ *ω*
- 223
- - <em>p</em>-Tree
+ - *p*-Tree
- Here’s some display math:
<verbatim>$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</verbatim>
- - Here’s one that has a line break in it:
- <em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup>.
+ - Here’s one that has a line break in it: *α* + *ω* × *x*<sup>2</sup>.
These shouldn’t be math:
- To get the famous equation, write <code>$e = mc^2$</code>.
- - $22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is
+ - $22,000 is a *lot* of money. So is $34,000. (It worked if “lot” is
emphasized.)
- Shoes ($20) and socks ($5).
- - Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.
+ - Escaped =$=: $73 *this should be emphasized* 23$.
Here’s a LaTeX table:
-<literal style="latex">
+<literal style="tex">
\begin{tabular}{|l|l|}\hline
Animal & Number \\ \hline
Dog & 2 \\
@@ -669,7 +666,7 @@ An e-mail address: [[mailto:nobody@nowhere.net][nobody@nowhere.net]]
Blockquoted: [[http://example.com/]]
</quote>
-Auto-links should not occur here: <code><http://example.com/></code>
+Auto-links should not occur here: =<http://example.com/>=
<example>
or here: <http://example.com/>
@@ -689,7 +686,7 @@ Here is a movie [[movie.jpg][movie]] icon.
* Footnotes
-Here is a footnote reference,[1] and another.[2] This should <em>not</em> be a
+Here is a footnote reference,[1] and another.[2] This should *not* be a
footnote reference, because it contains a space.[^my note] Here is an inline
note.[3]
@@ -716,9 +713,9 @@ This paragraph should not be part of the note, as it is not indented.
If you want, you can indent every line, but you can also be lazy and just
indent the first line of each block.
-[3] This is <em>easier</em> to type. Inline notes may contain
- [[http://google.com][links]] and <code>]</code> verbatim characters, as
- well as [bracketed text].
+[3] This is *easier* to type. Inline notes may contain
+ [[http://google.com][links]] and =]= verbatim characters, as well as
+ [bracketed text].
[4] In quote.
diff --git a/test/writer.native b/test/writer.native
index 0587bddb8..73fcc0633 100644
--- a/test/writer.native
+++ b/test/writer.native
@@ -324,7 +324,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "Shoes",Space,Str "($20)",Space,Str "and",Space,Str "socks",Space,Str "($5)."]]
,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
-,RawBlock (Format "latex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
+,RawBlock (Format "tex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,HorizontalRule
,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
@@ -384,14 +384,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,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 ("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","")]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",["uri"],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list?"]]
- ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+ ,[Plain [Link ("",["uri"],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should."]]]
-,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
+,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",["email"],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote
- [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+ [Para [Str "Blockquoted:",Space,Link ("",["uri"],[]) [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/>"
,HorizontalRule
diff --git a/test/writer.opendocument b/test/writer.opendocument
index 081b33971..09a246b52 100644
--- a/test/writer.opendocument
+++ b/test/writer.opendocument
@@ -6,629 +6,1007 @@
<office:automatic-styles>
<text:list-style style:name="L1">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L2">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L3">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L4">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L5">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L6">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L7">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L8">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L9">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L10">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L11">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L12">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L13">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L14">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L15">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L16">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L17">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L18">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L19">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L20">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L21">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L22">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="2" style:num-prefix="(" style:num-suffix=")">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
<text:list-level-style-number text:level="2" text:style-name="Numbering_20_Symbols" style:num-format="i" text:start-value="4" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-number>
<text:list-level-style-number text:level="3" text:style-name="Numbering_20_Symbols" style:num-format="A" text:start-value="1" style:num-prefix="(" style:num-suffix=")">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L23">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="A" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
<text:list-level-style-number text:level="2" text:style-name="Numbering_20_Symbols" style:num-format="I" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-number>
<text:list-level-style-number text:level="3" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="6" style:num-prefix="(" style:num-suffix=")">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
<text:list-level-style-number text:level="4" text:style-name="Numbering_20_Symbols" style:num-format="a" text:start-value="3" style:num-suffix=")">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L24">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
<text:list-level-style-number text:level="2" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L25">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<text:list-style style:name="L26">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L27">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L28">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L29">
<text:list-level-style-bullet text:level="1" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="2" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="0.4in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.0in" fo:text-indent="-0.1in" fo:margin-left="1.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="3" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="0.8in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="1.5in" fo:text-indent="-0.1in" fo:margin-left="1.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="4" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="1.2000000000000002in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.0in" fo:text-indent="-0.1in" fo:margin-left="2.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="5" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="1.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="2.5in" fo:text-indent="-0.1in" fo:margin-left="2.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="6" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="2.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.0in" fo:text-indent="-0.1in" fo:margin-left="3.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="7" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="2.4000000000000004in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="3.5in" fo:text-indent="-0.1in" fo:margin-left="3.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="8" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="◦">
- <style:list-level-properties text:space-before="2.8000000000000003in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.0in" fo:text-indent="-0.1in" fo:margin-left="4.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="9" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="▪">
- <style:list-level-properties text:space-before="3.2in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="4.5in" fo:text-indent="-0.1in" fo:margin-left="4.5in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
<text:list-level-style-bullet text:level="10" text:style-name="Bullet_20_Symbols" style:num-suffix="." text:bullet-char="•">
- <style:list-level-properties text:space-before="3.6in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="5.0in" fo:text-indent="-0.1in" fo:margin-left="5.0in" />
+ </style:list-level-properties>
</text:list-level-style-bullet>
</text:list-style>
<text:list-style style:name="L30">
<text:list-level-style-number text:level="1" text:style-name="Numbering_20_Symbols" style:num-format="1" text:start-value="1" style:num-suffix=".">
- <style:list-level-properties text:space-before="0.0in" text:min-label-width="0.4in" />
+ <style:list-level-properties text:list-level-position-and-space-mode="label-alignment" fo:text-align="right">
+ <style:list-level-label-alignment text:label-followed-by="listtab" text:list-tab-stop-position="0.5in" fo:text-indent="-0.1in" fo:margin-left="0.5in" />
+ </style:list-level-properties>
</text:list-level-style-number>
</text:list-style>
<style:style style:name="T1" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
@@ -803,23 +1181,31 @@
<text:p text:style-name="Text_20_body">This is a set of tests for pandoc. Most
of them are adapted from John Gruber’s markdown test suite.</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Headers</text:h>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Level 2 with an
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="headers" />Headers<text:bookmark-end text:name="headers" /></text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="level-2-with-an-embedded-link" />Level
+2 with an
<text:a xlink:type="simple" xlink:href="/url" office:name=""><text:span text:style-name="Definition">embedded
-link</text:span></text:a></text:h>
-<text:h text:style-name="Heading_20_3" text:outline-level="3">Level 3 with
-<text:span text:style-name="T1">emphasis</text:span></text:h>
-<text:h text:style-name="Heading_20_4" text:outline-level="4">Level 4</text:h>
-<text:h text:style-name="Heading_20_5" text:outline-level="5">Level 5</text:h>
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Level 1</text:h>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Level 2 with
-<text:span text:style-name="T1">emphasis</text:span></text:h>
-<text:h text:style-name="Heading_20_3" text:outline-level="3">Level 3</text:h>
+link</text:span></text:a><text:bookmark-end text:name="level-2-with-an-embedded-link" /></text:h>
+<text:h text:style-name="Heading_20_3" text:outline-level="3"><text:bookmark-start text:name="level-3-with-emphasis" />Level
+3 with
+<text:span text:style-name="T1">emphasis</text:span><text:bookmark-end text:name="level-3-with-emphasis" /></text:h>
+<text:h text:style-name="Heading_20_4" text:outline-level="4"><text:bookmark-start text:name="level-4" />Level
+4<text:bookmark-end text:name="level-4" /></text:h>
+<text:h text:style-name="Heading_20_5" text:outline-level="5"><text:bookmark-start text:name="level-5" />Level
+5<text:bookmark-end text:name="level-5" /></text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="level-1" />Level
+1<text:bookmark-end text:name="level-1" /></text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="level-2-with-emphasis" />Level
+2 with
+<text:span text:style-name="T1">emphasis</text:span><text:bookmark-end text:name="level-2-with-emphasis" /></text:h>
+<text:h text:style-name="Heading_20_3" text:outline-level="3"><text:bookmark-start text:name="level-3" />Level
+3<text:bookmark-end text:name="level-3" /></text:h>
<text:p text:style-name="First_20_paragraph">with no blank line</text:p>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Level 2</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="level-2" />Level
+2<text:bookmark-end text:name="level-2" /></text:h>
<text:p text:style-name="First_20_paragraph">with no blank line</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Paragraphs</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="paragraphs" />Paragraphs<text:bookmark-end text:name="paragraphs" /></text:h>
<text:p text:style-name="First_20_paragraph">Here’s a regular
paragraph.</text:p>
<text:p text:style-name="Text_20_body">In Markdown 1.0.0 and earlier. Version
@@ -830,8 +1216,8 @@ criminey.</text:p>
<text:p text:style-name="Text_20_body">There should be a hard line
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>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="block-quotes" />Block
+Quotes<text:bookmark-end text:name="block-quotes" /></text:h>
<text:p text:style-name="First_20_paragraph">E-mail style:</text:p>
<text:p text:style-name="P1">This is a block quote. It is pretty
short.</text:p>
@@ -855,8 +1241,8 @@ short.</text:p>
2 &gt; 1.</text:p>
<text:p text:style-name="Text_20_body">And a following paragraph.</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Code
-Blocks</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="code-blocks" />Code
+Blocks<text:bookmark-end text:name="code-blocks" /></text:h>
<text:p text:style-name="First_20_paragraph">Code:</text:p>
<text:p text:style-name="P9">---- (should be four hyphens)</text:p>
<text:p text:style-name="P10"></text:p>
@@ -870,8 +1256,8 @@ Blocks</text:h>
<text:p text:style-name="P17"></text:p>
<text:p text:style-name="P18">These should not be escaped: <text:s text:c="1" />\$ \\ \&gt; \[ \{</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Lists</text:h>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Unordered</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="lists" />Lists<text:bookmark-end text:name="lists" /></text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="unordered" />Unordered<text:bookmark-end text:name="unordered" /></text:h>
<text:p text:style-name="First_20_paragraph">Asterisks tight:</text:p>
<text:list text:style-name="L2">
<text:list-item>
@@ -944,7 +1330,7 @@ Blocks</text:h>
<text:p text:style-name="P24">Minus 3</text:p>
</text:list-item>
</text:list>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Ordered</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="ordered" />Ordered<text:bookmark-end text:name="ordered" /></text:h>
<text:p text:style-name="First_20_paragraph">Tight:</text:p>
<text:list text:style-name="L8">
<text:list-item>
@@ -1007,7 +1393,7 @@ Blocks</text:h>
<text:p text:style-name="P29">Item 3.</text:p>
</text:list-item>
</text:list>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Nested</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="nested" />Nested<text:bookmark-end text:name="nested" /></text:h>
<text:list text:style-name="L13">
<text:list-item>
<text:p text:style-name="P30">Tab</text:p><text:list text:style-name="L14">
@@ -1068,8 +1454,8 @@ paragraphs:</text:p>
<text:p text:style-name="P35">Third</text:p>
</text:list-item>
</text:list>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Tabs and
-spaces</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="tabs-and-spaces" />Tabs
+and spaces<text:bookmark-end text:name="tabs-and-spaces" /></text:h>
<text:list text:style-name="L20">
<text:list-item>
<text:p text:style-name="P37">this is a list item indented with
@@ -1089,8 +1475,8 @@ spaces</text:h>
</text:list>
</text:list-item>
</text:list>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Fancy list
-markers</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="fancy-list-markers" />Fancy
+list markers<text:bookmark-end text:name="fancy-list-markers" /></text:h>
<text:list text:style-name="L22">
<text:list-item>
<text:p text:style-name="P39">begins with 2</text:p>
@@ -1157,8 +1543,8 @@ item:</text:p>
<text:p text:style-name="Text_20_body">M.A. 2007</text:p>
<text:p text:style-name="Text_20_body">B. Williams</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Definition
-Lists</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="definition-lists" />Definition
+Lists<text:bookmark-end text:name="definition-lists" /></text:h>
<text:p text:style-name="First_20_paragraph">Tight using spaces:</text:p>
<text:p text:style-name="Definition_20_Term_20_Tight">apple</text:p>
<text:p text:style-name="Definition_20_Definition_20_Tight">red fruit</text:p>
@@ -1225,8 +1611,8 @@ fruit</text:p><text:list text:style-name="L25">
<text:p text:style-name="P44">sublist</text:p>
</text:list-item>
</text:list>
-<text:h text:style-name="Heading_20_1" text:outline-level="1">HTML
-Blocks</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="html-blocks" />HTML
+Blocks<text:bookmark-end text:name="html-blocks" /></text:h>
<text:p text:style-name="First_20_paragraph">Simple block on one
line:</text:p>
<text:p text:style-name="Text_20_body">foo</text:p>
@@ -1262,8 +1648,8 @@ spaces on the line:</text:p>
<text:p text:style-name="P50">&lt;hr /&gt;</text:p>
<text:p text:style-name="First_20_paragraph">Hr’s:</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Inline
-Markup</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="inline-markup" />Inline
+Markup<text:bookmark-end text:name="inline-markup" /></text:h>
<text:p text:style-name="First_20_paragraph">This is
<text:span text:style-name="T1">emphasized</text:span>, and so
<text:span text:style-name="T1">is this</text:span>.</text:p>
@@ -1300,8 +1686,9 @@ H<text:span text:style-name="T8">many of them</text:span>O.</text:p>
<text:p text:style-name="Text_20_body">These should not be superscripts or
subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Smart quotes,
-ellipses, dashes</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="smart-quotes-ellipses-dashes" />Smart
+quotes, ellipses,
+dashes<text:bookmark-end text:name="smart-quotes-ellipses-dashes" /></text:h>
<text:p text:style-name="First_20_paragraph">“Hello,” said the spider.
“‘Shelob’ is my name.”</text:p>
<text:p text:style-name="Text_20_body">‘A’, ‘B’, and ‘C’ are letters.</text:p>
@@ -1319,7 +1706,7 @@ five.</text:p>
1987–1999.</text:p>
<text:p text:style-name="Text_20_body">Ellipses…and…and….</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">LaTeX</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="latex" />LaTeX<text:bookmark-end text:name="latex" /></text:h>
<text:list text:style-name="L26">
<text:list-item>
<text:p text:style-name="P51"></text:p>
@@ -1371,8 +1758,8 @@ five.</text:p>
</text:list>
<text:p text:style-name="First_20_paragraph">Here’s a LaTeX table:</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Special
-Characters</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="special-characters" />Special
+Characters<text:bookmark-end text:name="special-characters" /></text:h>
<text:p text:style-name="First_20_paragraph">Here is some unicode:</text:p>
<text:list text:style-name="L28">
<text:list-item>
@@ -1415,8 +1802,8 @@ it.</text:p>
<text:p text:style-name="Text_20_body">Plus: +</text:p>
<text:p text:style-name="Text_20_body">Minus: -</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Links</text:h>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Explicit</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="links" />Links<text:bookmark-end text:name="links" /></text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="explicit" />Explicit<text:bookmark-end text:name="explicit" /></text:h>
<text:p text:style-name="First_20_paragraph">Just a
<text:a xlink:type="simple" xlink:href="/url/" office:name=""><text:span text:style-name="Definition">URL</text:span></text:a>.</text:p>
<text:p text:style-name="Text_20_body"><text:a xlink:type="simple" xlink:href="/url/" office:name="title"><text:span text:style-name="Definition">URL
@@ -1433,7 +1820,7 @@ and title</text:span></text:a></text:p>
<text:p text:style-name="Text_20_body"><text:a xlink:type="simple" xlink:href="mailto:nobody@nowhere.net" office:name=""><text:span text:style-name="Definition">Email
link</text:span></text:a></text:p>
<text:p text:style-name="Text_20_body"><text:a xlink:type="simple" xlink:href="" office:name=""><text:span text:style-name="Definition">Empty</text:span></text:a>.</text:p>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Reference</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="reference" />Reference<text:bookmark-end text:name="reference" /></text:h>
<text:p text:style-name="First_20_paragraph">Foo
<text:a xlink:type="simple" xlink:href="/url/" office:name=""><text:span text:style-name="Definition">bar</text:span></text:a>.</text:p>
<text:p text:style-name="Text_20_body">With
@@ -1453,8 +1840,8 @@ by itself should be a link.</text:p>
<text:a xlink:type="simple" xlink:href="/url/" office:name="Title with &quot;quotes&quot; inside"><text:span text:style-name="Definition">bar</text:span></text:a>.</text:p>
<text:p text:style-name="Text_20_body">Foo
<text:a xlink:type="simple" xlink:href="/url/" office:name="Title with &quot;quote&quot; inside"><text:span text:style-name="Definition">biz</text:span></text:a>.</text:p>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">With
-ampersands</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="with-ampersands" />With
+ampersands<text:bookmark-end text:name="with-ampersands" /></text:h>
<text:p text:style-name="First_20_paragraph">Here’s a
<text:a xlink:type="simple" xlink:href="http://example.com/?foo=1&amp;bar=2" office:name=""><text:span text:style-name="Definition">link
with an ampersand in the URL</text:span></text:a>.</text:p>
@@ -1467,7 +1854,7 @@ link</text:span></text:a>.</text:p>
<text:p text:style-name="Text_20_body">Here’s an
<text:a xlink:type="simple" xlink:href="/script?foo=1&amp;bar=2" office:name=""><text:span text:style-name="Definition">inline
link in pointy braces</text:span></text:a>.</text:p>
-<text:h text:style-name="Heading_20_2" text:outline-level="2">Autolinks</text:h>
+<text:h text:style-name="Heading_20_2" text:outline-level="2"><text:bookmark-start text:name="autolinks" />Autolinks<text:bookmark-end text:name="autolinks" /></text:h>
<text:p text:style-name="First_20_paragraph">With an ampersand:
<text:a xlink:type="simple" xlink:href="http://example.com/?foo=1&amp;bar=2" office:name=""><text:span text:style-name="Definition">http://example.com/?foo=1&amp;bar=2</text:span></text:a></text:p>
<text:list text:style-name="L29">
@@ -1489,16 +1876,16 @@ link in pointy braces</text:span></text:a>.</text:p>
<text:span text:style-name="Source_Text">&lt;http://example.com/&gt;</text:span></text:p>
<text:p text:style-name="P57">or here: &lt;http://example.com/&gt;</text:p>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Images</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="images" />Images<text:bookmark-end text:name="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="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="FigureCaption">Figure <text:sequence text:ref-name="refIllustration0" text:name="Illustration" text:formula="ooow:Illustration+1" style:num-format="1">1</text:sequence>: 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>
<text:p text:style-name="Horizontal_20_Line" />
-<text:h text:style-name="Heading_20_1" text:outline-level="1">Footnotes</text:h>
+<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="footnotes" />Footnotes<text:bookmark-end text:name="footnotes" /></text:h>
<text:p text:style-name="First_20_paragraph">Here is a footnote
reference,<text:note text:id="ftn0" text:note-class="footnote"><text:note-citation>1</text:note-citation><text:note-body><text:p text:style-name="Footnote">Here
is the footnote. It can go anywhere after the footnote reference. It need not
diff --git a/test/writer.org b/test/writer.org
index 1ae0ca8f3..32fcfc404 100644
--- a/test/writer.org
+++ b/test/writer.org
@@ -584,7 +584,7 @@ Superscripts: a^{bc}d a^{/hello/} a^{hello there}.
Subscripts: H_{2}O, H_{23}O, H_{many of them}O.
These should not be superscripts or subscripts, because of the unescaped
-spaces: a\^b c\^d, a~b c~d.
+spaces: a^b c^d, a~b c~d.
--------------
@@ -674,7 +674,7 @@ Backtick: `
Asterisk: *
-Underscore: \_
+Underscore: _
Left brace: {
@@ -724,7 +724,7 @@ Just a [[/url/][URL]].
[[/url/][URL and title]]
-[[/url/with_underscore][with\_underscore]]
+[[/url/with_underscore][with_underscore]]
[[mailto:nobody@nowhere.net][Email link]]
@@ -816,7 +816,7 @@ Here is a movie [[file:movie.jpg]] icon.
:END:
Here is a footnote reference,[fn:1] and another.[fn:2] This should /not/ be a
-footnote reference, because it contains a space.[\^my note] Here is an inline
+footnote reference, because it contains a space.[^my note] Here is an inline
note.[fn:3]
#+BEGIN_QUOTE
diff --git a/test/writer.rst b/test/writer.rst
index 0c986b887..b47490de2 100644
--- a/test/writer.rst
+++ b/test/writer.rst
@@ -385,53 +385,23 @@ HTML Blocks
Simple block on one line:
-.. raw:: html
-
- <div>
-
-foo
+.. container::
-.. raw:: html
-
- </div>
+ foo
And nested without indentation:
-.. raw:: html
-
- <div>
-
-.. raw:: html
-
- <div>
-
-.. raw:: html
-
- <div>
-
-foo
-
-.. raw:: html
-
- </div>
-
-.. raw:: html
-
- </div>
+.. container::
-.. raw:: html
+ .. container::
- <div>
+ .. container::
-bar
+ foo
-.. raw:: html
+ .. container::
- </div>
-
-.. raw:: html
-
- </div>
+ bar
Interpreted markdown in a table:
@@ -477,15 +447,9 @@ And this is **strong**
Here’s a simple block:
-.. raw:: html
-
- <div>
-
-foo
-
-.. raw:: html
+.. container::
- </div>
+ foo
This should be a code block, though:
@@ -503,31 +467,13 @@ As should this:
Now, nested:
-.. raw:: html
-
- <div>
+.. container::
-.. raw:: html
+ .. container::
- <div>
+ .. container::
-.. raw:: html
-
- <div>
-
-foo
-
-.. raw:: html
-
- </div>
-
-.. raw:: html
-
- </div>
-
-.. raw:: html
-
- </div>
+ foo
This should just be an HTML comment:
diff --git a/test/writer.tei b/test/writer.tei
index 779aa337b..587a6fcca 100644
--- a/test/writer.tei
+++ b/test/writer.tei
@@ -8,8 +8,8 @@
<author>Anonymous</author>
</titleStmt>
<publicationStmt>
- <p></p>
- </publicationStmt>
+ <date>July 17, 2006</date>
+ </publicationStmt>
<sourceDesc>
<p>Produced by pandoc.</p>
</sourceDesc>
diff --git a/test/writer.texinfo b/test/writer.texinfo
index f5727d96d..ebc0447ee 100644
--- a/test/writer.texinfo
+++ b/test/writer.texinfo
@@ -5,24 +5,6 @@
~~\text\~~
@end macro
-@macro textsubscript{text}
-@iftex
-@textsubscript{\text\}
-@end iftex
-@ifnottex
-_@{\text\@}
-@end ifnottex
-@end macro
-
-@macro textsuperscript{text}
-@iftex
-@textsuperscript{\text\}
-@end iftex
-@ifnottex
-^@{\text\@}
-@end ifnottex
-@end macro
-
@ifnottex
@paragraphindent 0
@end ifnottex
@@ -738,11 +720,9 @@ 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@sup{bc}d a@sup{@emph{hello}} a@sup{hello@ there}.
-Subscripts: H@textsubscript{2}O, H@textsubscript{23}O,
-H@textsubscript{many@ of@ them}O.
+Subscripts: H@sub{2}O, H@sub{23}O, H@sub{many@ of@ them}O.
These should not be superscripts or subscripts, because of the unescaped
spaces: a^b c^d, a~b c~d.
diff --git a/test/writer.textile b/test/writer.textile
index d19b698f9..78e659091 100644
--- a/test/writer.textile
+++ b/test/writer.textile
@@ -660,7 +660,7 @@ With an ampersand: "$":http://example.com/?foo=1&bar=2
* "$":http://example.com/
* It should.
-An e&#45;mail address: "nobody&#64;nowhere.net":mailto:nobody@nowhere.net
+An e&#45;mail address: "(email)nobody&#64;nowhere.net":mailto:nobody@nowhere.net
bq. Blockquoted: "$":http://example.com/