aboutsummaryrefslogtreecommitdiff
path: root/test/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests')
-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
7 files changed, 217 insertions, 45 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") =?>