aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Command.hs6
-rw-r--r--test/Tests/Lua.hs37
-rw-r--r--test/Tests/Readers/Creole.hs2
-rw-r--r--test/Tests/Readers/Docx.hs15
-rw-r--r--test/Tests/Readers/EPUB.hs2
-rw-r--r--test/Tests/Readers/Muse.hs113
-rw-r--r--test/Tests/Readers/Org/Block/Header.hs2
-rw-r--r--test/Tests/Readers/Org/Block/List.hs18
-rw-r--r--test/Tests/Readers/Org/Directive.hs4
-rw-r--r--test/Tests/Readers/Org/Inline.hs59
-rw-r--r--test/Tests/Readers/Org/Inline/Note.hs1
-rw-r--r--test/Tests/Readers/Org/Inline/Smart.hs4
-rw-r--r--test/Tests/Readers/Org/Meta.hs28
-rw-r--r--test/Tests/Readers/RST.hs29
-rw-r--r--test/Tests/Readers/Txt2Tags.hs8
-rw-r--r--test/Tests/Shared.hs36
-rw-r--r--test/Tests/Writers/ConTeXt.hs62
-rw-r--r--test/Tests/Writers/Docbook.hs2
-rw-r--r--test/Tests/Writers/FB2.hs2
-rw-r--r--test/Tests/Writers/JATS.hs2
-rw-r--r--test/Tests/Writers/Markdown.hs42
-rw-r--r--test/Tests/Writers/Muse.hs13
-rw-r--r--test/Tests/Writers/Native.hs2
-rw-r--r--test/Tests/Writers/Powerpoint.hs341
-rw-r--r--test/Tests/Writers/RST.hs10
-rw-r--r--test/Tests/Writers/TEI.hs2
-rw-r--r--test/command/4159.md3
-rw-r--r--test/command/4240.md33
-rw-r--r--test/command/4253.md8
-rw-r--r--test/command/4254.md12
-rw-r--r--test/command/4280.md7
-rw-r--r--test/command/4281.md18
-rw-r--r--test/command/adjacent_latex_blocks.md9
-rw-r--r--test/command/cite-in-inline-note.md6
-rw-r--r--test/command/macros.md3
-rw-r--r--test/docx/instrText_hyperlink.docxbin0 -> 13628 bytes
-rw-r--r--test/docx/instrText_hyperlink.native1
-rw-r--r--test/markdown-reader-more.native4
-rw-r--r--test/pptx/inline_formatting.native5
-rw-r--r--test/pptx/inline_formatting.pptxbin0 -> 25582 bytes
-rw-r--r--test/pptx/slide_breaks.native7
-rw-r--r--test/pptx/slide_breaks.pptxbin0 -> 28032 bytes
-rw-r--r--test/pptx/slide_breaks_slide_level_1.pptxbin0 -> 27202 bytes
-rw-r--r--test/rst-reader.native2
-rw-r--r--test/tables.context365
-rw-r--r--test/tables.markdown16
-rw-r--r--test/tables.plain16
-rw-r--r--test/writer.context5
-rw-r--r--test/writer.muse13
-rw-r--r--test/writers-lang-and-dir.context5
50 files changed, 867 insertions, 513 deletions
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs
index 4999ff45a..de83d0639 100644
--- a/test/Tests/Command.hs
+++ b/test/Tests/Command.hs
@@ -40,7 +40,7 @@ runTest testname pandocpath cmd inp norm = testCase testname $ do
-- filter \r so the tests will work on Windows machines
let out = filter (/= '\r') $ err' ++ out'
result <- if ec == ExitSuccess
- then do
+ then
if out == norm
then return TestPassed
else return
@@ -52,6 +52,7 @@ runTest testname pandocpath cmd inp norm = testCase testname $ do
assertBool (show result) (result == TestPassed)
tests :: TestTree
+{-# NOINLINE tests #-}
tests = unsafePerformIO $ do
pandocpath <- findPandoc
files <- filter (".md" `isSuffixOf`) <$>
@@ -89,7 +90,6 @@ extractCommandTest pandocpath fp = unsafePerformIO $ do
contents <- UTF8.toText <$> BS.readFile ("command" </> fp)
Pandoc _ blocks <- runIOorExplode (readMarkdown
def{ readerExtensions = pandocExtensions } contents)
- let codeblocks = map extractCode $ filter isCodeBlock $ blocks
+ let codeblocks = map extractCode $ filter isCodeBlock blocks
let cases = map (runCommandTest pandocpath) $ zip [1..] codeblocks
return $ testGroup fp cases
-
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 66dc2a6dd..b25a6fa4a 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -12,8 +12,10 @@ import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
header, linebreak, para, plain, rawBlock,
singleQuoted, space, str, strong, (<>))
import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
-import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc, pandocTypesVersion)
+import Text.Pandoc.Definition (Block (BlockQuote, Div, Para), Inline (Emph, Str),
+ Attr, Meta, Pandoc, pandocTypesVersion)
import Text.Pandoc.Lua (runLuaFilter, runPandocLua)
+import Text.Pandoc.Options (def)
import Text.Pandoc.Shared (pandocVersion)
import qualified Foreign.Lua as Lua
@@ -122,13 +124,44 @@ tests = map (localOption (QuickCheckTests 20))
Lua.getglobal "PANDOC_API_VERSION"
Lua.liftIO . assertEqual "pandoc-types version is wrong" versionNums
=<< Lua.peek Lua.stackTop
+
+ , testCase "Allow singleton inline in constructors" . runPandocLua' $ do
+ Lua.liftIO . assertEqual "Not the exptected Emph" (Emph [Str "test"])
+ =<< Lua.callFunc "pandoc.Emph" (Str "test")
+ Lua.liftIO . assertEqual "Unexpected element" (Para [Str "test"])
+ =<< Lua.callFunc "pandoc.Para" ("test" :: String)
+ Lua.liftIO . assertEqual "Unexptected element"
+ (BlockQuote [Para [Str "foo"]]) =<< (
+ do
+ Lua.getglobal' "pandoc.BlockQuote"
+ Lua.push (Para [Str "foo"])
+ _ <- Lua.call 1 1
+ Lua.peek Lua.stackTop
+ )
+
+ , testCase "Elements with Attr have `attr` accessor" . runPandocLua' $ do
+ Lua.push (Div ("hi", ["moin"], [])
+ [Para [Str "ignored"]])
+ Lua.getfield Lua.stackTop "attr"
+ Lua.liftIO . assertEqual "no accessor" (("hi", ["moin"], []) :: Attr)
+ =<< Lua.peek Lua.stackTop
+
+ , testCase "informative error messages" . runPandocLua' $ do
+ Lua.pushboolean True
+ err <- Lua.peekEither Lua.stackTop :: Lua.Lua (Either String Pandoc)
+ case err of
+ Left msg -> do
+ let expectedMsg = "Could not get Pandoc value: "
+ ++ "expected table but got boolean."
+ Lua.liftIO $ assertEqual "unexpected error message" expectedMsg msg
+ Right _ -> error "Getting a Pandoc element from a bool should fail."
]
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
assertFilterConversion msg filterPath docIn docExpected = do
docEither <- runIOorExplode $ do
setUserDataDir (Just "../data")
- runLuaFilter ("lua" </> filterPath) [] docIn
+ runLuaFilter def ("lua" </> filterPath) [] docIn
case docEither of
Left _ -> fail "lua filter failed"
Right docRes -> assertEqual msg docExpected docRes
diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs
index 3a21df738..3f60a523d 100644
--- a/test/Tests/Readers/Creole.hs
+++ b/test/Tests/Readers/Creole.hs
@@ -224,7 +224,7 @@ tests = [
<> " bar")
, "escaped auto link" =:
"foo ~http://foo.example.com/bar/baz.html bar"
- =?> para ("foo http://foo.example.com/bar/baz.html bar")
+ =?> para "foo http://foo.example.com/bar/baz.html bar"
, "wiki link simple" =:
"foo [[http://foo.example.com/foo.png]] bar"
=?> para ("foo "
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 68c2e3476..89a605bf7 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -5,6 +5,7 @@ import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
import qualified Data.Map as M
import qualified Data.Text as T
+import Data.Maybe
import System.IO.Unsafe
import Test.Tasty
import Test.Tasty.HUnit
@@ -46,7 +47,7 @@ compareOutput opts docxFile nativeFile = do
nf <- UTF8.toText <$> BS.readFile nativeFile
p <- runIOorExplode $ readDocx opts df
df' <- runIOorExplode $ readNative def nf
- return $ (noNorm p, noNorm df')
+ return (noNorm p, noNorm df')
testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO TestTree
testCompareWithOptsIO opts name docxFile nativeFile = do
@@ -87,11 +88,9 @@ compareMediaPathIO mediaPath mediaBag docxPath = do
Nothing -> error ("couldn't find " ++
mediaPath ++
" in media bag")
- docxBS = case docxMedia of
- Just bs -> bs
- Nothing -> error ("couldn't find " ++
- mediaPath ++
- " in media bag")
+ docxBS = fromMaybe (error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")) docxMedia
return $ mbBS == docxBS
compareMediaBagIO :: FilePath -> IO Bool
@@ -128,6 +127,10 @@ tests = [ testGroup "inlines"
"docx/links.docx"
"docx/links.native"
, testCompare
+ "hyperlinks in <w:instrText> tag"
+ "docx/instrText_hyperlink.docx"
+ "docx/instrText_hyperlink.native"
+ , testCompare
"inline image"
"docx/image.docx"
"docx/image_no_embed.native"
diff --git a/test/Tests/Readers/EPUB.hs b/test/Tests/Readers/EPUB.hs
index 201fd10a5..1337a9c11 100644
--- a/test/Tests/Readers/EPUB.hs
+++ b/test/Tests/Readers/EPUB.hs
@@ -17,7 +17,7 @@ getMediaBag fp = do
testMediaBag :: FilePath -> [(String, String, Int)] -> IO ()
testMediaBag fp bag = do
- actBag <- (mediaDirectory <$> getMediaBag fp)
+ actBag <- mediaDirectory <$> getMediaBag fp
assertBool (show "MediaBag did not match:\nExpected: "
++ show bag
++ "\nActual: "
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index e9ac64a96..36b08c3a2 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -27,15 +27,20 @@ infix 4 =:
spcSep :: [Inlines] -> Inlines
spcSep = mconcat . intersperse space
--- Tables and definition lists don't round-trip yet
+-- Tables don't round-trip yet
+-- Definition lists with multiple descriptions are supported by writer, but not reader yet
+
+singleDescription :: ([Inline], [[Block]]) -> ([Inline], [[Block]])
+singleDescription (a, x:_) = (a, [x])
+singleDescription x = x
makeRoundTrip :: Block -> Block
-makeRoundTrip (Table{}) = Para [Str "table was here"]
-makeRoundTrip (DefinitionList{}) = Para [Str "deflist was here"]
+makeRoundTrip Table{} = Para [Str "table was here"]
+makeRoundTrip (DefinitionList items) = DefinitionList $ map singleDescription items
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 code blocks and tables and compare third rewrite to the second.
+-- Currently we remove tables and compare third rewrite to the second.
-- First and second rewrites are not equal yet.
roundTrip :: Block -> Bool
roundTrip b = d'' == d'''
@@ -44,7 +49,7 @@ roundTrip b = d'' == d'''
d'' = rewrite d'
d''' = rewrite d''
rewrite = amuse . T.pack . (++ "\n") . T.unpack .
- (purely $ writeMuse def { writerExtensions = extensionsFromList [Ext_amuse]
+ purely (writeMuse def { writerExtensions = extensionsFromList [Ext_amuse]
, writerWrapText = WrapPreserve
})
@@ -114,8 +119,8 @@ tests =
, "Linebreak" =: "Line <br> break" =?> para ("Line" <> linebreak <> "break")
- , test emacsMuse "Non-breaking space"
- ("Foo~~bar" =?> para "Foo\160bar")
+ , "Non-breaking space" =: "Foo~~bar" =?> para "Foo\160bar"
+ , "Single ~" =: "Foo~bar" =?> para "Foo~bar"
, testGroup "Code markup"
[ "Code" =: "=foo(bar)=" =?> para (code "foo(bar)")
@@ -153,6 +158,9 @@ tests =
] =?>
para "foo =bar" <>
para "baz= foo"
+
+ , "Code at the beginning of paragraph but not first column" =:
+ " - =foo=" =?> bulletList [ para $ code "foo" ]
]
, "Code tag" =: "<code>foo(bar)</code>" =?> para (code "foo(bar)")
@@ -161,6 +169,8 @@ tests =
, "Verbatim inside code" =: "<code><verbatim>foo</verbatim></code>" =?> para (code "<verbatim>foo</verbatim>")
+ , "Verbatim tag after text" =: "Foo <verbatim>bar</verbatim>" =?> para "Foo bar"
+
, testGroup "Links"
[ "Link without description" =:
"[[https://amusewiki.org/]]" =?>
@@ -279,20 +289,12 @@ tests =
, " One two three"
, ""
, "</verse>"
- , "<verse>Foo bar</verse>"
- , "<verse>"
- , "Foo bar</verse>"
- , "<verse>"
- , " Foo</verse>"
] =?>
lineBlock [ ""
, text "Foo bar baz"
, text "\160\160One two three"
, ""
- ] <>
- lineBlock [ "Foo bar" ] <>
- lineBlock [ "Foo bar" ] <>
- lineBlock [ "\160\160\160Foo" ]
+ ]
, testGroup "Example"
[ "Braces on separate lines" =:
T.unlines [ "{{{"
@@ -356,6 +358,11 @@ tests =
, " </example>"
] =?>
bulletList [ codeBlock "foo" ]
+ , "Empty example inside list" =:
+ T.unlines [ " - <example>"
+ , " </example>"
+ ] =?>
+ bulletList [ codeBlock "" ]
, "Example inside list with empty lines" =:
T.unlines [ " - <example>"
, " foo"
@@ -537,12 +544,14 @@ tests =
, "[1] First footnote paragraph"
, ""
, " Second footnote paragraph"
+ , "with continuation"
+ , ""
, "Not a note"
, "[2] Second footnote"
] =?>
para (text "Multiparagraph" <>
note (para "First footnote paragraph" <>
- para "Second footnote paragraph") <>
+ para "Second footnote paragraph\nwith continuation") <>
text " footnotes" <>
note (para "Second footnote")) <>
para (text "Not a note")
@@ -713,8 +722,48 @@ tests =
, mempty
, para "Item3"
]
+ , "Bullet list with last item empty" =:
+ T.unlines
+ [ " -"
+ , ""
+ , "foo"
+ ] =?>
+ bulletList [ mempty ] <>
+ para "foo"
, testGroup "Nested lists"
- [ "Nested list" =:
+ [ "Nested bullet list" =:
+ T.unlines [ " - Item1"
+ , " - Item2"
+ , " - Item3"
+ , " - Item4"
+ , " - Item5"
+ , " - Item6"
+ ] =?>
+ bulletList [ para "Item1" <>
+ bulletList [ para "Item2" <>
+ bulletList [ para "Item3" ]
+ , para "Item4" <>
+ bulletList [ para "Item5" ]
+ ]
+ , para "Item6"
+ ]
+ , "Nested ordered list" =:
+ T.unlines [ " 1. Item1"
+ , " 1. Item2"
+ , " 1. Item3"
+ , " 2. Item4"
+ , " 1. Item5"
+ , " 2. Item6"
+ ] =?>
+ orderedListWith (1, Decimal, Period) [ para "Item1" <>
+ orderedListWith (1, Decimal, Period) [ para "Item2" <>
+ orderedListWith (1, Decimal, Period) [ para "Item3" ]
+ , para "Item4" <>
+ orderedListWith (1, Decimal, Period) [ para "Item5" ]
+ ]
+ , para "Item6"
+ ]
+ , "Mixed nested list" =:
T.unlines
[ " - Item1"
, " - Item2"
@@ -736,12 +785,6 @@ tests =
]
]
]
- , "Incorrectly indented Text::Amuse nested list" =:
- T.unlines
- [ " - First item"
- , " - Not nested item"
- ] =?>
- bulletList [ para "First item", para "Not nested item"]
, "Text::Amuse includes only one space in list marker" =:
T.unlines
[ " - First item"
@@ -886,6 +929,8 @@ tests =
definitionList [ ("foo", [ para "bar" ]) ]
, "Definition list term with emphasis" =: " *Foo* :: bar\n" =?>
definitionList [ (emph "Foo", [ para "bar" ]) ]
+ , "Definition list term with :: inside code" =: " foo <code> :: </code> :: bar <code> :: </code> baz\n" =?>
+ definitionList [ ("foo " <> code " :: ", [ para $ "bar " <> code " :: " <> " baz" ]) ]
, "Multi-line definition lists" =:
T.unlines
[ " First term :: Definition of first term"
@@ -920,16 +965,18 @@ tests =
definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."])
, ("Term2", [ para "This is a second definition"])
])
- -- Emacs Muse creates two separate lists when indentation of items is different.
- -- We follow Amusewiki and allow different indentation within one list.
- , "Changing indentation" =:
+ , "One-line nested definition list" =:
+ " Foo :: bar :: baz" =?>
+ definitionList [ ("Foo", [ definitionList [ ("bar", [ para "baz" ])]])]
+ , "Nested definition list" =:
T.unlines
- [ " First term :: Definition of first term"
- , "and its continuation."
- , " Second term :: Definition of second term."
- ] =?>
- definitionList [ ("First term", [ para "Definition of first term\nand its continuation." ])
- , ("Second term", [ para "Definition of second term." ])
+ [ " First :: Second :: Third"
+ , " Fourth :: Fifth :: Sixth"
+ , " Seventh :: Eighth"
+ ] =?>
+ definitionList [ ("First", [ definitionList [ ("Second", [ para "Third" ]),
+ ("Fourth", [ definitionList [ ("Fifth", [ para "Sixth"] ) ] ] ) ] ] )
+ , ("Seventh", [ para "Eighth" ])
]
, "Two blank lines separate definition lists" =:
T.unlines
diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs
index d895c86e2..e8ad88558 100644
--- a/test/Tests/Readers/Org/Block/Header.hs
+++ b/test/Tests/Readers/Org/Block/Header.hs
@@ -130,7 +130,7 @@ tests =
mconcat [ para "foo"
, headerWith ("thing-other-thing", [], [])
1
- ((strikeout "thing") <> " other thing")
+ (strikeout "thing" <> " other thing")
]
, "Comment Trees" =:
diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs
index 32bb13294..343682a80 100644
--- a/test/Tests/Readers/Org/Block/List.hs
+++ b/test/Tests/Readers/Org/Block/List.hs
@@ -75,16 +75,16 @@ tests =
]
, "Bullet List with Decreasing Indent" =:
- (" - Discovery\n\
- \ - Human After All\n") =?>
+ " - Discovery\n\
+ \ - Human After All\n" =?>
mconcat [ bulletList [ plain "Discovery" ]
, bulletList [ plain ("Human" <> space <> "After" <> space <> "All")]
]
, "Header follows Bullet List" =:
- (" - Discovery\n\
+ " - Discovery\n\
\ - Human After All\n\
- \* Homework") =?>
+ \* Homework" =?>
mconcat [ bulletList [ plain "Discovery"
, plain ("Human" <> space <> "After" <> space <> "All")
]
@@ -92,9 +92,9 @@ tests =
]
, "Bullet List Unindented with trailing Header" =:
- ("- Discovery\n\
+ "- Discovery\n\
\- Homework\n\
- \* NotValidListItem") =?>
+ \* NotValidListItem" =?>
mconcat [ bulletList [ plain "Discovery"
, plain "Homework"
]
@@ -166,14 +166,14 @@ tests =
, "Ordered List in Bullet List" =:
("- Emacs\n" <>
" 1. Org\n") =?>
- bulletList [ (plain "Emacs") <>
- (orderedList [ plain "Org"])
+ bulletList [ plain "Emacs" <>
+ orderedList [ plain "Org"]
]
, "Bullet List in Ordered List" =:
("1. GNU\n" <>
" - Freedom\n") =?>
- orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ]
+ orderedList [ plain "GNU" <> bulletList [ plain "Freedom" ] ]
, "Definition List" =:
T.unlines [ "- PLL :: phase-locked loop"
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index 862315ef3..7e2c0fb8d 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -107,8 +107,8 @@ tests =
] =?>
mconcat [ para "first block"
, orderedList
- [ (para "top-level section 1" <>
- orderedList [ para "subsection" ])
+ [ para "top-level section 1" <>
+ orderedList [ para "subsection" ]
, para "top-level section 2" ]
]
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index cb50ba630..da0d1db0b 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -36,7 +36,7 @@ tests =
, "Underline" =:
"_underline_" =?>
- para (underlineSpan $ "underline")
+ para (underlineSpan "underline")
, "Strikeout" =:
"+Kill Bill+" =?>
@@ -127,11 +127,12 @@ tests =
, "Markup should work properly after a blank line" =:
T.unlines ["foo", "", "/bar/"] =?>
- (para $ text "foo") <> (para $ emph $ text "bar")
+ para (text "foo") <>
+ para (emph $ text "bar")
, "Inline math must stay within three lines" =:
T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
- para ((math "a\nb\nc") <> softbreak <>
+ para (math "a\nb\nc" <> softbreak <>
"$d" <> softbreak <> "e" <> softbreak <>
"f" <> softbreak <> "g$")
@@ -139,7 +140,7 @@ tests =
"$a$ $b$! $c$?" =?>
para (spcSep [ math "a"
, "$b$!"
- , (math "c") <> "?"
+ , math "c" <> "?"
])
, "Markup may not span more than two lines" =:
@@ -166,12 +167,12 @@ tests =
para (mconcat $ intersperse softbreak
[ "a" <> subscript "(a(b)(c)d)"
, "e" <> superscript "(f(g)h)"
- , "i" <> (subscript "(jk)") <> "l)"
- , "m" <> (superscript "()") <> "n"
+ , "i" <> subscript "(jk)" <> "l)"
+ , "m" <> superscript "()" <> "n"
, "o" <> subscript "p{q{}r}"
, "s" <> superscript "t{u}v"
- , "w" <> (subscript "xy") <> "z}"
- , "1" <> (superscript "") <> "2"
+ , "w" <> subscript "xy" <> "z}"
+ , "1" <> superscript "" <> "2"
, "3" <> subscript "{}"
, "4" <> superscript ("(a(" <> strong "b(c" <> ")d))")
])
@@ -182,17 +183,17 @@ tests =
, testGroup "Images"
[ "Image" =:
"[[./sunset.jpg]]" =?>
- (para $ image "./sunset.jpg" "" "")
+ para (image "./sunset.jpg" "" "")
, "Image with explicit file: prefix" =:
"[[file:sunrise.jpg]]" =?>
- (para $ image "sunrise.jpg" "" "")
+ para (image "sunrise.jpg" "" "")
, "Multiple images within a paragraph" =:
T.unlines [ "[[file:sunrise.jpg]]"
, "[[file:sunset.jpg]]"
] =?>
- (para $ (image "sunrise.jpg" "" "")
+ para ((image "sunrise.jpg" "" "")
<> softbreak
<> (image "sunset.jpg" "" ""))
@@ -200,75 +201,75 @@ tests =
T.unlines [ "#+ATTR_HTML: :width 50%"
, "[[file:guinea-pig.gif]]"
] =?>
- (para $ imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
+ para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
]
, "Explicit link" =:
"[[http://zeitlens.com/][pseudo-random /nonsense/]]" =?>
- (para $ link "http://zeitlens.com/" ""
+ para (link "http://zeitlens.com/" ""
("pseudo-random" <> space <> emph "nonsense"))
, "Self-link" =:
"[[http://zeitlens.com/]]" =?>
- (para $ link "http://zeitlens.com/" "" "http://zeitlens.com/")
+ para (link "http://zeitlens.com/" "" "http://zeitlens.com/")
, "Absolute file link" =:
"[[/url][hi]]" =?>
- (para $ link "file:///url" "" "hi")
+ para (link "file:///url" "" "hi")
, "Link to file in parent directory" =:
"[[../file.txt][moin]]" =?>
- (para $ link "../file.txt" "" "moin")
+ para (link "../file.txt" "" "moin")
, "Empty link (for gitit interop)" =:
"[[][New Link]]" =?>
- (para $ link "" "" "New Link")
+ para (link "" "" "New Link")
, "Image link" =:
"[[sunset.png][file:dusk.svg]]" =?>
- (para $ link "sunset.png" "" (image "dusk.svg" "" ""))
+ para (link "sunset.png" "" (image "dusk.svg" "" ""))
, "Image link with non-image target" =:
"[[http://example.com][./logo.png]]" =?>
- (para $ link "http://example.com" "" (image "./logo.png" "" ""))
+ para (link "http://example.com" "" (image "./logo.png" "" ""))
, "Plain link" =:
"Posts on http://zeitlens.com/ can be funny at times." =?>
- (para $ spcSep [ "Posts", "on"
+ para (spcSep [ "Posts", "on"
, link "http://zeitlens.com/" "" "http://zeitlens.com/"
, "can", "be", "funny", "at", "times."
])
, "Angle link" =:
"Look at <http://moltkeplatz.de> for fnords." =?>
- (para $ spcSep [ "Look", "at"
+ para (spcSep [ "Look", "at"
, link "http://moltkeplatz.de" "" "http://moltkeplatz.de"
, "for", "fnords."
])
, "Absolute file link" =:
"[[file:///etc/passwd][passwd]]" =?>
- (para $ link "file:///etc/passwd" "" "passwd")
+ para (link "file:///etc/passwd" "" "passwd")
, "File link" =:
"[[file:target][title]]" =?>
- (para $ link "target" "" "title")
+ para (link "target" "" "title")
, "Anchor" =:
"<<anchor>> Link here later." =?>
- (para $ spanWith ("anchor", [], []) mempty <>
+ para (spanWith ("anchor", [], []) mempty <>
"Link" <> space <> "here" <> space <> "later.")
, "Inline code block" =:
"src_emacs-lisp{(message \"Hello\")}" =?>
- (para $ codeWith ( ""
+ para (codeWith ( ""
, [ "commonlisp" ]
, [ ("org-language", "emacs-lisp") ])
"(message \"Hello\")")
, "Inline code block with arguments" =:
"src_sh[:export both :results output]{echo 'Hello, World'}" =?>
- (para $ codeWith ( ""
+ para (codeWith ( ""
, [ "bash" ]
, [ ("org-language", "sh")
, ("export", "both")
@@ -279,7 +280,7 @@ tests =
, "Inline code block with toggle" =:
"src_sh[:toggle]{echo $HOME}" =?>
- (para $ codeWith ( ""
+ para (codeWith ( ""
, [ "bash" ]
, [ ("org-language", "sh")
, ("toggle", "yes")
@@ -415,7 +416,7 @@ tests =
in [
"Berkeley-style in-text citation" =:
"See @Dominik201408." =?>
- (para $ "See "
+ para ("See "
<> cite [dominikInText] "@Dominik201408"
<> ".")
@@ -468,7 +469,7 @@ tests =
, "MathML symbol in LaTeX-style" =:
"There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?>
- para ("There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ').")
+ para "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ')."
, "MathML symbol in LaTeX-style, including braces" =:
"\\Aacute{}stor" =?>
diff --git a/test/Tests/Readers/Org/Inline/Note.hs b/test/Tests/Readers/Org/Inline/Note.hs
index 46416d7d8..9eb1d02d6 100644
--- a/test/Tests/Readers/Org/Inline/Note.hs
+++ b/test/Tests/Readers/Org/Inline/Note.hs
@@ -84,4 +84,3 @@ tests =
, para "next"
]
]
-
diff --git a/test/Tests/Readers/Org/Inline/Smart.hs b/test/Tests/Readers/Org/Inline/Smart.hs
index 7a5e653cf..77f10699d 100644
--- a/test/Tests/Readers/Org/Inline/Smart.hs
+++ b/test/Tests/Readers/Org/Inline/Smart.hs
@@ -38,9 +38,9 @@ tests =
, test orgSmart "Single quotes can be followed by emphasized text"
("Singles on the '/meat market/'" =?>
- para ("Singles on the " <> (singleQuoted $ emph "meat market")))
+ para ("Singles on the " <> singleQuoted (emph "meat market")))
, test orgSmart "Double quotes can be followed by emphasized text"
("Double income, no kids: \"/DINK/\"" =?>
- para ("Double income, no kids: " <> (doubleQuoted $ emph "DINK")))
+ para ("Double income, no kids: " <> doubleQuoted (emph "DINK")))
]
diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs
index 3ad6f5d8b..409cd00ae 100644
--- a/test/Tests/Readers/Org/Meta.hs
+++ b/test/Tests/Readers/Org/Meta.hs
@@ -30,32 +30,32 @@ tests =
, "Title" =:
"#+TITLE: Hello, World" =?>
let titleInline = toList $ "Hello," <> space <> "World"
- meta = setMeta "title" (MetaInlines titleInline) $ nullMeta
+ meta = setMeta "title" (MetaInlines titleInline) nullMeta
in Pandoc meta mempty
, "Author" =:
"#+author: John /Emacs-Fanboy/ Doe" =?>
let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ]
- meta = setMeta "author" (MetaList [MetaInlines author]) $ nullMeta
+ meta = setMeta "author" (MetaList [MetaInlines author]) nullMeta
in Pandoc meta mempty
, "Multiple authors" =:
"#+author: James Dewey Watson, Francis Harry Compton Crick " =?>
let watson = MetaInlines $ toList "James Dewey Watson"
crick = MetaInlines $ toList "Francis Harry Compton Crick"
- meta = setMeta "author" (MetaList [watson, crick]) $ nullMeta
+ meta = setMeta "author" (MetaList [watson, crick]) nullMeta
in Pandoc meta mempty
, "Date" =:
"#+Date: Feb. *28*, 2014" =?>
- let date = toList . spcSep $ [ "Feb.", (strong "28") <> ",", "2014" ]
- meta = setMeta "date" (MetaInlines date) $ nullMeta
+ let date = toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ]
+ meta = setMeta "date" (MetaInlines date) nullMeta
in Pandoc meta mempty
, "Description" =:
"#+DESCRIPTION: Explanatory text" =?>
let description = "Explanatory text"
- meta = setMeta "description" (MetaString description) $ nullMeta
+ meta = setMeta "description" (MetaString description) nullMeta
in Pandoc meta mempty
, "Properties drawer" =:
@@ -94,7 +94,7 @@ tests =
, "#+author: Max"
] =?>
let author = MetaInlines [Str "Max"]
- meta = setMeta "author" (MetaList [author]) $ nullMeta
+ meta = setMeta "author" (MetaList [author]) nullMeta
in Pandoc meta mempty
, "Logbook drawer" =:
@@ -135,7 +135,7 @@ tests =
, "Search links are read as emph" =:
"[[Wally][Where's Wally?]]" =?>
- (para (emph $ "Where's" <> space <> "Wally?"))
+ para (emph $ "Where's" <> space <> "Wally?")
, "Link to nonexistent anchor" =:
T.unlines [ "<<link-here>> Target."
@@ -149,25 +149,25 @@ tests =
T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s"
, "[[wp:Org_mode][Wikipedia on Org-mode]]"
] =?>
- (para (link "https://en.wikipedia.org/wiki/Org_mode" ""
- ("Wikipedia" <> space <> "on" <> space <> "Org-mode")))
+ para (link "https://en.wikipedia.org/wiki/Org_mode" ""
+ ("Wikipedia" <> space <> "on" <> space <> "Org-mode"))
, "Link abbreviation, defined after first use" =:
T.unlines [ "[[zl:non-sense][Non-sense articles]]"
, "#+LINK: zl http://zeitlens.com/tags/%s.html"
] =?>
- (para (link "http://zeitlens.com/tags/non-sense.html" ""
- ("Non-sense" <> space <> "articles")))
+ para (link "http://zeitlens.com/tags/non-sense.html" ""
+ ("Non-sense" <> space <> "articles"))
, "Link abbreviation, URL encoded arguments" =:
T.unlines [ "#+link: expl http://example.com/%h/foo"
, "[[expl:Hello, World!][Moin!]]"
] =?>
- (para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!"))
+ para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!")
, "Link abbreviation, append arguments" =:
T.unlines [ "#+link: expl http://example.com/"
, "[[expl:foo][bar]]"
] =?>
- (para (link "http://example.com/foo" "" "bar"))
+ para (link "http://example.com/foo" "" "bar")
]
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index 928fc1a99..3753fbf12 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -36,8 +36,8 @@ tests = [ "line block with blank line" =:
, ":Parameter i: integer"
, ":Final: item"
, " on two lines" ]
- =?> ( doc
- $ para "para" <>
+ =?>
+ doc (para "para" <>
definitionList [ (str "Hostname", [para "media08"])
, (text "IP address", [para "10.0.0.19"])
, (str "Size", [para "3ru"])
@@ -56,10 +56,10 @@ tests = [ "line block with blank line" =:
, ""
, ":Version: 1"
]
- =?> ( setMeta "version" (para "1")
- $ setMeta "title" ("Title" :: Inlines)
+ =?>
+ setMeta "version" (para "1") (setMeta "title" ("Title" :: Inlines)
$ setMeta "subtitle" ("Subtitle" :: Inlines)
- $ doc mempty )
+ $ doc mempty)
, "with inline markup" =: T.unlines
[ ":*Date*: today"
, ""
@@ -73,8 +73,8 @@ tests = [ "line block with blank line" =:
, ".. _two: http://example.com"
, ".. _three: http://example.org"
]
- =?> ( setMeta "date" (str "today")
- $ doc
+ =?>
+ setMeta "date" (str "today") (doc
$ definitionList [ (emph "one", [para "emphasis"])
, (link "http://example.com" "" "two", [para "reference"])
, (link "http://example.org" "" "three", [para "another one"])
@@ -102,13 +102,12 @@ tests = [ "line block with blank line" =:
, " def func(x):"
, " return y"
] =?>
- ( doc $ codeBlockWith
+ doc (codeBlockWith
( ""
, ["sourceCode", "python", "numberLines", "class1", "class2", "class3"]
, [ ("startFrom", "34") ]
)
- "def func(x):\n return y"
- )
+ "def func(x):\n return y")
, "Code directive with number-lines, no line specified" =: T.unlines
[ ".. code::python"
, " :number-lines: "
@@ -116,13 +115,12 @@ tests = [ "line block with blank line" =:
, " def func(x):"
, " return y"
] =?>
- ( doc $ codeBlockWith
+ doc (codeBlockWith
( ""
, ["sourceCode", "python", "numberLines"]
, [ ("startFrom", "") ]
)
- "def func(x):\n return y"
- )
+ "def func(x):\n return y")
, testGroup "literal / line / code blocks"
[ "indented literal block" =: T.unlines
[ "::"
@@ -131,7 +129,8 @@ tests = [ "line block with blank line" =:
, ""
, " can go on for many lines"
, "but must stop here"]
- =?> (doc $
+ =?>
+ doc (
codeBlock "block quotes\n\ncan go on for many lines" <>
para "but must stop here")
, "line block with 3 lines" =: "| a\n| b\n| c"
@@ -185,6 +184,6 @@ tests = [ "line block with blank line" =:
, ".. [1]"
, " bar"
] =?>
- (para $ "foo" <> (note $ para "bar"))
+ para ("foo" <> (note $ para "bar"))
]
]
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
index 28f647de4..9c5053af7 100644
--- a/test/Tests/Readers/Txt2Tags.hs
+++ b/test/Tests/Readers/Txt2Tags.hs
@@ -30,11 +30,11 @@ simpleTable' :: Int
-> [Blocks]
-> [[Blocks]]
-> Blocks
-simpleTable' n = table "" (take n $ repeat (AlignCenter, 0.0))
+simpleTable' n = table "" (replicate n (AlignCenter, 0.0))
tests :: [TestTree]
tests =
- [ testGroup "Inlines" $
+ [ testGroup "Inlines"
[ "Plain String" =:
"Hello, World" =?>
para (spcSep [ "Hello,", "World" ])
@@ -114,7 +114,7 @@ tests =
]
- , testGroup "Basic Blocks" $
+ , testGroup "Basic Blocks"
["Paragraph, lines grouped together" =:
"A paragraph\n A blank line ends the \n current paragraph\n"
=?> para "A paragraph\n A blank line ends the\n current paragraph"
@@ -197,7 +197,7 @@ tests =
]
- , testGroup "Lists" $
+ , testGroup "Lists"
[ "Simple Bullet Lists" =:
("- Item1\n" <>
"- Item2\n") =?>
diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs
index 6fdbda3dd..cc448419c 100644
--- a/test/Tests/Shared.hs
+++ b/test/Tests/Shared.hs
@@ -19,21 +19,21 @@ tests = [ testGroup "compactifyDL"
testCollapse :: [TestTree]
testCollapse = map (testCase "collapse")
- [ (collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""]))
- , (collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"]))
- , (collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]]))
- , (collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"]))
- , (collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"]))
- , (collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"]))
- , (collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"]))
- , (collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""]))
- , (collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""]))
- , (collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."]))
- , (collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."]))
- , (collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."]))
- , (collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."]))
- , (collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"]))
- , (collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"]))
- , (collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"]))
- , (collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"]))
- , (collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"]))]
+ [ collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""])
+ , collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"])
+ , collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]])
+ , collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"])
+ , collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"])
+ , collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"])
+ , collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"])
+ , collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""])
+ , collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""])
+ , collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."])
+ , collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."])
+ , collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."])
+ , collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."])
+ , collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"])
+ , collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"])
+ , collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"])
+ , collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"])
+ , collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"])]
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index 783b601a9..5ce629674 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -15,6 +15,9 @@ context = unpack . purely (writeConTeXt def) . toPandoc
context' :: (ToPandoc a) => a -> String
context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc
+contextNtb :: (ToPandoc a) => a -> String
+contextNtb = unpack . purely (writeConTeXt def{ writerExtensions = enableExtension Ext_ntb pandocExtensions }) . toPandoc
+
{-
"my test" =: X =?> Y
@@ -38,9 +41,9 @@ tests = [ testGroup "inline code"
, "without '}'" =: code "]" =?> "\\type{]}"
, testProperty "code property" $ \s -> null s ||
if '{' `elem` s || '}' `elem` s
- then (context' $ code s) == "\\mono{" ++
- (context' $ str s) ++ "}"
- else (context' $ code s) == "\\type{" ++ s ++ "}"
+ then context' (code s) == "\\mono{" ++
+ context' (str s) ++ "}"
+ else context' (code s) == "\\type{" ++ s ++ "}"
]
, testGroup "headers"
[ "level 1" =:
@@ -68,5 +71,56 @@ tests = [ testGroup "inline code"
, " \\stopitemize"
, "\\stopitemize" ]
]
+ , testGroup "natural tables"
+ [ test contextNtb "table with header and caption" $
+ let caption = text "Table 1"
+ aligns = [(AlignRight, 0.0), (AlignLeft, 0.0), (AlignCenter, 0.0), (AlignDefault, 0.0)]
+ headers = [plain $ text "Right",
+ plain $ text "Left",
+ plain $ text "Center",
+ plain $ text "Default"]
+ rows = [[plain $ text "1.1",
+ plain $ text "1.2",
+ plain $ text "1.3",
+ plain $ text "1.4"]
+ ,[plain $ text "2.1",
+ plain $ text "2.2",
+ plain $ text "2.3",
+ plain $ text "2.4"]
+ ,[plain $ text "3.1",
+ plain $ text "3.2",
+ plain $ text "3.3",
+ plain $ text "3.4"]]
+ in table caption aligns headers rows
+ =?> unlines [ "\\startplacetable[caption={Table 1}]"
+ , "\\startTABLE"
+ , "\\startTABLEhead"
+ , "\\NC[align=left] Right"
+ , "\\NC[align=right] Left"
+ , "\\NC[align=middle] Center"
+ , "\\NC Default"
+ , "\\NC\\NR"
+ , "\\stopTABLEhead"
+ , "\\startTABLEbody"
+ , "\\NC[align=left] 1.1"
+ , "\\NC[align=right] 1.2"
+ , "\\NC[align=middle] 1.3"
+ , "\\NC 1.4"
+ , "\\NC\\NR"
+ , "\\NC[align=left] 2.1"
+ , "\\NC[align=right] 2.2"
+ , "\\NC[align=middle] 2.3"
+ , "\\NC 2.4"
+ , "\\NC\\NR"
+ , "\\stopTABLEbody"
+ , "\\startTABLEfoot"
+ , "\\NC[align=left] 3.1"
+ , "\\NC[align=right] 3.2"
+ , "\\NC[align=middle] 3.3"
+ , "\\NC 3.4"
+ , "\\NC\\NR"
+ , "\\stopTABLEfoot"
+ , "\\stopTABLE"
+ , "\\stopplacetable" ]
+ ]
]
-
diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs
index 90ae073fa..89ea76586 100644
--- a/test/Tests/Writers/Docbook.hs
+++ b/test/Tests/Writers/Docbook.hs
@@ -230,7 +230,7 @@ tests = [ testGroup "line blocks"
]
]
]
- , testGroup "writer options" $
+ , testGroup "writer options"
[ testGroup "top-level division" $
let
headers = header 1 (text "header1")
diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs
index b4d11abf4..6663c42f8 100644
--- a/test/Tests/Writers/FB2.hs
+++ b/test/Tests/Writers/FB2.hs
@@ -23,7 +23,7 @@ tests = [ testGroup "block elements"
]
, testGroup "inlines"
[
- "Emphasis" =: emph ("emphasized")
+ "Emphasis" =: emph "emphasized"
=?> fb2 "<emphasis>emphasized</emphasis>"
]
, "bullet list" =: bulletList [ plain $ text "first"
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
index f14f1c229..572b16451 100644
--- a/test/Tests/Writers/JATS.hs
+++ b/test/Tests/Writers/JATS.hs
@@ -120,5 +120,3 @@ tests = [ testGroup "inline code"
\</sec>"
]
]
-
-
diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs
index 012e0888c..7f9ac3627 100644
--- a/test/Tests/Writers/Markdown.hs
+++ b/test/Tests/Writers/Markdown.hs
@@ -80,7 +80,7 @@ noteTestDoc =
".") <>
blockQuote (para ("A note inside a block quote." <>
note (para "The second note.")) <>
- para ("A second paragraph.")) <>
+ para "A second paragraph.") <>
header 1 "Second Header" <>
para "Some more text."
@@ -91,7 +91,7 @@ noteTests = testGroup "note and reference location"
[ test (markdownWithOpts defopts)
"footnotes at the end of a document" $
noteTestDoc =?>
- (unlines $ [ "First Header"
+ (unlines [ "First Header"
, "============"
, ""
, "This is a footnote.[^1] And this is a [link](https://www.google.com)."
@@ -112,7 +112,7 @@ noteTests = testGroup "note and reference location"
, test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock})
"footnotes at the end of blocks" $
noteTestDoc =?>
- (unlines $ [ "First Header"
+ (unlines [ "First Header"
, "============"
, ""
, "This is a footnote.[^1] And this is a [link](https://www.google.com)."
@@ -133,7 +133,7 @@ noteTests = testGroup "note and reference location"
, test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True})
"footnotes and reference links at the end of blocks" $
noteTestDoc =?>
- (unlines $ [ "First Header"
+ (unlines [ "First Header"
, "============"
, ""
, "This is a footnote.[^1] And this is a [link]."
@@ -156,7 +156,7 @@ noteTests = testGroup "note and reference location"
, test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection})
"footnotes at the end of section" $
noteTestDoc =?>
- (unlines $ [ "First Header"
+ (unlines [ "First Header"
, "============"
, ""
, "This is a footnote.[^1] And this is a [link](https://www.google.com)."
@@ -186,27 +186,27 @@ shortcutLinkRefsTests =
(=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc)
in testGroup "Shortcut reference links"
[ "Simple link (shortcutable)"
- =: (para (link "/url" "title" "foo"))
+ =: para (link "/url" "title" "foo")
=?> "[foo]\n\n [foo]: /url \"title\""
, "Followed by another link (unshortcutable)"
- =: (para ((link "/url1" "title1" "first")
- <> (link "/url2" "title2" "second")))
+ =: para ((link "/url1" "title1" "first")
+ <> (link "/url2" "title2" "second"))
=?> unlines [ "[first][][second]"
, ""
, " [first]: /url1 \"title1\""
, " [second]: /url2 \"title2\""
]
, "Followed by space and another link (unshortcutable)"
- =: (para ((link "/url1" "title1" "first") <> " "
- <> (link "/url2" "title2" "second")))
+ =: para ((link "/url1" "title1" "first") <> " "
+ <> (link "/url2" "title2" "second"))
=?> unlines [ "[first][] [second]"
, ""
, " [first]: /url1 \"title1\""
, " [second]: /url2 \"title2\""
]
, "Reference link is used multiple times (unshortcutable)"
- =: (para ((link "/url1" "" "foo") <> (link "/url2" "" "foo")
- <> (link "/url3" "" "foo")))
+ =: para ((link "/url1" "" "foo") <> (link "/url2" "" "foo")
+ <> (link "/url3" "" "foo"))
=?> unlines [ "[foo][][foo][1][foo][2]"
, ""
, " [foo]: /url1"
@@ -214,8 +214,8 @@ shortcutLinkRefsTests =
, " [2]: /url3"
]
, "Reference link is used multiple times (unshortcutable)"
- =: (para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo")
- <> " " <> (link "/url3" "" "foo")))
+ =: para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo")
+ <> " " <> (link "/url3" "" "foo"))
=?> unlines [ "[foo][] [foo][1] [foo][2]"
, ""
, " [foo]: /url1"
@@ -223,43 +223,43 @@ shortcutLinkRefsTests =
, " [2]: /url3"
]
, "Reference link is followed by text in brackets"
- =: (para ((link "/url" "" "link") <> "[text in brackets]"))
+ =: para ((link "/url" "" "link") <> "[text in brackets]")
=?> unlines [ "[link][]\\[text in brackets\\]"
, ""
, " [link]: /url"
]
, "Reference link is followed by space and text in brackets"
- =: (para ((link "/url" "" "link") <> " [text in brackets]"))
+ =: para ((link "/url" "" "link") <> " [text in brackets]")
=?> unlines [ "[link][] \\[text in brackets\\]"
, ""
, " [link]: /url"
]
, "Reference link is followed by RawInline"
- =: (para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]"))
+ =: para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]")
=?> unlines [ "[link][][rawText]"
, ""
, " [link]: /url"
]
, "Reference link is followed by space and RawInline"
- =: (para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]"))
+ =: para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]")
=?> unlines [ "[link][] [rawText]"
, ""
, " [link]: /url"
]
, "Reference link is followed by RawInline with space"
- =: (para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]"))
+ =: para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]")
=?> unlines [ "[link][] [rawText]"
, ""
, " [link]: /url"
]
, "Reference link is followed by citation"
- =: (para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]")))
+ =: para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))
=?> unlines [ "[link][][@author]"
, ""
, " [link]: /url"
]
, "Reference link is followed by space and citation"
- =: (para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]")))
+ =: para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))
=?> unlines [ "[link][] [@author]"
, ""
, " [link]: /url"
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index e2e6ba06c..158f80f67 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -94,6 +94,15 @@ tests = [ testGroup "block elements"
, " second definition :: second description"
, " third definition :: third description"
]
+ , "definition list with multiple descriptions" =:
+ definitionList [ (text "first definition", [plain $ text "first description"
+ ,plain $ text "second description"])
+ , (text "second definition", [plain $ text "third description"])
+ ]
+ =?> unlines [ " first definition :: first description"
+ , " :: second description"
+ , " second definition :: third description"
+ ]
]
-- Test that lists of the same type and style are separated with two blanklines
, testGroup "sequential lists"
@@ -197,8 +206,8 @@ tests = [ testGroup "block elements"
]
, "nested definition lists" =: definitionList [ (text "first definition", [plain $ text "first description"])
, (text "second definition",
- [ plain (text "second description")
- , definitionList [ ( text "first inner definition"
+ [ plain (text "second description") <>
+ definitionList [ ( text "first inner definition"
, [plain $ text "first inner description"])
, ( text "second inner definition"
, [plain $ text "second inner description"])
diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs
index c22185968..0c4bf7623 100644
--- a/test/Tests/Writers/Native.hs
+++ b/test/Tests/Writers/Native.hs
@@ -18,5 +18,5 @@ p_write_blocks_rt bs =
tests :: [TestTree]
tests = [ testProperty "p_write_rt" p_write_rt
, testProperty "p_write_blocks_rt" $ mapSize
- (\x -> if x > 3 then 3 else x) $ p_write_blocks_rt
+ (\x -> if x > 3 then 3 else x) p_write_blocks_rt
]
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index cc94f822d..139081013 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -1,169 +1,196 @@
+{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE MultiWayIf #-}
module Tests.Writers.Powerpoint (tests) where
-import Control.Exception (throwIO)
+-- import Control.Exception (throwIO)
import Text.Pandoc
-import Text.Pandoc.Builder
-import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Walk
import Test.Tasty
import Test.Tasty.HUnit
-import Test.Tasty.QuickCheck
import Codec.Archive.Zip
import Text.XML.Light
-import Data.List (isPrefixOf, isSuffixOf, sort)
-import Data.Maybe (mapMaybe)
-
-getPptxArchive :: WriterOptions -> Pandoc -> IO Archive
-getPptxArchive opts pd = do
- mbs <- runIO $
- do setUserDataDir $ Just "../data"
- writePowerpoint opts pd
- case mbs of
- Left e -> throwIO e
- Right bs -> return $ toArchive bs
-
------ Number of Slides -----------
-
-numberOfSlides :: WriterOptions -> Pandoc -> IO Int
-numberOfSlides opts pd = do
- archive <- getPptxArchive opts pd
- return $
- length $
- filter (isSuffixOf ".xml") $
- filter (isPrefixOf "ppt/slides/slide") $
- filesInArchive archive
-
-testNumberOfSlides :: TestName -> Int -> WriterOptions -> Pandoc -> TestTree
-testNumberOfSlides name n opts pd =
- testCase name $ do
- n' <- numberOfSlides opts pd
- n' @=? n
-
-numSlideTests :: TestTree
-numSlideTests = testGroup "Number of slides in output"
- [ testNumberOfSlides
- "simple one-slide deck" 1
- def
- (doc $ para "foo")
- , testNumberOfSlides
- "with metadata (header slide)" 2
- def
- (setTitle "My Title" $ doc $ para "foo")
- , testNumberOfSlides
- "With h1 slide (using default slide-level)" 1
- def
- (doc $ header 1 "Header" <> para "foo")
- , testNumberOfSlides
- "With h2 slide (using default slide-level)" 2
- def
- (doc $ header 1 "Header" <> header 2 "subeader" <> para "foo")
- , testNumberOfSlides
- "With h1 slide (using slide-level 3)" 2
- def {writerSlideLevel= Just 3}
- (doc $ header 1 "Header" <> para "foo")
- , testNumberOfSlides
- "With h2 slide (using slide-level 3)" 3
- def {writerSlideLevel= Just 3}
- (doc $ header 1 "Header" <> header 2 "subeader" <> para "foo")
- , testNumberOfSlides
- "With image slide, no header" 3
- def
- (doc $
- para "first slide" <>
- (para $ image "lalune.jpg" "" "") <>
- para "foo")
- , testNumberOfSlides
- "With image slide, header" 3
- def
- (doc $
- para "first slide" <>
- header 2 "image header" <>
- (para $ image "lalune.jpg" "" "") <>
- para "foo")
- , testNumberOfSlides
- "With table, no header" 3
- def
- (doc $
- para "first slide" <>
- (simpleTable [para "foo" <> para "bar"] [[para "this" <> para "that"]]) <>
- para "foo")
- , testNumberOfSlides
- "With table, header" 3
- def
- (doc $
- para "first slide" <>
- header 2 "table header" <>
- (simpleTable [para "foo" <> para "bar"] [[para "this" <> para "that"]]) <>
- para "foo")
- , testNumberOfSlides
- "hrule" 2
- def
- (doc $
- para "first slide" <> horizontalRule <> para "last slide")
- , testNumberOfSlides
- "with notes slide" 2
- def
- (doc $
- para $ text "Foo" <> note (para "note text"))
- ]
-
------ Content Types -----------
-
-
-contentTypesFileExists :: WriterOptions -> Pandoc -> TestTree
-contentTypesFileExists opts pd =
- testCase "Existence of [Content_Types].xml file" $
- do archive <- getPptxArchive opts pd
- assertBool "Missing [Content_Types].xml file" $
- "[Content_Types].xml" `elem` (filesInArchive archive)
-
-
-
--- We want an "Override" entry for each xml file under ppt/.
-prop_ContentOverrides :: Pandoc -> IO Bool
-prop_ContentOverrides pd = do
- -- remove Math to avoid warnings
- let go :: Inline -> Inline
- go (Math _ _) = Str "Math"
- go i = i
- pd' = walk go pd
- archive <- getPptxArchive def pd'
- let xmlFiles = filter ("[Content_Types].xml" /=) $
- filter (isSuffixOf ".xml") $
- filesInArchive archive
- contentTypes <- case findEntryByPath "[Content_Types].xml" archive of
- Just ent -> return $ fromEntry ent
- Nothing -> throwIO $
- PandocSomeError "Missing [Content_Types].xml file"
- typesElem <- case parseXMLDoc contentTypes of
- Just element -> return $ element
- Nothing -> throwIO $
- PandocSomeError "[Content_Types].xml cannot be parsed"
- let ns = findAttr (QName "xmlns" Nothing Nothing) typesElem
- overrides = findChildren (QName "Override" ns Nothing) typesElem
- partNames = mapMaybe (findAttr (QName "PartName" Nothing Nothing)) overrides
- -- files in content_types are absolute
- absXmlFiles = map (\fp -> case fp of
- ('/':_) -> fp
- _ -> '/': fp
- )
- xmlFiles
- return $ sort absXmlFiles == sort partNames
-
-contentOverridesTests :: TestTree
-contentOverridesTests = localOption (QuickCheckTests 20) $
- testProperty "Content Overrides for each XML file" $
- \x -> ioProperty $ prop_ContentOverrides (x :: Pandoc)
-
-contentTypeTests :: TestTree
-contentTypeTests = testGroup "[Content_Types].xml file"
- [ contentTypesFileExists def (doc $ para "foo")
- , contentOverridesTests
- ]
+import qualified Data.ByteString.Lazy as BL
+import qualified Data.Text.IO as T
+import Data.List (isPrefixOf, isSuffixOf, sort, (\\), intercalate)
+import Data.Maybe (fromJust, isNothing)
+import Tests.Helpers
+import Data.Algorithm.Diff
+import Control.Monad (when)
+
+
+getPptxBytes :: WriterOptions
+ -> FilePath
+ -> FilePath
+ -> IO (BL.ByteString, BL.ByteString)
+getPptxBytes opts nativeFp pptxFp = do
+ ntvTxt <- T.readFile nativeFp
+ ntv <- runIOorExplode $ readNative def ntvTxt
+ myPptxBs <- runIOorExplode $ writePowerpoint opts ntv
+ goodPptxBs <- BL.readFile pptxFp
+ return (myPptxBs, goodPptxBs)
+
+
+assertSameFileList :: Archive -> Archive -> FilePath -> Assertion
+assertSameFileList myArch goodArch pptxFp = do
+ let filesMy = filesInArchive myArch
+ filesGood = filesInArchive goodArch
+ diffMyGood = filesMy \\ filesGood
+ diffGoodMy = filesGood \\ filesMy
+ if | null diffMyGood && null diffGoodMy -> return ()
+ | null diffMyGood ->
+ assertFailure $
+ "Files in " ++ pptxFp ++ " but not in generated archive:\n" ++
+ intercalate ", " diffGoodMy
+ | null diffGoodMy ->
+ assertFailure $
+ "Files in generated archive but not in " ++ pptxFp ++ ":\n" ++
+ intercalate ", " diffMyGood
+ | otherwise ->
+ assertFailure $
+ "Files in " ++ pptxFp ++ " but not in generated archive:\n" ++
+ intercalate ", " diffGoodMy ++
+ "\n" ++
+ "Files in generated archive but not in " ++ pptxFp ++ ":\n" ++
+ intercalate ", " diffMyGood
+
+compareXMLBool :: Content -> Content -> Bool
+-- We make a special exception for times at the moment, and just pass
+-- them because we can't control the utctime when running IO. Besides,
+-- so long as we have two times, we're okay.
+compareXMLBool (Elem myElem) (Elem goodElem)
+ | (QName "created" _ (Just "dcterms")) <- elName myElem
+ , (QName "created" _ (Just "dcterms")) <- elName goodElem =
+ True
+compareXMLBool (Elem myElem) (Elem goodElem)
+ | (QName "modified" _ (Just "dcterms")) <- elName myElem
+ , (QName "modified" _ (Just "dcterms")) <- elName goodElem =
+ True
+compareXMLBool (Elem myElem) (Elem goodElem) =
+ and [ elName myElem == elName goodElem
+ , elAttribs myElem == elAttribs goodElem
+ , and $
+ map (uncurry compareXMLBool) $
+ zip (elContent myElem) (elContent goodElem)
+ ]
+compareXMLBool (Text myCData) (Text goodCData) =
+ and [ cdVerbatim myCData == cdVerbatim goodCData
+ , cdData myCData == cdData goodCData
+ , cdLine myCData == cdLine goodCData
+ ]
+compareXMLBool (CRef myStr) (CRef goodStr) =
+ myStr == goodStr
+compareXMLBool _ _ = False
+
+displayDiff :: Content -> Content -> String
+displayDiff elemA elemB =
+ showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB)
+
+compareXMLFile :: FilePath -> Archive -> Archive -> Assertion
+compareXMLFile fp myArch goodArch = do
+ let mbMyEntry = findEntryByPath fp myArch
+ when (isNothing mbMyEntry)
+ (assertFailure $
+ "Can't extract " ++ fp ++ " from generated archive")
+ let mbMyXMLDoc = parseXMLDoc $ fromEntry $ fromJust mbMyEntry
+ when (isNothing mbMyXMLDoc)
+ (assertFailure $
+ "Can't parse xml in " ++ fp ++ " from generated archive")
+ let myContent = Elem $ fromJust mbMyXMLDoc
+
+ let mbGoodEntry = findEntryByPath fp goodArch
+ when (isNothing mbGoodEntry)
+ (assertFailure $
+ "Can't extract " ++ fp ++ " from archive in stored pptx file")
+ let mbGoodXMLDoc = parseXMLDoc $ fromEntry $ fromJust mbGoodEntry
+ when (isNothing mbGoodXMLDoc)
+ (assertFailure $
+ "Can't parse xml in " ++ fp ++ " from archive in stored pptx file")
+ let goodContent = Elem $ fromJust mbGoodXMLDoc
+
+ assertBool
+ ("Non-matching xml in " ++ fp ++ ":\n" ++ displayDiff myContent goodContent)
+ (compareXMLBool myContent goodContent)
+
+compareBinaryFile :: FilePath -> Archive -> Archive -> Assertion
+compareBinaryFile fp myArch goodArch = do
+ let mbMyEntry = findEntryByPath fp myArch
+ when (isNothing mbMyEntry)
+ (assertFailure $
+ "Can't extract " ++ fp ++ " from generated archive")
+ let myBytes = fromEntry $ fromJust mbMyEntry
+
+ let mbGoodEntry = findEntryByPath fp goodArch
+ when (isNothing mbGoodEntry)
+ (assertFailure $
+ "Can't extract " ++ fp ++ " from archive in stored pptx file")
+ let goodBytes = fromEntry $ fromJust mbGoodEntry
+
+ assertBool (fp ++ " doesn't match") (myBytes == goodBytes)
+
+testSameFileList :: WriterOptions -> FilePath -> FilePath -> TestTree
+testSameFileList opts myFp goodFp =
+ testCase ("Identical file list in archives") $ do
+ (myBS, goodBS) <- getPptxBytes opts myFp goodFp
+ let myArch = toArchive myBS
+ goodArch = toArchive goodBS
+ (assertSameFileList myArch goodArch goodFp)
+
+testSameXML :: WriterOptions -> FilePath -> FilePath -> TestTree
+testSameXML opts myFp goodFp = testCaseSteps "Comparing extracted xml files" $
+ \step -> do
+ (myBS, goodBS) <- getPptxBytes opts myFp goodFp
+ let myArch = toArchive myBS
+ goodArch = toArchive goodBS
+
+ let xmlFileList = sort $
+ filter (\fp -> ".xml" `isSuffixOf` fp || ".rels" `isSuffixOf` fp)
+ (filesInArchive myArch)
+ mapM_
+ (\fp -> step ("- " ++ fp) >> compareXMLFile fp myArch goodArch)
+ xmlFileList
+
+testSameMedia :: WriterOptions -> FilePath -> FilePath -> TestTree
+testSameMedia opts myFp goodFp = testCaseSteps "Comparing media files" $
+ \step -> do
+ (myBS, goodBS) <- getPptxBytes opts myFp goodFp
+ let myArch = toArchive myBS
+ goodArch = toArchive goodBS
+
+ let mediaFileList = sort $
+ filter (\fp -> "ppt/media/" `isPrefixOf` fp)
+ (filesInArchive myArch)
+
+ mapM_
+ (\fp -> step ("- " ++ fp) >> compareBinaryFile fp myArch goodArch)
+ mediaFileList
+
+testCompareWithOpts :: String -> WriterOptions ->FilePath -> FilePath -> TestTree
+testCompareWithOpts testName opts nativeFp pptxFp =
+ testGroup testName [ testSameFileList opts nativeFp pptxFp
+ , testSameXML opts nativeFp pptxFp
+ , testSameMedia opts nativeFp pptxFp
+ ]
+
+
+testCompare :: String -> FilePath -> FilePath -> TestTree
+testCompare testName nativeFp pptxFp =
+ testCompareWithOpts testName def nativeFp pptxFp
+
+--------------------------------------------------------------
tests :: [TestTree]
-tests = [ numSlideTests
- , contentTypeTests
+tests = [ testCompare
+ "Inline formatting"
+ "pptx/inline_formatting.native"
+ "pptx/inline_formatting.pptx"
+ , testCompare
+ "slide breaks (default slide-level)"
+ "pptx/slide_breaks.native"
+ "pptx/slide_breaks.pptx"
+ , testCompareWithOpts
+ "slide breaks (slide-level set to 1)"
+ def{writerSlideLevel=Just 1}
+ "pptx/slide_breaks.native"
+ "pptx/slide_breaks_slide_level_1.pptx"
]
diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs
index 13944ed34..4c0a926bb 100644
--- a/test/Tests/Writers/RST.hs
+++ b/test/Tests/Writers/RST.hs
@@ -40,6 +40,16 @@ tests = [ testGroup "rubrics"
, " :name: foo"
, " :class: baz"]
]
+ , testGroup "ligatures" -- handling specific sequences of blocks
+ [ "a list is closed by a comment before a quote" =: -- issue 4248
+ bulletList [plain "bulleted"] <> blockQuote (plain "quoted") =?>
+ unlines
+ [ "- bulleted"
+ , ""
+ , ".."
+ , ""
+ , " quoted"]
+ ]
, testGroup "headings"
[ "normal heading" =:
header 1 (text "foo") =?>
diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs
index f0a034bbd..fa372909f 100644
--- a/test/Tests/Writers/TEI.hs
+++ b/test/Tests/Writers/TEI.hs
@@ -31,7 +31,7 @@ tests = [ testGroup "block elements"
]
, testGroup "inlines"
[
- "Emphasis" =: emph ("emphasized")
+ "Emphasis" =: emph "emphasized"
=?> "<p><hi rendition=\"simple:italic\">emphasized</hi></p>"
,"SingleQuoted" =: singleQuoted (text "quoted material")
=?> "<p><quote>quoted material</quote></p>"
diff --git a/test/command/4159.md b/test/command/4159.md
index 81deba53a..4881edcc5 100644
--- a/test/command/4159.md
+++ b/test/command/4159.md
@@ -3,5 +3,6 @@
\newcommand{\gen}{a\ Gen\ b}
abc
^D
-[Para [Str "abc"]]
+[RawBlock (Format "latex") "\\newcommand{\\gen}{a\\ Gen\\ b}"
+,Para [Str "abc"]]
```
diff --git a/test/command/4240.md b/test/command/4240.md
new file mode 100644
index 000000000..39a7d2adf
--- /dev/null
+++ b/test/command/4240.md
@@ -0,0 +1,33 @@
+```
+% pandoc -f rst -s -t native
+=====
+Title
+=====
+
+--------
+Subtitle
+--------
+
+header1
+=======
+
+header2
+-------
+
+.. _id:
+
+header3
+~~~~~~~
+
+.. _id2:
+.. _id3:
+
+header4
+~~~~~~~
+^D
+Pandoc (Meta {unMeta = fromList [("subtitle",MetaInlines [Str "Subtitle"]),("title",MetaInlines [Str "Title"])]})
+[Header 1 ("header1",[],[]) [Str "header1"]
+,Header 2 ("header2",[],[]) [Str "header2"]
+,Header 3 ("id",[],[]) [Str "header3"]
+,Header 3 ("id3",[],[]) [Str "header4",Span ("id2",[],[]) []]]
+```
diff --git a/test/command/4253.md b/test/command/4253.md
new file mode 100644
index 000000000..01f5eea86
--- /dev/null
+++ b/test/command/4253.md
@@ -0,0 +1,8 @@
+```
+% pandoc -f latex -t native
+\newcommand{\noop}[1]{#1}
+\noop{\newcommand{\foo}[1]{#1}}
+\foo{hi}
+^D
+[Para [Str "hi"]]
+```
diff --git a/test/command/4254.md b/test/command/4254.md
new file mode 100644
index 000000000..e4cc5c6b0
--- /dev/null
+++ b/test/command/4254.md
@@ -0,0 +1,12 @@
+```
+% pandoc -f rst -t latex
+.. math::
+
+ x &= y\\
+ y &= z
+^D
+\[\begin{aligned}
+x &= y\\
+y &= z
+\end{aligned}\]
+```
diff --git a/test/command/4280.md b/test/command/4280.md
new file mode 100644
index 000000000..6a89b5e63
--- /dev/null
+++ b/test/command/4280.md
@@ -0,0 +1,7 @@
+```
+% pandoc -f rst -t native
+Driver
+------
+^D
+[Header 1 ("driver",[],[]) [Str "Driver"]]
+```
diff --git a/test/command/4281.md b/test/command/4281.md
new file mode 100644
index 000000000..9806e8178
--- /dev/null
+++ b/test/command/4281.md
@@ -0,0 +1,18 @@
+```
+% pandoc -t native
+:::: {.a}
+- ::: {.b}
+ text
+ :::
+ ::: {.c}
+ text
+ :::
+::::
+^D
+[Div ("",["a"],[])
+ [BulletList
+ [[Div ("",["b"],[])
+ [Para [Str "text"]]
+ ,Div ("",["c"],[])
+ [Para [Str "text"]]]]]]
+```
diff --git a/test/command/adjacent_latex_blocks.md b/test/command/adjacent_latex_blocks.md
new file mode 100644
index 000000000..3e72f1d4f
--- /dev/null
+++ b/test/command/adjacent_latex_blocks.md
@@ -0,0 +1,9 @@
+```
+% pandoc -f markdown -t native
+\listoffigures
+
+\listoftables
+^D
+[RawBlock (Format "latex") "\\listoffigures"
+,RawBlock (Format "latex") "\\listoftables"]
+```
diff --git a/test/command/cite-in-inline-note.md b/test/command/cite-in-inline-note.md
new file mode 100644
index 000000000..069484eed
--- /dev/null
+++ b/test/command/cite-in-inline-note.md
@@ -0,0 +1,6 @@
+```
+% pandoc -t native
+foo^[bar [@doe]]
+^D
+[Para [Str "foo",Note [Para [Str "bar",Space,Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@doe]"]]]]]
+```
diff --git a/test/command/macros.md b/test/command/macros.md
index 4bd2eb00a..9de87e7a0 100644
--- a/test/command/macros.md
+++ b/test/command/macros.md
@@ -3,6 +3,7 @@
\newcommand{\my}{\phi}
$\my+\my$
^D
+\newcommand{\my}{\phi}
$\phi+\phi$
```
@@ -73,6 +74,7 @@ x &= y\\\end{aligned}\]
\my+\my
\end{equation}
^D
+\newcommand{\my}{\phi}
\begin{equation}
\phi+\phi
\end{equation}
@@ -96,5 +98,6 @@ x &= y\\\end{aligned}\]
\newcommand{\my}{\emph{a}}
\my
^D
+\newcommand{\my}{\emph{a}}
\emph{a}
```
diff --git a/test/docx/instrText_hyperlink.docx b/test/docx/instrText_hyperlink.docx
new file mode 100644
index 000000000..9f24b3896
--- /dev/null
+++ b/test/docx/instrText_hyperlink.docx
Binary files differ
diff --git a/test/docx/instrText_hyperlink.native b/test/docx/instrText_hyperlink.native
new file mode 100644
index 000000000..4293c48db
--- /dev/null
+++ b/test/docx/instrText_hyperlink.native
@@ -0,0 +1 @@
+[Para [Str "\24076\26395\28145\20837\20102\35299\30340\35835\32773\21487\20197\21435\30475David",Space,Str "French",Space,Str "Belding\21644Kevin",Space,Str "J.",Space,Str "Mitchell\30340",Link ("",[],[]) [Str "Foundations",Space,Str "of",Space,Str "Analysis,",Space,Str "2nd",Space,Str "Edition"] ("https://books.google.com/books?id=sp_Zcb9ot90C&lpg=PR4&hl=zh-CN&pg=PA19#v=onepage&q&f=true",""),Str ",\21487\20174\&19\39029\30475\36215\65292\25110D.C.",Space,Str "Goldrei\30340",Space,Link ("",[],[]) [Str "Classic",Space,Str "Set",Space,Str "Theory:",Space,Str "For",Space,Str "Guided",Space,Str "Independent",Space,Str "Study"] ("https://books.google.ae/books?id=dlc0DwAAQBAJ&lpg=PT29&hl=zh-CN&pg=PT26#v=onepage&q&f=true",""),Str "\65292\20174\31532\20108\31456\30475\36215\65292\38405\35835\26102\35201\27880\24847\26412\25991\19982\36825\20123\20070\25152\19981\21516\30340\26159\24182\27809\26377\25226\23454\25968\30475\20316\26159\26377\29702\25968\38598\30340\20998\21106\12290"]]
diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native
index 742b6187c..17e91bb89 100644
--- a/test/markdown-reader-more.native
+++ b/test/markdown-reader-more.native
@@ -3,7 +3,8 @@ 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\n\n\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
+,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]"
,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}"
,Header 2 ("urls-with-spaces-and-punctuation",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "punctuation"]
@@ -54,6 +55,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}"
,Para [Math InlineMath "\\langle x,y \\rangle"]
,Header 2 ("case-insensitive-references",[],[]) [Str "Case-insensitive",Space,Str "references"]
,Para [Link ("",[],[]) [Str "Fum"] ("/fum","")]
diff --git a/test/pptx/inline_formatting.native b/test/pptx/inline_formatting.native
new file mode 100644
index 000000000..d79220e4f
--- /dev/null
+++ b/test/pptx/inline_formatting.native
@@ -0,0 +1,5 @@
+Pandoc (Meta {unMeta = fromList []})
+[Para [Str "Here",Space,Str "are",Space,Str "examples",Space,Str "of",Space,Emph [Str "italics"],Str ",",Space,Strong [Str "bold"],Str ",",Space,Str "and",Space,Strong [Emph [Str "bold",Space,Str "italics"]],Str "."]
+,Para [Str "Here",Space,Str "is",Space,Strikeout [Str "strook-three"],Space,Str "strike-through",Space,Str "and",Space,SmallCaps [Str "small",Space,Str "caps"],Str "."]
+,Para [Str "We",Space,Str "can",Space,Str "also",Space,Str "do",Space,Str "subscripts",Space,Str "(H",Subscript [Str "2"],Str "0)",Space,Str "and",Space,Str "super",Superscript [Str "script"],Str "."]
+,RawBlock (Format "html") "<!-- Comments don't show up. -->"]
diff --git a/test/pptx/inline_formatting.pptx b/test/pptx/inline_formatting.pptx
new file mode 100644
index 000000000..e128f1bce
--- /dev/null
+++ b/test/pptx/inline_formatting.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks.native b/test/pptx/slide_breaks.native
new file mode 100644
index 000000000..084c61737
--- /dev/null
+++ b/test/pptx/slide_breaks.native
@@ -0,0 +1,7 @@
+Pandoc (Meta {unMeta = fromList []})
+[Para [Str "Break",Space,Str "with",Space,Str "a",Space,Str "new",Space,Str "section-level",Space,Str "header"]
+,Header 1 ("below-section-level",[],[]) [Str "Below",Space,Str "section-level"]
+,Header 2 ("section-level",[],[]) [Str "Section-level"]
+,Para [Str "Third",Space,Str "slide",Space,Str "(with",Space,Str "a",Space,Str "section-level",Space,Str "of",Space,Str "2)"]
+,HorizontalRule
+,Para [Str "This",Space,Str "is",Space,Str "another",Space,Str "slide."]]
diff --git a/test/pptx/slide_breaks.pptx b/test/pptx/slide_breaks.pptx
new file mode 100644
index 000000000..b22b0bc50
--- /dev/null
+++ b/test/pptx/slide_breaks.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks_slide_level_1.pptx b/test/pptx/slide_breaks_slide_level_1.pptx
new file mode 100644
index 000000000..d4d7bc415
--- /dev/null
+++ b/test/pptx/slide_breaks_slide_level_1.pptx
Binary files differ
diff --git a/test/rst-reader.native b/test/rst-reader.native
index 724c23b03..b0e51bd3f 100644
--- a/test/rst-reader.native
+++ b/test/rst-reader.native
@@ -317,7 +317,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Math DisplayMath "E=mc^2"]
,Para [Math DisplayMath "E = mc^2"]
,Para [Math DisplayMath "E = mc^2",Math DisplayMath "\\alpha = \\beta"]
-,Para [Math DisplayMath "E &= mc^2\\\\\nF &= \\pi E",Math DisplayMath "F &= \\gamma \\alpha^2"]
+,Para [Math DisplayMath "\\begin{aligned}\nE &= mc^2\\\\\nF &= \\pi E\n\\end{aligned}",Math DisplayMath "F &= \\gamma \\alpha^2"]
,Para [Str "All",Space,Str "done."]
,Header 1 ("default-role",[],[]) [Str "Default-Role"]
,Para [Str "Try",Space,Str "changing",Space,Str "the",Space,Str "default",Space,Str "role",Space,Str "to",Space,Str "a",Space,Str "few",Space,Str "different",Space,Str "things."]
diff --git a/test/tables.context b/test/tables.context
index 371e559e5..89ff4a025 100644
--- a/test/tables.context
+++ b/test/tables.context
@@ -1,175 +1,230 @@
Simple table with caption:
-\placetable{Demonstration of simple table syntax.}
-\starttable[|r|l|c|l|]
-\HL
-\NC Right
-\NC Left
-\NC Center
-\NC Default
-\NC\AR
-\HL
-\NC 12
-\NC 12
-\NC 12
-\NC 12
-\NC\AR
-\NC 123
-\NC 123
-\NC 123
-\NC 123
-\NC\AR
-\NC 1
-\NC 1
-\NC 1
-\NC 1
-\NC\AR
-\HL
-\stoptable
+\startplacetable[caption={Demonstration of simple table syntax.}]
+\startxtable
+\startxtablehead[head]
+\startxrow
+\startxcell[align=left] Right \stopxcell
+\startxcell[align=right] Left \stopxcell
+\startxcell[align=middle] Center \stopxcell
+\startxcell Default \stopxcell
+\stopxrow
+\stopxtablehead
+\startxtablebody[body]
+\startxrow
+\startxcell[align=left] 12 \stopxcell
+\startxcell[align=right] 12 \stopxcell
+\startxcell[align=middle] 12 \stopxcell
+\startxcell 12 \stopxcell
+\stopxrow
+\startxrow
+\startxcell[align=left] 123 \stopxcell
+\startxcell[align=right] 123 \stopxcell
+\startxcell[align=middle] 123 \stopxcell
+\startxcell 123 \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=left] 1 \stopxcell
+\startxcell[align=right] 1 \stopxcell
+\startxcell[align=middle] 1 \stopxcell
+\startxcell 1 \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
Simple table without caption:
-\placetable[none]{}
-\starttable[|r|l|c|l|]
-\HL
-\NC Right
-\NC Left
-\NC Center
-\NC Default
-\NC\AR
-\HL
-\NC 12
-\NC 12
-\NC 12
-\NC 12
-\NC\AR
-\NC 123
-\NC 123
-\NC 123
-\NC 123
-\NC\AR
-\NC 1
-\NC 1
-\NC 1
-\NC 1
-\NC\AR
-\HL
-\stoptable
+\startplacetable[location=none]
+\startxtable
+\startxtablehead[head]
+\startxrow
+\startxcell[align=left] Right \stopxcell
+\startxcell[align=right] Left \stopxcell
+\startxcell[align=middle] Center \stopxcell
+\startxcell Default \stopxcell
+\stopxrow
+\stopxtablehead
+\startxtablebody[body]
+\startxrow
+\startxcell[align=left] 12 \stopxcell
+\startxcell[align=right] 12 \stopxcell
+\startxcell[align=middle] 12 \stopxcell
+\startxcell 12 \stopxcell
+\stopxrow
+\startxrow
+\startxcell[align=left] 123 \stopxcell
+\startxcell[align=right] 123 \stopxcell
+\startxcell[align=middle] 123 \stopxcell
+\startxcell 123 \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=left] 1 \stopxcell
+\startxcell[align=right] 1 \stopxcell
+\startxcell[align=middle] 1 \stopxcell
+\startxcell 1 \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
Simple table indented two spaces:
-\placetable{Demonstration of simple table syntax.}
-\starttable[|r|l|c|l|]
-\HL
-\NC Right
-\NC Left
-\NC Center
-\NC Default
-\NC\AR
-\HL
-\NC 12
-\NC 12
-\NC 12
-\NC 12
-\NC\AR
-\NC 123
-\NC 123
-\NC 123
-\NC 123
-\NC\AR
-\NC 1
-\NC 1
-\NC 1
-\NC 1
-\NC\AR
-\HL
-\stoptable
+\startplacetable[caption={Demonstration of simple table syntax.}]
+\startxtable
+\startxtablehead[head]
+\startxrow
+\startxcell[align=left] Right \stopxcell
+\startxcell[align=right] Left \stopxcell
+\startxcell[align=middle] Center \stopxcell
+\startxcell Default \stopxcell
+\stopxrow
+\stopxtablehead
+\startxtablebody[body]
+\startxrow
+\startxcell[align=left] 12 \stopxcell
+\startxcell[align=right] 12 \stopxcell
+\startxcell[align=middle] 12 \stopxcell
+\startxcell 12 \stopxcell
+\stopxrow
+\startxrow
+\startxcell[align=left] 123 \stopxcell
+\startxcell[align=right] 123 \stopxcell
+\startxcell[align=middle] 123 \stopxcell
+\startxcell 123 \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=left] 1 \stopxcell
+\startxcell[align=right] 1 \stopxcell
+\startxcell[align=middle] 1 \stopxcell
+\startxcell 1 \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
Multiline table with caption:
-\placetable{Here's the caption. It may span multiple lines.}
-\starttable[|cp(0.15\textwidth)|lp(0.14\textwidth)|rp(0.16\textwidth)|lp(0.34\textwidth)|]
-\HL
-\NC Centered Header
-\NC Left Aligned
-\NC Right Aligned
-\NC Default aligned
-\NC\AR
-\HL
-\NC First
-\NC row
-\NC 12.0
-\NC Example of a row that spans multiple lines.
-\NC\AR
-\NC Second
-\NC row
-\NC 5.0
-\NC Here's another one. Note the blank line between rows.
-\NC\AR
-\HL
-\stoptable
+\startplacetable[caption={Here's the caption. It may span multiple lines.}]
+\startxtable
+\startxtablehead[head]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] Centered Header \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] Left Aligned \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] Right Aligned \stopxcell
+\startxcell[align=right,width={0.34\textwidth}] Default aligned \stopxcell
+\stopxrow
+\stopxtablehead
+\startxtablebody[body]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] First \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] 12.0 \stopxcell
+\startxcell[align=right,width={0.34\textwidth}] Example of a row that spans
+multiple lines. \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] 5.0 \stopxcell
+\startxcell[align=right,width={0.34\textwidth}] Here's another one. Note the
+blank line between rows. \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
Multiline table without caption:
-\placetable[none]{}
-\starttable[|cp(0.15\textwidth)|lp(0.14\textwidth)|rp(0.16\textwidth)|lp(0.34\textwidth)|]
-\HL
-\NC Centered Header
-\NC Left Aligned
-\NC Right Aligned
-\NC Default aligned
-\NC\AR
-\HL
-\NC First
-\NC row
-\NC 12.0
-\NC Example of a row that spans multiple lines.
-\NC\AR
-\NC Second
-\NC row
-\NC 5.0
-\NC Here's another one. Note the blank line between rows.
-\NC\AR
-\HL
-\stoptable
+\startplacetable[location=none]
+\startxtable
+\startxtablehead[head]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] Centered Header \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] Left Aligned \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] Right Aligned \stopxcell
+\startxcell[align=right,width={0.34\textwidth}] Default aligned \stopxcell
+\stopxrow
+\stopxtablehead
+\startxtablebody[body]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] First \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] 12.0 \stopxcell
+\startxcell[align=right,width={0.34\textwidth}] Example of a row that spans
+multiple lines. \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] 5.0 \stopxcell
+\startxcell[align=right,width={0.34\textwidth}] Here's another one. Note the
+blank line between rows. \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
Table without column headers:
-\placetable[none]{}
-\starttable[|r|l|c|r|]
-\HL
-\NC 12
-\NC 12
-\NC 12
-\NC 12
-\NC\AR
-\NC 123
-\NC 123
-\NC 123
-\NC 123
-\NC\AR
-\NC 1
-\NC 1
-\NC 1
-\NC 1
-\NC\AR
-\HL
-\stoptable
+\startplacetable[location=none]
+\startxtable
+\startxtablebody[body]
+\startxrow
+\startxcell[align=left] 12 \stopxcell
+\startxcell[align=right] 12 \stopxcell
+\startxcell[align=middle] 12 \stopxcell
+\startxcell[align=left] 12 \stopxcell
+\stopxrow
+\startxrow
+\startxcell[align=left] 123 \stopxcell
+\startxcell[align=right] 123 \stopxcell
+\startxcell[align=middle] 123 \stopxcell
+\startxcell[align=left] 123 \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=left] 1 \stopxcell
+\startxcell[align=right] 1 \stopxcell
+\startxcell[align=middle] 1 \stopxcell
+\startxcell[align=left] 1 \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
Multiline table without column headers:
-\placetable[none]{}
-\starttable[|cp(0.15\textwidth)|lp(0.14\textwidth)|rp(0.16\textwidth)|lp(0.34\textwidth)|]
-\HL
-\NC First
-\NC row
-\NC 12.0
-\NC Example of a row that spans multiple lines.
-\NC\AR
-\NC Second
-\NC row
-\NC 5.0
-\NC Here's another one. Note the blank line between rows.
-\NC\AR
-\HL
-\stoptable
+\startplacetable[location=none]
+\startxtable
+\startxtablebody[body]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] First \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] 12.0 \stopxcell
+\startxcell[width={0.34\textwidth}] Example of a row that spans multiple
+lines. \stopxcell
+\stopxrow
+\stopxtablebody
+\startxtablefoot[foot]
+\startxrow
+\startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell
+\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
+\startxcell[align=left,width={0.16\textwidth}] 5.0 \stopxcell
+\startxcell[width={0.34\textwidth}] Here's another one. Note the blank line
+between rows. \stopxcell
+\stopxrow
+\stopxtablefoot
+\stopxtable
+\stopplacetable
diff --git a/test/tables.markdown b/test/tables.markdown
index 7f89bfc08..f5ee776fa 100644
--- a/test/tables.markdown
+++ b/test/tables.markdown
@@ -28,33 +28,33 @@ Simple table indented two spaces:
Multiline table with caption:
- --------------------------------------------------------------
+ -------------------------------------------------------------
Centered Left Right Default aligned
Header Aligned Aligned
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
First row 12.0 Example of a row that
spans multiple lines.
Second row 5.0 Here's another one. Note
the blank line between
rows.
- --------------------------------------------------------------
+ -------------------------------------------------------------
: Here's the caption. It may span multiple lines.
Multiline table without caption:
- --------------------------------------------------------------
+ -------------------------------------------------------------
Centered Left Right Default aligned
Header Aligned Aligned
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
First row 12.0 Example of a row that
spans multiple lines.
Second row 5.0 Here's another one. Note
the blank line between
rows.
- --------------------------------------------------------------
+ -------------------------------------------------------------
Table without column headers:
@@ -66,11 +66,11 @@ Table without column headers:
Multiline table without column headers:
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
First row 12.0 Example of a row that
spans multiple lines.
Second row 5.0 Here's another one. Note
the blank line between
rows.
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
diff --git a/test/tables.plain b/test/tables.plain
index e46317a6f..7013d0caa 100644
--- a/test/tables.plain
+++ b/test/tables.plain
@@ -28,33 +28,33 @@ Simple table indented two spaces:
Multiline table with caption:
- --------------------------------------------------------------
+ -------------------------------------------------------------
Centered Left Right Default aligned
Header Aligned Aligned
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
First row 12.0 Example of a row that
spans multiple lines.
Second row 5.0 Here’s another one. Note
the blank line between
rows.
- --------------------------------------------------------------
+ -------------------------------------------------------------
: Here’s the caption. It may span multiple lines.
Multiline table without caption:
- --------------------------------------------------------------
+ -------------------------------------------------------------
Centered Left Right Default aligned
Header Aligned Aligned
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
First row 12.0 Example of a row that
spans multiple lines.
Second row 5.0 Here’s another one. Note
the blank line between
rows.
- --------------------------------------------------------------
+ -------------------------------------------------------------
Table without column headers:
@@ -66,11 +66,11 @@ Table without column headers:
Multiline table without column headers:
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
First row 12.0 Example of a row that
spans multiple lines.
Second row 5.0 Here’s another one. Note
the blank line between
rows.
- ----------- ---------- ------------ --------------------------
+ ----------- ---------- ------------ -------------------------
diff --git a/test/writer.context b/test/writer.context
index 9884c82c9..e7af684f8 100644
--- a/test/writer.context
+++ b/test/writer.context
@@ -51,6 +51,11 @@
\setupthinrules[width=15em] % width of horizontal rules
+\setupxtable[frame=off]
+\setupxtable[head][topframe=on,bottomframe=on]
+\setupxtable[body][]
+\setupxtable[foot][bottomframe=on]
+
\starttext
\startalignment[middle]
diff --git a/test/writer.muse b/test/writer.muse
index db34a2733..33c622a3a 100644
--- a/test/writer.muse
+++ b/test/writer.muse
@@ -287,24 +287,21 @@ Multiple blocks with italics:
Multiple definitions, tight:
apple :: red fruit
- computer
+ :: computer
orange :: orange fruit
- bank
+ :: bank
Multiple definitions, loose:
apple :: red fruit
-
- computer
+ :: computer
orange :: orange fruit
-
- bank
+ :: bank
Blank line after term, indented marker, alternate markers:
apple :: red fruit
-
- computer
+ :: computer
orange :: orange fruit
1. sublist
diff --git a/test/writers-lang-and-dir.context b/test/writers-lang-and-dir.context
index 250ee8c59..19c45a4c9 100644
--- a/test/writers-lang-and-dir.context
+++ b/test/writers-lang-and-dir.context
@@ -49,6 +49,11 @@
\setupthinrules[width=15em] % width of horizontal rules
+\setupxtable[frame=off]
+\setupxtable[head][topframe=on,bottomframe=on]
+\setupxtable[body][]
+\setupxtable[foot][bottomframe=on]
+
\starttext