aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers
diff options
context:
space:
mode:
authorIgor Pashev <pashev.igor@gmail.com>2021-07-17 18:10:34 +0200
committerIgor Pashev <pashev.igor@gmail.com>2021-07-17 18:46:16 +0200
commit48459559a13a20083fc9b31eb523b8ea2bf0a63f (patch)
tree1c04e75709457403110a6f8c5c90099f22369de3 /test/Tests/Writers
parent0c39509d9b6a58958228cebf5d643598e5c98950 (diff)
parent46099e79defe662e541b12548200caf29063c1c6 (diff)
downloadpandoc-48459559a13a20083fc9b31eb523b8ea2bf0a63f.tar.gz
Merge branch 'master' of https://github.com/jgm/pandoc
Diffstat (limited to 'test/Tests/Writers')
-rw-r--r--test/Tests/Writers/AnnotatedTable.hs1
-rw-r--r--test/Tests/Writers/AsciiDoc.hs2
-rw-r--r--test/Tests/Writers/ConTeXt.hs237
-rw-r--r--test/Tests/Writers/Docbook.hs105
-rw-r--r--test/Tests/Writers/Docx.hs17
-rw-r--r--test/Tests/Writers/FB2.hs2
-rw-r--r--test/Tests/Writers/HTML.hs111
-rw-r--r--test/Tests/Writers/JATS.hs228
-rw-r--r--test/Tests/Writers/Jira.hs61
-rw-r--r--test/Tests/Writers/LaTeX.hs2
-rw-r--r--test/Tests/Writers/Markdown.hs2
-rw-r--r--test/Tests/Writers/Ms.hs2
-rw-r--r--test/Tests/Writers/Muse.hs1
-rw-r--r--test/Tests/Writers/Native.hs2
-rw-r--r--test/Tests/Writers/OOXML.hs9
-rw-r--r--test/Tests/Writers/Org.hs59
-rw-r--r--test/Tests/Writers/Plain.hs2
-rw-r--r--test/Tests/Writers/Powerpoint.hs2
-rw-r--r--test/Tests/Writers/RST.hs2
-rw-r--r--test/Tests/Writers/TEI.hs2
20 files changed, 543 insertions, 306 deletions
diff --git a/test/Tests/Writers/AnnotatedTable.hs b/test/Tests/Writers/AnnotatedTable.hs
index 7e16cf8e0..53cca80a6 100644
--- a/test/Tests/Writers/AnnotatedTable.hs
+++ b/test/Tests/Writers/AnnotatedTable.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Writers.AnnotatedTable
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index 75f6e5e97..04655635f 100644
--- a/test/Tests/Writers/AsciiDoc.hs
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.AsciiDoc (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index c747e5d2f..fbbf9b948 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.ConTeXt (tests) where
-import Prelude
import Data.Text (unpack, pack)
import Test.Tasty
import Test.Tasty.QuickCheck
@@ -41,116 +39,125 @@ infix 4 =:
(=:) = test context
tests :: [TestTree]
-tests = [ testGroup "inline code"
- [ "with '}'" =: code "}" =?> "\\mono{\\}}"
- , "without '}'" =: code "]" =?> "\\type{]}"
- , testProperty "code property" $ \s -> null s || '\n' `elem` s ||
- if '{' `elem` s || '}' `elem` s
- then context' (code $ pack s) == "\\mono{" ++
- context' (str $ pack s) ++ "}"
- else context' (code $ pack s) == "\\type{" ++ s ++ "}"
- ]
- , testGroup "headers"
- [ "level 1" =:
- headerWith ("my-header",[],[]) 1 "My header" =?> "\\section[title={My header},reference={my-header}]"
- , test contextDiv "section-divs" $
- ( headerWith ("header1", [], []) 1 (text "Header1")
- <> headerWith ("header2", [], []) 2 (text "Header2")
- <> headerWith ("header3", [], []) 3 (text "Header3")
- <> headerWith ("header4", [], []) 4 (text "Header4")
- <> headerWith ("header5", [], []) 5 (text "Header5")
- <> headerWith ("header6", [], []) 6 (text "Header6"))
- =?>
- unlines [ "\\startsection[title={Header1},reference={header1}]\n"
- , "\\startsubsection[title={Header2},reference={header2}]\n"
- , "\\startsubsubsection[title={Header3},reference={header3}]\n"
- , "\\startsubsubsubsection[title={Header4},reference={header4}]\n"
- , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n"
- , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n"
- , "\\stopsubsubsubsubsubsection\n"
- , "\\stopsubsubsubsubsection\n"
- , "\\stopsubsubsubsection\n"
- , "\\stopsubsubsection\n"
- , "\\stopsubsection\n"
- , "\\stopsection" ]
- ]
- , testGroup "bullet lists"
- [ "nested" =:
- bulletList [
- plain (text "top")
- <> bulletList [
- plain (text "next")
- <> bulletList [plain (text "bot")]
- ]
- ] =?> unlines
- [ "\\startitemize[packed]"
- , "\\item"
- , " top"
- , " \\startitemize[packed]"
- , " \\item"
- , " next"
- , " \\startitemize[packed]"
- , " \\item"
- , " bot"
- , " \\stopitemize"
- , " \\stopitemize"
- , "\\stopitemize" ]
- ]
- , testGroup "natural tables"
- [ test contextNtb "table with header and caption" $
- let capt = text "Table 1"
- aligns = [(AlignRight, ColWidthDefault), (AlignLeft, ColWidthDefault), (AlignCenter, ColWidthDefault), (AlignDefault, ColWidthDefault)]
- 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"]]
- toRow = Row nullAttr . map simpleCell
- in table (simpleCaption $ plain capt)
- aligns
- (TableHead nullAttr [toRow headers])
- [TableBody nullAttr 0 [] $ map toRow rows]
- (TableFoot nullAttr [])
- =?> unlines [ "\\startplacetable[title={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" ]
- ]
- ]
+tests =
+ [ testGroup "inline code"
+ [ "with '}'" =: code "}" =?> "\\mono{\\}}"
+ , "without '}'" =: code "]" =?> "\\type{]}"
+ , "span with ID" =:
+ spanWith ("city", [], []) "Berlin" =?>
+ "\\reference[city]{}Berlin"
+ , testProperty "code property" $ \s -> null s || '\n' `elem` s ||
+ if '{' `elem` s || '}' `elem` s
+ then context' (code $ pack s) == "\\mono{" ++
+ context' (str $ pack s) ++ "}"
+ else context' (code $ pack s) == "\\type{" ++ s ++ "}"
+ ]
+ , testGroup "headers"
+ [ "level 1" =:
+ headerWith ("my-header",[],[]) 1 "My header" =?>
+ "\\section[title={My header},reference={my-header}]"
+ , test contextDiv "section-divs" $
+ ( headerWith ("header1", [], []) 1 (text "Header1")
+ <> headerWith ("header2", [], []) 2 (text "Header2")
+ <> headerWith ("header3", [], []) 3 (text "Header3")
+ <> headerWith ("header4", [], []) 4 (text "Header4")
+ <> headerWith ("header5", [], []) 5 (text "Header5")
+ <> headerWith ("header6", [], []) 6 (text "Header6"))
+ =?>
+ unlines
+ [ "\\startsection[title={Header1},reference={header1}]\n"
+ , "\\startsubsection[title={Header2},reference={header2}]\n"
+ , "\\startsubsubsection[title={Header3},reference={header3}]\n"
+ , "\\startsubsubsubsection[title={Header4},reference={header4}]\n"
+ , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n"
+ , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n"
+ , "\\stopsubsubsubsubsubsection\n"
+ , "\\stopsubsubsubsubsection\n"
+ , "\\stopsubsubsubsection\n"
+ , "\\stopsubsubsection\n"
+ , "\\stopsubsection\n"
+ , "\\stopsection" ]
+ ]
+ , testGroup "bullet lists"
+ [ "nested" =:
+ bulletList [
+ plain (text "top")
+ <> bulletList [
+ plain (text "next")
+ <> bulletList [plain (text "bot")]
+ ]
+ ] =?> unlines
+ [ "\\startitemize[packed]"
+ , "\\item"
+ , " top"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " next"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " bot"
+ , " \\stopitemize"
+ , " \\stopitemize"
+ , "\\stopitemize" ]
+ ]
+ , testGroup "natural tables"
+ [ test contextNtb "table with header and caption" $
+ let capt = text "Table 1"
+ aligns = [ (AlignRight, ColWidthDefault)
+ , (AlignLeft, ColWidthDefault)
+ , (AlignCenter, ColWidthDefault)
+ , (AlignDefault, ColWidthDefault) ]
+ 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"]]
+ toRow = Row nullAttr . map simpleCell
+ in table (simpleCaption $ plain capt)
+ aligns
+ (TableHead nullAttr [toRow headers])
+ [TableBody nullAttr 0 [] $ map toRow rows]
+ (TableFoot nullAttr [])
+ =?> unlines [ "\\startplacetable[title={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 f6a047b0b..f517f803a 100644
--- a/test/Tests/Writers/Docbook.hs
+++ b/test/Tests/Writers/Docbook.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Docbook (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
@@ -13,9 +11,14 @@ import Text.Pandoc.Builder
docbook :: (ToPandoc a) => a -> String
docbook = docbookWithOpts def{ writerWrapText = WrapNone }
+docbook5 :: (ToPandoc a) => a -> String
+docbook5 = docbook5WithOpts def{ writerWrapText = WrapNone }
+
docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc
+docbook5WithOpts :: ToPandoc a => WriterOptions -> a -> String
+docbook5WithOpts opts = unpack . purely (writeDocbook5 opts) . toPandoc
{-
"my test" =: X =?> Y
@@ -70,6 +73,72 @@ tests = [ testGroup "line blocks"
, "</para>" ]
)
]
+ , testGroup "divs"
+ [ "admonition" =: divWith ("foo", ["warning"], []) (para "This is a test")
+ =?> unlines
+ [ "<warning id=\"foo\">"
+ , " <para>"
+ , " This is a test"
+ , " </para>"
+ , "</warning>"
+ ]
+ , "admonition-with-title" =:
+ divWith ("foo", ["note"], []) (
+ divWith ("foo", ["title"], [])
+ (plain (text "This is title")) <>
+ para "This is a test"
+ )
+ =?> unlines
+ [ "<note id=\"foo\">"
+ , " <title>This is title</title>"
+ , " <para>"
+ , " This is a test"
+ , " </para>"
+ , "</note>"
+ ]
+ , "admonition-with-title-in-para" =:
+ divWith ("foo", ["note"], []) (
+ divWith ("foo", ["title"], [])
+ (para "This is title") <>
+ para "This is a test"
+ )
+ =?> unlines
+ [ "<note id=\"foo\">"
+ , " <title>This is title</title>"
+ , " <para>"
+ , " This is a test"
+ , " </para>"
+ , "</note>"
+ ]
+ , "single-child" =:
+ divWith ("foo", [], []) (para "This is a test")
+ =?> unlines
+ [ "<para id=\"foo\">"
+ , " This is a test"
+ , "</para>"
+ ]
+ , "single-literal-child" =:
+ divWith ("foo", [], []) lineblock
+ =?> unlines
+ [ "<literallayout id=\"foo\">some text"
+ , "and more lines"
+ , "and again</literallayout>"
+ ]
+ , "multiple-children" =:
+ divWith ("foo", [], []) (
+ para "This is a test" <>
+ para "This is an another test"
+ )
+ =?> unlines
+ [ "<anchor id=\"foo\" />"
+ , "<para>"
+ , " This is a test"
+ , "</para>"
+ , "<para>"
+ , " This is an another test"
+ , "</para>"
+ ]
+ ]
, testGroup "compact lists"
[ testGroup "bullet"
[ "compact" =: bulletList [plain "a", plain "b", plain "c"]
@@ -302,4 +371,36 @@ tests = [ testGroup "line blocks"
]
]
]
+ , testGroup "section attributes" $
+ let
+ headers = headerWith ("myid1",[],[("role","internal"),("xml:id","anotherid"),("dir","rtl")]) 1 "header1"
+ <> headerWith ("myid2",[],[("invalidname","value"),("arch","linux"),("dir","invaliddir")]) 1 "header2"
+ in
+ [ test docbook5 "sections with attributes (db5)" $
+ headers =?>
+ unlines [ "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid1\" role=\"internal\" dir=\"rtl\">"
+ , " <title>header1</title>"
+ , " <para>"
+ , " </para>"
+ , "</section>"
+ , "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid2\">"
+ , " <title>header2</title>"
+ , " <para>"
+ , " </para>"
+ , "</section>"
+ ]
+ , test docbook "sections with attributes (db4)" $
+ headers =?>
+ unlines [ "<sect1 id=\"myid1\" role=\"internal\">"
+ , " <title>header1</title>"
+ , " <para>"
+ , " </para>"
+ , "</sect1>"
+ , "<sect1 id=\"myid2\" arch=\"linux\">"
+ , " <title>header2</title>"
+ , " <para>"
+ , " </para>"
+ , "</sect1>"
+ ]
+ ]
]
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
index 8f051b4b7..da25b95e0 100644
--- a/test/Tests/Writers/Docx.hs
+++ b/test/Tests/Writers/Docx.hs
@@ -1,7 +1,5 @@
-{-# LANGUAGE NoImplicitPrelude #-}
module Tests.Writers.Docx (tests) where
-import Prelude
import Text.Pandoc
import Test.Tasty
import Tests.Writers.OOXML
@@ -114,6 +112,11 @@ tests = [ testGroup "inlines"
"docx/tables.native"
"docx/golden/tables.docx"
, docxTest
+ "tables without explicit column widths"
+ def
+ "docx/tables-default-widths.native"
+ "docx/golden/tables-default-widths.docx"
+ , docxTest
"tables with lists in cells"
def
"docx/table_with_list_cell.native"
@@ -128,6 +131,16 @@ tests = [ testGroup "inlines"
def
"docx/codeblock.native"
"docx/golden/codeblock.docx"
+ , docxTest
+ "raw OOXML blocks"
+ def
+ "docx/raw-blocks.native"
+ "docx/golden/raw-blocks.docx"
+ , docxTest
+ "raw bookmark markers"
+ def
+ "docx/raw-bookmarks.native"
+ "docx/golden/raw-bookmarks.docx"
]
, testGroup "track changes"
[ docxTest
diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs
index 7699c58e9..2e10636fa 100644
--- a/test/Tests/Writers/FB2.hs
+++ b/test/Tests/Writers/FB2.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.FB2 (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs
index 6ff0a6e1d..404f6da98 100644
--- a/test/Tests/Writers/HTML.hs
+++ b/test/Tests/Writers/HTML.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.HTML (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
@@ -36,55 +34,60 @@ infix 4 =:
(=:) = test html
tests :: [TestTree]
-tests = [ testGroup "inline code"
- [ "basic" =: code "@&" =?> "<code>@&amp;</code>"
- , "haskell" =: codeWith ("",["haskell"],[]) ">>="
- =?> "<code class=\"sourceCode haskell\"><span class=\"op\">&gt;&gt;=</span></code>"
- , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
- =?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
- ]
- , testGroup "images"
- [ "alt with formatting" =:
- image "/url" "title" ("my " <> emph "image")
- =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
- ]
- , testGroup "blocks"
- [ "definition list with empty <dt>" =:
- definitionList [(mempty, [para $ text "foo bar"])]
- =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
- ]
- , testGroup "quotes"
- [ "quote with cite attribute (without q-tags)" =:
- doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
- =?> "“<span cite=\"http://example.org\">examples</span>”"
- , tQ "quote with cite attribute (with q-tags)" $
- doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
- =?> "<q cite=\"http://example.org\">examples</q>"
- ]
- , testGroup "sample"
- [ "sample should be rendered correctly" =:
- plain (codeWith ("",["sample"],[]) "Answer is 42") =?>
- "<samp>Answer is 42</samp>"
- ]
- , testGroup "variable"
- [ "variable should be rendered correctly" =:
- plain (codeWith ("",["variable"],[]) "result") =?>
- "<var>result</var>"
- ]
- , testGroup "sample with style"
- [ "samp should wrap highlighted code" =:
- codeWith ("",["sample","haskell"],[]) ">>="
- =?> ("<samp><code class=\"sourceCode haskell\">" ++
- "<span class=\"op\">&gt;&gt;=</span></code></samp>")
- ]
- , testGroup "variable with style"
- [ "var should wrap highlighted code" =:
- codeWith ("",["haskell","variable"],[]) ">>="
- =?> ("<var><code class=\"sourceCode haskell\">" ++
- "<span class=\"op\">&gt;&gt;=</span></code></var>")
- ]
- ]
- where
- tQ :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
- tQ = test htmlQTags
+tests =
+ [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<code>@&amp;</code>"
+ , "haskell" =: codeWith ("",["haskell"],[]) ">>="
+ =?> "<code class=\"sourceCode haskell\"><span class=\"op\">&gt;&gt;=</span></code>"
+ , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
+ =?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
+ ]
+ , testGroup "images"
+ [ "alt with formatting" =:
+ image "/url" "title" ("my " <> emph "image")
+ =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
+ ]
+ , testGroup "blocks"
+ [ "definition list with empty <dt>" =:
+ definitionList [(mempty, [para $ text "foo bar"])]
+ =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
+ , "heading with disallowed attributes" =:
+ headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test"
+ =?>
+ "<h1 lang=\"en\">test</h1>"
+ ]
+ , testGroup "quotes"
+ [ "quote with cite attribute (without q-tags)" =:
+ doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
+ =?> "“<span cite=\"http://example.org\">examples</span>”"
+ , tQ "quote with cite attribute (with q-tags)" $
+ doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
+ =?> "<q cite=\"http://example.org\">examples</q>"
+ ]
+ , testGroup "sample"
+ [ "sample should be rendered correctly" =:
+ plain (codeWith ("",["sample"],[]) "Answer is 42") =?>
+ "<samp>Answer is 42</samp>"
+ ]
+ , testGroup "variable"
+ [ "variable should be rendered correctly" =:
+ plain (codeWith ("",["variable"],[]) "result") =?>
+ "<var>result</var>"
+ ]
+ , testGroup "sample with style"
+ [ "samp should wrap highlighted code" =:
+ codeWith ("",["sample","haskell"],[]) ">>="
+ =?> ("<samp><code class=\"sourceCode haskell\">" ++
+ "<span class=\"op\">&gt;&gt;=</span></code></samp>")
+ ]
+ , testGroup "variable with style"
+ [ "var should wrap highlighted code" =:
+ codeWith ("",["haskell","variable"],[]) ">>="
+ =?> ("<var><code class=\"sourceCode haskell\">" ++
+ "<span class=\"op\">&gt;&gt;=</span></code></var>")
+ ]
+ ]
+ where
+ tQ :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+ tQ = test htmlQTags
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
index 7d98f979b..5b96ed2ed 100644
--- a/test/Tests/Writers/JATS.hs
+++ b/test/Tests/Writers/JATS.hs
@@ -1,23 +1,21 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.JATS (tests) where
-import Prelude
-import Data.Text (unpack)
+import Data.Text (Text)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import qualified Data.Text as T
-jats :: (ToPandoc a) => a -> String
-jats = unpack
- . purely (writeJATS def{ writerWrapText = WrapNone })
- . toPandoc
+jats :: (ToPandoc a) => a -> Text
+jats = purely (writeJATS def{ writerWrapText = WrapNone })
+ . toPandoc
-jatsArticleAuthoring :: (ToPandoc a) => a -> String
-jatsArticleAuthoring = unpack
- . purely (writeJatsArticleAuthoring def{ writerWrapText = WrapNone })
+jatsArticleAuthoring :: (ToPandoc a) => a -> Text
+jatsArticleAuthoring =
+ purely (writeJatsArticleAuthoring def{ writerWrapText = WrapNone })
. toPandoc
{-
@@ -34,89 +32,133 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
+ => String -> (a, Text) -> TestTree
(=:) = test jats
tests :: [TestTree]
-tests = [ testGroup "inline code"
- [ "basic" =: code "@&" =?> "<p><monospace>@&amp;</monospace></p>"
- , "lang" =: codeWith ("", ["c"], []) "@&" =?> "<p><code language=\"c\">@&amp;</code></p>"
- ]
- , testGroup "block code"
- [ "basic" =: codeBlock "@&" =?> "<preformat>@&amp;</preformat>"
- , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "<code language=\"c\">@&amp;</code>"
- ]
- , testGroup "images"
- [ "basic" =:
- image "/url" "title" mempty
- =?> "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
- ]
- , testGroup "inlines"
- [ "Emphasis" =: emph "emphasized"
- =?> "<p><italic>emphasized</italic></p>"
-
- , test jatsArticleAuthoring "footnote in articleauthoring tag set"
- ("test" <> note (para "footnote") =?>
- unlines [ "<p>test<fn>"
- , " <p>footnote</p>"
- , "</fn></p>"
- ])
- ]
- , "bullet list" =: bulletList [ plain $ text "first"
- , plain $ text "second"
- , plain $ text "third"
- ]
- =?> "<list list-type=\"bullet\">\n\
- \ <list-item>\n\
- \ <p>first</p>\n\
- \ </list-item>\n\
- \ <list-item>\n\
- \ <p>second</p>\n\
- \ </list-item>\n\
- \ <list-item>\n\
- \ <p>third</p>\n\
- \ </list-item>\n\
- \</list>"
- , testGroup "definition lists"
- [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
- [plain (text "hi there")])] =?>
- "<def-list>\n\
- \ <def-item>\n\
- \ <term><xref alt=\"testing\" rid=\"go\">testing</xref></term>\n\
- \ <def>\n\
- \ <p>hi there</p>\n\
- \ </def>\n\
- \ </def-item>\n\
- \</def-list>"
- ]
- , testGroup "math"
- [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
- "<p><inline-formula><alternatives>\n\
- \<tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
- \<mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula></p>"
- ]
- , testGroup "headers"
- [ "unnumbered header" =:
- headerWith ("foo",["unnumbered"],[]) 1
- (text "Header 1" <> note (plain $ text "note")) =?>
- "<sec id=\"foo\">\n\
- \ <title>Header 1<xref ref-type=\"fn\" rid=\"fn1\">1</xref></title>\n\
- \</sec>"
- , "unnumbered sub header" =:
- headerWith ("foo",["unnumbered"],[]) 1
- (text "Header")
- <> headerWith ("foo",["unnumbered"],[]) 2
- (text "Sub-Header") =?>
- "<sec id=\"foo\">\n\
- \ <title>Header</title>\n\
- \ <sec id=\"foo\">\n\
- \ <title>Sub-Header</title>\n\
- \ </sec>\n\
- \</sec>"
- , "containing image" =:
- header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
- "<sec>\n\
- \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
- \</sec>"
- ]
- ]
+tests =
+ [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<p><monospace>@&amp;</monospace></p>"
+ , "lang" =: codeWith ("", ["c"], []) "@&" =?> "<p><code language=\"c\">@&amp;</code></p>"
+ ]
+ , testGroup "block code"
+ [ "basic" =: codeBlock "@&" =?> "<preformat>@&amp;</preformat>"
+ , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "<code language=\"c\">@&amp;</code>"
+ ]
+ , testGroup "images"
+ [ "basic" =:
+ image "/url" "title" mempty
+ =?> "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
+ ]
+ , testGroup "inlines"
+ [ "Emphasis" =: emph "emphasized"
+ =?> "<p><italic>emphasized</italic></p>"
+
+ , test jatsArticleAuthoring "footnote in articleauthoring tag set"
+ ("test" <> note (para "footnote") =?>
+ unlines [ "<p>test<fn>"
+ , " <p>footnote</p>"
+ , "</fn></p>"
+ ])
+ ]
+ , "bullet list" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>first</p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>second</p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>third</p>\n\
+ \ </list-item>\n\
+ \</list>"
+ , testGroup "definition lists"
+ [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
+ [plain (text "hi there")])] =?>
+ "<def-list>\n\
+ \ <def-item>\n\
+ \ <term><xref alt=\"testing\" rid=\"go\">testing</xref></term>\n\
+ \ <def>\n\
+ \ <p>hi there</p>\n\
+ \ </def>\n\
+ \ </def-item>\n\
+ \</def-list>"
+ ]
+ , testGroup "math"
+ [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
+ "<p><inline-formula><alternatives>\n\
+ \<tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \<mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula></p>"
+ ]
+ , testGroup "headers"
+ [ "unnumbered header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header 1" <> note (plain $ text "note")) =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header 1<xref ref-type=\"fn\" rid=\"fn1\">1</xref></title>\n\
+ \</sec>"
+ , "unnumbered sub header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header")
+ <> headerWith ("foo",["unnumbered"],[]) 2
+ (text "Sub-Header") =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header</title>\n\
+ \ <sec id=\"foo\">\n\
+ \ <title>Sub-Header</title>\n\
+ \ </sec>\n\
+ \</sec>"
+ , "containing image" =:
+ header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
+ "<sec>\n\
+ \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
+ \</sec>"
+ ]
+
+ , testGroup "ids"
+ [ "non-ASCII in header ID" =:
+ headerWith ("smørbrød",[],[]) 1 (text "smørbrød") =?>
+ T.unlines [ "<sec id=\"smørbrød\">"
+ , " <title>smørbrød</title>"
+ , "</sec>"
+ ]
+
+ , "disallowed symbol in header id" =:
+ headerWith ("i/o",[],[]) 1 (text "I/O") =?>
+ T.unlines [ "<sec id=\"iU002Fo\">"
+ , " <title>I/O</title>"
+ , "</sec>"
+ ]
+
+ , "disallowed symbols in internal link target" =:
+ link "#foo:bar" "" "baz" =?>
+ "<p><xref alt=\"baz\" rid=\"fooU003Abar\">baz</xref></p>"
+
+ , "code id starting with a number" =:
+ codeWith ("7y",[],[]) "print 5" =?>
+ "<p><monospace id=\"U0037y\">print 5</monospace></p>"
+ ]
+
+ , testGroup "spans"
+ [ "unwrapped if no attributes given" =:
+ spanWith nullAttr "text in span" =?>
+ "<p>text in span</p>"
+
+ , "converted to named-content element if class given" =:
+ spanWith ("a", ["genus-species"], [("alt", "aa")]) "C. elegans" =?>
+ ("<p><named-content id=\"a\" alt=\"aa\" content-type=\"genus-species\">"
+ <> "C. elegans</named-content></p>")
+
+ , "unwrapped if styled-content element would have no attributes" =:
+ spanWith ("", [], [("hidden", "true")]) "text in span" =?>
+ "<p>text in span</p>"
+
+ , "use content-type attribute if present" =:
+ spanWith ("", [], [("content-type", "species")]) "E. coli" =?>
+ "<p><named-content content-type=\"species\">E. coli</named-content></p>"
+ ]
+ ]
diff --git a/test/Tests/Writers/Jira.hs b/test/Tests/Writers/Jira.hs
index 93d830c94..00a7ae931 100644
--- a/test/Tests/Writers/Jira.hs
+++ b/test/Tests/Writers/Jira.hs
@@ -3,6 +3,7 @@ module Tests.Writers.Jira (tests) where
import Data.Text (unpack)
import Test.Tasty
+import Test.Tasty.HUnit (HasCallStack)
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@@ -12,7 +13,7 @@ jira :: (ToPandoc a) => a -> String
jira = unpack . purely (writeJira def) . toPandoc
infix 4 =:
-(=:) :: (ToString a, ToPandoc a)
+(=:) :: (ToString a, ToPandoc a, HasCallStack)
=> String -> (a, String) -> TestTree
(=:) = test jira
@@ -60,6 +61,64 @@ tests =
, "user link with user as description" =:
linkWith ("", ["user-account"], []) "~johndoe" "" "~johndoe" =?>
"[~johndoe]"
+
+ , "'smart' link" =:
+ para (linkWith ("", ["smart-link"], []) "http://example.com" "" "x") =?>
+ "[x|http://example.com|smart-link]"
+
+ , "'smart' card" =:
+ para (linkWith ("", ["smart-card"], []) "http://example.org" "" "x") =?>
+ "[x|http://example.org|smart-card]"
+ ]
+
+ , testGroup "spans"
+ [ "id is used as anchor" =:
+ spanWith ("unicorn", [], []) (str "Unicorn") =?>
+ "{anchor:unicorn}Unicorn"
+
+ , "use `color` attribute" =:
+ spanWith ("",[],[("color","red")]) "ruby" =?>
+ "{color:red}ruby{color}"
+ ]
+
+ , testGroup "code"
+ [ "code block with known language" =:
+ codeBlockWith ("", ["java"], []) "Book book = new Book(\"Algebra\")" =?>
+ "{code:java}\nBook book = new Book(\"Algebra\")\n{code}"
+
+ , "code block without language" =:
+ codeBlockWith ("", [], []) "preformatted\n text.\n" =?>
+ "{noformat}\npreformatted\n text.\n{noformat}"
+ ]
+ ]
+
+ , testGroup "blocks"
+ [ testGroup "div"
+ [ "empty attributes" =:
+ divWith nullAttr (para "interesting text") =?>
+ "interesting text"
+
+ , "just identifier" =:
+ divWith ("a", [], []) (para "interesting text") =?>
+ "{anchor:a}interesting text"
+
+ , "with class 'panel'" =:
+ divWith ("", ["panel"], []) (para "Contents!") =?>
+ "{panel}\nContents\\!\n{panel}\n"
+
+ , "panel with id" =:
+ divWith ("b", ["panel"], []) (para "text") =?>
+ "{panel}\n{anchor:b}text\n{panel}\n"
+
+ , "title attribute" =:
+ divWith ("", [], [("title", "Gimme!")]) (para "Contents!") =?>
+ "{panel:title=Gimme!}\nContents\\!\n{panel}\n"
+
+ , "nested panels" =:
+ let panelAttr = ("", ["panel"], [])
+ in divWith panelAttr (para "hi" <>
+ divWith panelAttr (para "wassup?")) =?>
+ "{panel}\nhi\n\nwassup?\n{panel}\n"
]
]
]
diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs
index 44e23d48e..ae5879099 100644
--- a/test/Tests/Writers/LaTeX.hs
+++ b/test/Tests/Writers/LaTeX.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.LaTeX (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs
index 4b819de24..d4f927ebe 100644
--- a/test/Tests/Writers/Markdown.hs
+++ b/test/Tests/Writers/Markdown.hs
@@ -1,9 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Tests.Writers.Markdown (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Writers/Ms.hs b/test/Tests/Writers/Ms.hs
index d73603314..ad6849633 100644
--- a/test/Tests/Writers/Ms.hs
+++ b/test/Tests/Writers/Ms.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Ms (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index d0df0799f..5bddca3af 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Muse (tests) where
diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs
index 905e83b1e..d7771ca19 100644
--- a/test/Tests/Writers/Native.hs
+++ b/test/Tests/Writers/Native.hs
@@ -1,7 +1,5 @@
-{-# LANGUAGE NoImplicitPrelude #-}
module Tests.Writers.Native (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Test.Tasty.QuickCheck
diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs
index 628ea9409..83f05cfec 100644
--- a/test/Tests/Writers/OOXML.hs
+++ b/test/Tests/Writers/OOXML.hs
@@ -1,10 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.OOXML (ooxmlTest) where
-import Prelude
import Text.Pandoc
import Test.Tasty
import Test.Tasty.Golden.Advanced
@@ -45,7 +43,8 @@ compareXMLBool _ _ = False
displayDiff :: Content -> Content -> String
displayDiff elemA elemB =
- showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB)
+ showDiff (1,1)
+ (getDiff (lines $ showContent elemA) (lines $ showContent elemB))
goldenArchive :: FilePath -> IO Archive
goldenArchive fp = toArchive . BL.fromStrict <$> BS.readFile fp
@@ -56,7 +55,9 @@ testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString)
-> IO Archive
testArchive writerFn opts fp = do
txt <- T.readFile fp
- bs <- runIOorExplode $ readNative def txt >>= writerFn opts
+ bs <- runIOorExplode $ do
+ setTranslations "en-US"
+ readNative def txt >>= writerFn opts
return $ toArchive bs
compareFileList :: FilePath -> Archive -> Archive -> Maybe String
diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs
index c99f7344d..bd6c9b7ab 100644
--- a/test/Tests/Writers/Org.hs
+++ b/test/Tests/Writers/Org.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Org (tests) where
-import Prelude
+import Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -11,17 +10,51 @@ import Text.Pandoc.Builder
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
-(=:) = test (purely (writeOrg def . toPandoc))
+ => String -> (a, Text) -> TestTree
+(=:) = test org
+
+defopts :: WriterOptions
+defopts = def
+ { writerExtensions = getDefaultExtensions "org"
+ }
+
+org :: (ToPandoc a) => a -> Text
+org = orgWithOpts defopts
+
+orgWithOpts :: (ToPandoc a) => WriterOptions -> a -> Text
+orgWithOpts opts x = purely (writeOrg opts) $ toPandoc x
+
tests :: [TestTree]
-tests = [ testGroup "links"
- -- See http://orgmode.org/manual/Internal-links.html#Internal-links
- [ "simple link"
- =: link "/url" "" "foo"
- =?> "[[/url][foo]]"
- , "internal link to anchor"
- =: link "#my-custom-id" "" "#my-custom-id"
- =?> "[[#my-custom-id]]"
+tests =
+ [ testGroup "links"
+ -- See http://orgmode.org/manual/Internal-links.html#Internal-links
+ [ "simple link"
+ =: link "/url" "" "foo"
+ =?> "[[/url][foo]]"
+ , "internal link to anchor"
+ =: link "#my-custom-id" "" "#my-custom-id"
+ =?> "[[#my-custom-id]]"
+ ]
+
+ , testGroup "lists"
+ [ "bullet task list"
+ =: bulletList [plain "☐ a", plain "☒ b"]
+ =?> T.unlines
+ [ "- [ ] a"
+ , "- [X] b"
+ ]
+ , "ordered task list"
+ =: orderedList [plain ("☐" <> space <> "a"), plain "☒ b"]
+ =?> T.unlines
+ [ "1. [ ] a"
+ , "2. [X] b"
+ ]
+ , test (orgWithOpts def) "bullet without task_lists" $
+ bulletList [plain "☐ a", plain "☒ b"]
+ =?> T.unlines
+ [ "- ☐ a"
+ , "- ☒ b"
]
- ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Plain.hs b/test/Tests/Writers/Plain.hs
index b8d1f6693..17edc9dbd 100644
--- a/test/Tests/Writers/Plain.hs
+++ b/test/Tests/Writers/Plain.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Plain (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index be98fe0e7..87ebe990c 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -1,7 +1,5 @@
-{-# LANGUAGE NoImplicitPrelude #-}
module Tests.Writers.Powerpoint (tests) where
-import Prelude
import Tests.Writers.OOXML (ooxmlTest)
import Text.Pandoc
import Test.Tasty
diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs
index a52423fad..94745e9a2 100644
--- a/test/Tests/Writers/RST.hs
+++ b/test/Tests/Writers/RST.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.RST (tests) where
-import Prelude
import Control.Monad.Identity
import Test.Tasty
import Test.Tasty.HUnit
diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs
index 31e970495..fa372909f 100644
--- a/test/Tests/Writers/TEI.hs
+++ b/test/Tests/Writers/TEI.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.TEI (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc