diff options
| author | John MacFarlane <[email protected]> | 2021-03-11 15:49:27 -0800 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2021-03-13 15:05:37 -0800 |
| commit | 8be95ad8e5150d5cab66c4abdf59baaf4670c6c8 (patch) | |
| tree | 9655036efbaabda6a2a7802dc971c7fba5a987ca /test/Tests/Writers | |
| parent | 35b66a76718205c303f416bf0afc01c098e8a171 (diff) | |
Use custom Prelude based on relude.relude
The Prelude now longer exports partial functions, so
a large number of uses of these functions in the
code base have been rewritten.
A .ghci file has been added; this is necessary for
ghci to work properly with the custom Prelude.
Currently there are lots of compiler warnings.
We should either fix these or go to using a custom
Prelude that changes less than relude.
Diffstat (limited to 'test/Tests/Writers')
| -rw-r--r-- | test/Tests/Writers/AnnotatedTable.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/AsciiDoc.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/ConTeXt.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/Docbook.hs | 15 | ||||
| -rw-r--r-- | test/Tests/Writers/FB2.hs | 10 | ||||
| -rw-r--r-- | test/Tests/Writers/HTML.hs | 12 | ||||
| -rw-r--r-- | test/Tests/Writers/JATS.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/Jira.hs | 2 | ||||
| -rw-r--r-- | test/Tests/Writers/LaTeX.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/Markdown.hs | 16 | ||||
| -rw-r--r-- | test/Tests/Writers/Ms.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/Muse.hs | 6 | ||||
| -rw-r--r-- | test/Tests/Writers/Native.hs | 5 | ||||
| -rw-r--r-- | test/Tests/Writers/OOXML.hs | 57 | ||||
| -rw-r--r-- | test/Tests/Writers/Org.hs | 2 | ||||
| -rw-r--r-- | test/Tests/Writers/Plain.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Writers/RST.hs | 10 | ||||
| -rw-r--r-- | test/Tests/Writers/TEI.hs | 2 |
18 files changed, 87 insertions, 78 deletions
diff --git a/test/Tests/Writers/AnnotatedTable.hs b/test/Tests/Writers/AnnotatedTable.hs index 53cca80a6..8e8ce9d3e 100644 --- a/test/Tests/Writers/AnnotatedTable.hs +++ b/test/Tests/Writers/AnnotatedTable.hs @@ -35,7 +35,7 @@ import Test.Tasty.QuickCheck ( QuickCheckTests(..) , elements ) import Text.Pandoc.Arbitrary ( ) -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B import qualified Text.Pandoc.Writers.AnnotatedTable as Ann @@ -150,7 +150,7 @@ propBuilderAnnTable th tbs tf = withColSpec $ \cs -> convertTable (table emptyCaption cs th tbs tf) === convertAnnTable (Ann.toTable nullAttr emptyCaption cs th tbs tf) where - convertTable blks = case toList blks of + convertTable blks = case B.toList blks of [Table _ _ colspec a b c] -> Right (colspec, a, b, c) x -> Left x convertAnnTable x = case Ann.fromTable x of diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs index 04655635f..6ab2bdb0d 100644 --- a/test/Tests/Writers/AsciiDoc.hs +++ b/test/Tests/Writers/AsciiDoc.hs @@ -11,9 +11,9 @@ import Text.Pandoc.Builder asciidoc :: (ToPandoc a) => a -> String asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc -testAsciidoc :: (ToString a, ToPandoc a) +testAsciidoc :: (ToText a, ToPandoc a) => String - -> (a, String) + -> (a, Text) -> TestTree testAsciidoc = test asciidoc diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index 5c1c98d4e..6aea41c85 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -34,8 +34,8 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test context tests :: [TestTree] diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs index 842aed7ae..657461366 100644 --- a/test/Tests/Writers/Docbook.hs +++ b/test/Tests/Writers/Docbook.hs @@ -8,11 +8,11 @@ import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -docbook :: (ToPandoc a) => a -> String +docbook :: (ToPandoc a) => a -> Text docbook = docbookWithOpts def{ writerWrapText = WrapNone } -docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String -docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc +docbookWithOpts :: ToPandoc a => WriterOptions -> a -> Text +docbookWithOpts opts = purely (writeDocbook4 opts) . toPandoc {- "my test" =: X =?> Y @@ -27,15 +27,16 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test docbook lineblock :: Blocks lineblock = para ("some text" <> linebreak <> "and more lines" <> linebreak <> "and again") -lineblock_out :: [String] + +lineblock_out :: [Text] lineblock_out = [ "<literallayout>some text" , "and more lines" , "and again</literallayout>" @@ -304,7 +305,7 @@ tests = [ testGroup "line blocks" <> header 3 (text "header3") docbookTopLevelDiv :: (ToPandoc a) - => TopLevelDivision -> a -> String + => TopLevelDivision -> a -> Text docbookTopLevelDiv division = docbookWithOpts def{ writerTopLevelDivision = division } in diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs index 2e10636fa..e4ff4d5cc 100644 --- a/test/Tests/Writers/FB2.hs +++ b/test/Tests/Writers/FB2.hs @@ -7,13 +7,13 @@ import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -fb2 :: String -> String -fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++ - "<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section>" ++ x ++ "</section></body></FictionBook>" +fb2 :: Text -> Text +fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" <> + "<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section>" <> x <> "</section></body></FictionBook>" infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test (purely (writeFB2 def) . toPandoc) tests :: [TestTree] diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 328801e31..5d59fd79b 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -29,8 +29,8 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test html tests :: [TestTree] @@ -72,17 +72,17 @@ tests = [ testGroup "inline code" , testGroup "sample with style" [ "samp should wrap highlighted code" =: codeWith ("",["sample","haskell"],[]) ">>=" - =?> ("<samp><code class=\"sourceCode haskell\">" ++ + =?> ("<samp><code class=\"sourceCode haskell\">" <> "<span class=\"op\">>>=</span></code></samp>") ] , testGroup "variable with style" [ "var should wrap highlighted code" =: codeWith ("",["haskell","variable"],[]) ">>=" - =?> ("<var><code class=\"sourceCode haskell\">" ++ + =?> ("<var><code class=\"sourceCode haskell\">" <> "<span class=\"op\">>>=</span></code></var>") ] ] where - tQ :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree + tQ :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree tQ = test htmlQTags diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs index 2f501c890..55a277c6a 100644 --- a/test/Tests/Writers/JATS.hs +++ b/test/Tests/Writers/JATS.hs @@ -31,8 +31,8 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test jats tests :: [TestTree] diff --git a/test/Tests/Writers/Jira.hs b/test/Tests/Writers/Jira.hs index 0c6f48853..58abf8bc8 100644 --- a/test/Tests/Writers/Jira.hs +++ b/test/Tests/Writers/Jira.hs @@ -13,7 +13,7 @@ jira :: (ToPandoc a) => a -> String jira = unpack . purely (writeJira def) . toPandoc infix 4 =: -(=:) :: (ToString a, ToPandoc a, HasCallStack) +(=:) :: (ToText a, ToPandoc a, HasCallStack) => String -> (a, String) -> TestTree (=:) = test jira diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs index ae5879099..1ce62487e 100644 --- a/test/Tests/Writers/LaTeX.hs +++ b/test/Tests/Writers/LaTeX.hs @@ -33,8 +33,8 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test latex tests :: [TestTree] diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs index d4f927ebe..aea920b9d 100644 --- a/test/Tests/Writers/Markdown.hs +++ b/test/Tests/Writers/Markdown.hs @@ -14,11 +14,11 @@ defopts = def { writerExtensions = pandocExtensions , writerSetextHeaders = True } -markdown :: (ToPandoc a) => a -> String -markdown = unpack . purely (writeMarkdown defopts) . toPandoc +markdown :: (ToPandoc a) => a -> Text +markdown = purely (writeMarkdown defopts) . toPandoc -markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -markdownWithOpts opts x = unpack . purely (writeMarkdown opts) $ toPandoc x +markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> Text +markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x {- "my test" =: X =?> Y @@ -33,8 +33,8 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test markdown tests :: [TestTree] @@ -182,9 +182,9 @@ noteTests = testGroup "note and reference location" shortcutLinkRefsTests :: TestTree shortcutLinkRefsTests = let infix 4 =: - (=:) :: (ToString a, ToPandoc a) + (=:) :: (ToText a, ToPandoc a) - => String -> (a, String) -> TestTree + => String -> (a, Text) -> TestTree (=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc) in testGroup "Shortcut reference links" [ "Simple link (shortcutable)" diff --git a/test/Tests/Writers/Ms.hs b/test/Tests/Writers/Ms.hs index ad6849633..ce8c712ac 100644 --- a/test/Tests/Writers/Ms.hs +++ b/test/Tests/Writers/Ms.hs @@ -7,8 +7,8 @@ import Text.Pandoc import Text.Pandoc.Builder infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test (purely (writeMs def . toPandoc)) tests :: [TestTree] diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 5bddca3af..c76574682 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -7,7 +7,7 @@ import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B defopts :: WriterOptions defopts = def{ writerWrapText = WrapPreserve, @@ -21,7 +21,7 @@ museWithOpts :: (ToPandoc a) => WriterOptions -> a -> Text museWithOpts opts = purely (writeMuse opts) . toPandoc infix 4 =: -(=:) :: (ToString a, ToPandoc a) +(=:) :: (ToText a, ToPandoc a) => String -> (a, Text) -> TestTree (=:) = test muse @@ -446,7 +446,7 @@ tests = [ testGroup "block elements" , "escape hash to avoid accidental anchors" =: text "#foo bar" =?> "<verbatim>#foo</verbatim> bar" , "escape definition list markers" =: str "::" =?> "<verbatim>::</verbatim>" - , "normalize strings before escaping" =: fromList [Str ":", Str ":"] =?> "<verbatim>::</verbatim>" + , "normalize strings before escaping" =: B.fromList [Str ":", Str ":"] =?> "<verbatim>::</verbatim>" -- We don't want colons to be escaped if they can't be confused -- with definition list item markers. , "do not escape colon" =: str ":" =?> ":" diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs index d7771ca19..b1a8882f1 100644 --- a/test/Tests/Writers/Native.hs +++ b/test/Tests/Writers/Native.hs @@ -6,14 +6,15 @@ import Test.Tasty.QuickCheck import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () +import Text.Pandoc.Shared (safeRead) p_write_rt :: Pandoc -> Bool p_write_rt d = - read (unpack $ purely (writeNative def{ writerTemplate = Just mempty }) d) == d + safeRead (purely (writeNative def{ writerTemplate = Just mempty }) d) == Just d p_write_blocks_rt :: [Block] -> Bool p_write_blocks_rt bs = - read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs + safeRead (purely (writeNative def) (Pandoc nullMeta bs)) == Just bs tests :: [TestTree] tests = [ testProperty "p_write_rt" p_write_rt diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index c1e47622d..ac74a9652 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -16,6 +16,7 @@ import Data.Maybe (catMaybes, mapMaybe) import Tests.Helpers import Data.Algorithm.Diff import System.FilePath.Glob (compile, match) +import qualified Data.Text as T compareXMLBool :: Content -> Content -> Bool -- We make a special exception for times at the moment, and just pass @@ -41,10 +42,11 @@ compareXMLBool (CRef myStr) (CRef goodStr) = myStr == goodStr compareXMLBool _ _ = False -displayDiff :: Content -> Content -> String +displayDiff :: Content -> Content -> Text displayDiff elemA elemB = - showDiff (1,1) - (getDiff (lines $ showContent elemA) (lines $ showContent elemB)) + T.pack $ showDiff (1,1) + (getDiff (lines $ T.pack $ showContent elemA) + (lines $ T.pack $ showContent elemB)) goldenArchive :: FilePath -> IO Archive goldenArchive fp = toArchive . BL.fromStrict <$> BS.readFile fp @@ -58,7 +60,7 @@ testArchive writerFn opts fp = do bs <- runIOorExplode $ readNative def txt >>= writerFn opts return $ toArchive bs -compareFileList :: FilePath -> Archive -> Archive -> Maybe String +compareFileList :: FilePath -> Archive -> Archive -> Maybe Text compareFileList goldenFP goldenArch testArch = let testFiles = filesInArchive testArch goldenFiles = filesInArchive goldenArch @@ -69,54 +71,58 @@ compareFileList goldenFP goldenArch testArch = [ if null diffGoldenTest then Nothing else Just $ - "Files in " ++ goldenFP ++ " but not in generated archive:\n" ++ - intercalate ", " diffGoldenTest + "Files in " <> T.pack goldenFP <> + " but not in generated archive:\n" <> + T.pack (intercalate ", " diffGoldenTest) , if null diffTestGolden then Nothing else Just $ - "Files in generated archive but not in " ++ goldenFP ++ ":\n" ++ - intercalate ", " diffTestGolden + "Files in generated archive but not in " <> T.pack goldenFP <> + ":\n" <> T.pack (intercalate ", " diffTestGolden) ] in if null $ catMaybes results then Nothing - else Just $ intercalate "\n" $ catMaybes results + else Just $ T.intercalate "\n" $ catMaybes results -compareXMLFile' :: FilePath -> Archive -> Archive -> Either String () +compareXMLFile' :: FilePath -> Archive -> Archive -> Either Text () compareXMLFile' fp goldenArch testArch = do testEntry <- case findEntryByPath fp testArch of Just entry -> Right entry Nothing -> Left $ - "Can't extract " ++ fp ++ " from generated archive" + "Can't extract " <> T.pack fp <> " from generated archive" testXMLDoc <- case parseXMLDoc $ fromEntry testEntry of Just doc -> Right doc Nothing -> Left $ - "Can't parse xml in " ++ fp ++ " from generated archive" + "Can't parse xml in " <> T.pack fp <> + " from generated archive" goldenEntry <- case findEntryByPath fp goldenArch of Just entry -> Right entry Nothing -> Left $ - "Can't extract " ++ fp ++ " from archive in stored file" + "Can't extract " <> T.pack fp <> + " from archive in stored file" goldenXMLDoc <- case parseXMLDoc $ fromEntry goldenEntry of Just doc -> Right doc Nothing -> Left $ - "Can't parse xml in " ++ fp ++ " from archive in stored file" + "Can't parse xml in " <> T.pack fp <> + " from archive in stored file" let testContent = Elem testXMLDoc goldenContent = Elem goldenXMLDoc if compareXMLBool goldenContent testContent then Right () - else Left $ - "Non-matching xml in " ++ fp ++ ":\n" ++ displayDiff testContent goldenContent + else Left $ "Non-matching xml in " <> T.pack fp <> ":\n" <> + displayDiff testContent goldenContent -compareXMLFile :: FilePath -> Archive -> Archive -> Maybe String +compareXMLFile :: FilePath -> Archive -> Archive -> Maybe Text compareXMLFile fp goldenArch testArch = case compareXMLFile' fp goldenArch testArch of Right _ -> Nothing Left s -> Just s -compareAllXMLFiles :: Archive -> Archive -> Maybe String +compareAllXMLFiles :: Archive -> Archive -> Maybe Text compareAllXMLFiles goldenArch testArch = let allFiles = filesInArchive goldenArch `union` filesInArchive testArch allXMLFiles = sort $ @@ -130,29 +136,30 @@ compareAllXMLFiles goldenArch testArch = then Nothing else Just $ unlines results -compareMediaFile' :: FilePath -> Archive -> Archive -> Either String () +compareMediaFile' :: FilePath -> Archive -> Archive -> Either Text () compareMediaFile' fp goldenArch testArch = do testEntry <- case findEntryByPath fp testArch of Just entry -> Right entry Nothing -> Left $ - "Can't extract " ++ fp ++ " from generated archive" + "Can't extract " <> T.pack fp <> " from generated archive" goldenEntry <- case findEntryByPath fp goldenArch of Just entry -> Right entry Nothing -> Left $ - "Can't extract " ++ fp ++ " from archive in stored file" + "Can't extract " <> T.pack fp <> + " from archive in stored file" if fromEntry testEntry == fromEntry goldenEntry then Right () else Left $ - "Non-matching binary file: " ++ fp + "Non-matching binary file: " <> T.pack fp -compareMediaFile :: FilePath -> Archive -> Archive -> Maybe String +compareMediaFile :: FilePath -> Archive -> Archive -> Maybe Text compareMediaFile fp goldenArch testArch = case compareMediaFile' fp goldenArch testArch of Right _ -> Nothing Left s -> Just s -compareAllMediaFiles :: Archive -> Archive -> Maybe String +compareAllMediaFiles :: Archive -> Archive -> Maybe Text compareAllMediaFiles goldenArch testArch = let allFiles = filesInArchive goldenArch `union` filesInArchive testArch mediaPattern = compile "*/media/*" @@ -181,5 +188,5 @@ ooxmlTest writerFn testName opts nativeFP goldenFP = , compareAllXMLFiles goldenArch testArch , compareAllMediaFiles goldenArch testArch ] - in return $ if null res then Nothing else Just $ unlines res) + in return $ if null res then Nothing else Just $ T.unpack $ unlines res) (\a -> BL.writeFile goldenFP $ fromArchive a) diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs index bd6c9b7ab..1935861ab 100644 --- a/test/Tests/Writers/Org.hs +++ b/test/Tests/Writers/Org.hs @@ -9,7 +9,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder infix 4 =: -(=:) :: (ToString a, ToPandoc a) +(=:) :: (ToText a, ToPandoc a) => String -> (a, Text) -> TestTree (=:) = test org diff --git a/test/Tests/Writers/Plain.hs b/test/Tests/Writers/Plain.hs index 17edc9dbd..f4c539805 100644 --- a/test/Tests/Writers/Plain.hs +++ b/test/Tests/Writers/Plain.hs @@ -9,8 +9,8 @@ import Text.Pandoc.Builder infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test (purely (writePlain def{ writerExtensions = enableExtension Ext_gutenberg plainExtensions }) . toPandoc) diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index 94745e9a2..64df785a8 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -12,19 +12,19 @@ import Text.Pandoc.Writers.RST import qualified Data.Text as T infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> TestTree +(=:) :: (ToText a, ToPandoc a) + => String -> (a, Text) -> TestTree (=:) = test (purely (writeRST def . toPandoc)) -testTemplate :: (ToString a, ToString c, ToPandoc a) => +testTemplate :: (ToText a, ToText c, ToPandoc a) => String -> String -> (a, c) -> TestTree testTemplate t = case runIdentity (compileTemplate [] (T.pack t)) of - Left e -> error $ "Could not compile RST template: " ++ e + Left e -> error $ T.pack $ "Could not compile RST template: " ++ e Right templ -> test (purely (writeRST def{ writerTemplate = Just templ }) . toPandoc) bodyTemplate :: Template T.Text bodyTemplate = case runIdentity (compileTemplate [] "$body$\n") of - Left e -> error $ + Left e -> error $ T.pack $ "Could not compile RST bodyTemplate" ++ e Right templ -> templ diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs index fa372909f..562b27187 100644 --- a/test/Tests/Writers/TEI.hs +++ b/test/Tests/Writers/TEI.hs @@ -20,7 +20,7 @@ which is in turn shorthand for -} infix 4 =: -(=:) :: (ToString a, ToPandoc a) +(=:) :: (ToText a, ToPandoc a) => String -> (a, String) -> TestTree (=:) = test (purely (writeTEI def) . toPandoc) |
