aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Lua.hs80
-rw-r--r--test/Tests/Readers/Docx.hs4
-rw-r--r--test/Tests/Readers/Muse.hs98
-rw-r--r--test/Tests/Writers/ConTeXt.hs55
-rw-r--r--test/Tests/Writers/Muse.hs13
-rw-r--r--test/Tests/Writers/Powerpoint.hs2
-rw-r--r--test/Tests/Writers/RST.hs10
-rw-r--r--test/command/4159.md3
-rw-r--r--test/command/4235.md12
-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/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/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
25 files changed, 548 insertions, 227 deletions
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 6f495a3ca..b25a6fa4a 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -2,6 +2,7 @@
module Tests.Lua ( tests ) where
import Control.Monad (when)
+import Data.Version (Version (versionBranch))
import System.FilePath ((</>))
import Test.Tasty (TestTree, localOption)
import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
@@ -11,8 +12,11 @@ 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)
+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
@@ -106,13 +110,58 @@ tests = map (localOption (QuickCheckTests 20))
, plain (str "stringify: OK")
, plain (str "to_roman_numeral: OK")
])
+
+ , testCase "Pandoc version is set" . runPandocLua' $ do
+ Lua.getglobal' "table.concat"
+ Lua.getglobal "PANDOC_VERSION"
+ Lua.push ("." :: String) -- seperator
+ Lua.call 2 1
+ Lua.liftIO . assertEqual "pandoc version is wrong" pandocVersion
+ =<< Lua.peek Lua.stackTop
+
+ , testCase "Pandoc types version is set" . runPandocLua' $ do
+ let versionNums = versionBranch pandocTypesVersion
+ 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
@@ -121,18 +170,21 @@ roundtripEqual :: (Eq a, Lua.FromLuaStack a, Lua.ToLuaStack a) => a -> IO Bool
roundtripEqual x = (x ==) <$> roundtripped
where
roundtripped :: (Lua.FromLuaStack a, Lua.ToLuaStack a) => IO a
- roundtripped = runIOorExplode $ do
- setUserDataDir (Just "../data")
- res <- runPandocLua $ do
- oldSize <- Lua.gettop
- Lua.push x
- size <- Lua.gettop
- when (size - oldSize /= 1) $
- error ("not exactly one additional element on the stack: " ++ show size)
- res <- Lua.peekEither (-1)
- case res of
- Left _ -> error "could not read from stack"
- Right y -> return y
+ roundtripped = runPandocLua' $ do
+ oldSize <- Lua.gettop
+ Lua.push x
+ size <- Lua.gettop
+ when (size - oldSize /= 1) $
+ error ("not exactly one additional element on the stack: " ++ show size)
+ res <- Lua.peekEither (-1)
case res of
Left e -> error (show e)
Right y -> return y
+
+runPandocLua' :: Lua.Lua a -> IO a
+runPandocLua' op = runIOorExplode $ do
+ setUserDataDir (Just "../data")
+ res <- runPandocLua op
+ case res of
+ Left e -> error (show e)
+ Right x -> return x
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 68c2e3476..d58e219de 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -128,6 +128,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/Muse.hs b/test/Tests/Readers/Muse.hs
index e9ac64a96..c92b395ff 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -114,8 +114,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 +153,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 +164,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 +284,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 +353,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 +539,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 +717,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 +780,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 +924,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 +960,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/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index 783b601a9..7145240e3 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
@@ -68,5 +71,57 @@ 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/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/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index 39fd1bab5..cc94f822d 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -52,7 +52,7 @@ numSlideTests = testGroup "Number of slides in output"
def
(setTitle "My Title" $ doc $ para "foo")
, testNumberOfSlides
- "With h1 slide (using default slide-level)" 2
+ "With h1 slide (using default slide-level)" 1
def
(doc $ header 1 "Header" <> para "foo")
, testNumberOfSlides
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/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/4235.md b/test/command/4235.md
new file mode 100644
index 000000000..a5d545676
--- /dev/null
+++ b/test/command/4235.md
@@ -0,0 +1,12 @@
+```
+% pandoc --id-prefix=foo
+This.^[Has a footnote.]
+^D
+<p>This.<a href="#foofn1" class="footnote-ref" id="foofnref1"><sup>1</sup></a></p>
+<section class="footnotes">
+<hr />
+<ol>
+<li id="foofn1"><p>Has a footnote.<a href="#foofnref1" class="footnote-back">↩</a></p></li>
+</ol>
+</section>
+```
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/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/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