diff options
Diffstat (limited to 'test/Tests')
-rw-r--r-- | test/Tests/Command.hs | 3 | ||||
-rw-r--r-- | test/Tests/Helpers.hs | 2 | ||||
-rw-r--r-- | test/Tests/Lua.hs | 7 | ||||
-rw-r--r-- | test/Tests/Readers/Docx.hs | 3 | ||||
-rw-r--r-- | test/Tests/Readers/EPUB.hs | 5 | ||||
-rw-r--r-- | test/Tests/Readers/LaTeX.hs | 6 | ||||
-rw-r--r-- | test/Tests/Readers/Markdown.hs | 3 | ||||
-rw-r--r-- | test/Tests/Readers/Odt.hs | 1 | ||||
-rw-r--r-- | test/Tests/Readers/Org/Block.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Org/Block/CodeBlock.hs | 16 | ||||
-rw-r--r-- | test/Tests/Readers/Org/Shared.hs | 3 | ||||
-rw-r--r-- | test/Tests/Shared.hs | 1 | ||||
-rw-r--r-- | test/Tests/Writers/AsciiDoc.hs | 21 | ||||
-rw-r--r-- | test/Tests/Writers/ConTeXt.hs | 8 |
14 files changed, 49 insertions, 32 deletions
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs index 7c47870aa..d76cca71a 100644 --- a/test/Tests/Command.hs +++ b/test/Tests/Command.hs @@ -16,6 +16,7 @@ where import Prelude import Data.Algorithm.Diff import qualified Data.ByteString as BS +import qualified Data.Text as T import Data.List (isSuffixOf) import Prelude hiding (readFile) import System.Directory @@ -77,7 +78,7 @@ isCodeBlock (CodeBlock _ _) = True isCodeBlock _ = False extractCode :: Block -> String -extractCode (CodeBlock _ code) = code +extractCode (CodeBlock _ code) = T.unpack code extractCode _ = "" dropPercent :: String -> String diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 5ad867065..85bd518b3 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -142,7 +142,7 @@ instance ToString Blocks where toString = unpack . purely (writeNative def) . toPandoc instance ToString Inlines where - toString = trimr . unpack . purely (writeNative def) . toPandoc + toString = unpack . trimr . purely (writeNative def) . toPandoc instance ToString String where toString = id diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs index 49d54c9c8..7683df09f 100644 --- a/test/Tests/Lua.hs +++ b/test/Tests/Lua.hs @@ -33,7 +33,8 @@ import Text.Pandoc.Options (def) import Text.Pandoc.Shared (pandocVersion) import qualified Foreign.Lua as Lua -import qualified Data.ByteString.Char8 as BS +import qualified Data.Text as T +import qualified Data.Text.Encoding as TE tests :: [TestTree] tests = map (localOption (QuickCheckTests 20)) @@ -132,12 +133,12 @@ tests = map (localOption (QuickCheckTests 20)) assertFilterConversion "unexpected script name" "script-name.lua" (doc $ para "ignored") - (doc $ para (str $ "lua" </> "script-name.lua")) + (doc $ para (str $ T.pack $ "lua" </> "script-name.lua")) , testCase "Pandoc version is set" . runLuaTest $ do Lua.getglobal "PANDOC_VERSION" Lua.liftIO . - assertEqual "pandoc version is wrong" (BS.pack pandocVersion) + assertEqual "pandoc version is wrong" (TE.encodeUtf8 pandocVersion) =<< Lua.tostring' Lua.stackTop , testCase "Pandoc types version is set" . runLuaTest $ do diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index e107ff9ee..bc036e0cc 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -1,4 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Tests.Readers.Docx Copyright : © 2017-2019 Jesse Rosenthal, John MacFarlane @@ -79,7 +80,7 @@ testForWarningsWithOptsIO opts name docxFile expected = do df <- B.readFile docxFile logs <- runIOorExplode $ setVerbosity ERROR >> readDocx opts df >> P.getLog let warns = [m | DocxParserWarning m <- logs] - return $ test id name (unlines warns, unlines expected) + return $ test id name (T.unlines warns, unlines expected) testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> TestTree testForWarningsWithOpts opts name docxFile expected = diff --git a/test/Tests/Readers/EPUB.hs b/test/Tests/Readers/EPUB.hs index f917668ef..3aca6c88c 100644 --- a/test/Tests/Readers/EPUB.hs +++ b/test/Tests/Readers/EPUB.hs @@ -14,6 +14,7 @@ module Tests.Readers.EPUB (tests) where import Prelude import qualified Data.ByteString.Lazy as BL +import qualified Data.Text as T import Test.Tasty import Test.Tasty.HUnit import qualified Text.Pandoc.Class as P @@ -35,7 +36,9 @@ testMediaBag fp bag = do ++ show bag ++ "\nActual: " ++ show actBag) - (actBag == bag) + (actBag == packBag bag) + where + packBag = map $ \(x, y, z) -> (x, T.pack y, z) featuresBag :: [(String, String, Int)] featuresBag = [("img/check.gif","image/gif",1340) diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index d12eb22c9..8842bfee5 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -169,10 +169,10 @@ tests = [ testGroup "tokenization" testGroup "Character Escapes" [ "Two-character escapes" =: mconcat ["^^" <> T.pack [i,j] | i <- hex, j <- hex] =?> - para (str ['\0'..'\255']) + para (str $ T.pack ['\0'..'\255']) , "One-character escapes" =: mconcat ["^^" <> T.pack [i] | i <- hex] =?> - para (str $ ['p'..'y']++['!'..'&']) + para (str $ T.pack $ ['p'..'y']++['!'..'&']) ] , testGroup "memoir scene breaks" [ "plainbreak" =: @@ -255,7 +255,7 @@ baseCitation = Citation{ citationId = "item1" } rt :: String -> Inlines -rt = rawInline "latex" +rt = rawInline "latex" . T.pack natbibCitations :: TestTree natbibCitations = testGroup "natbib" diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index 566a42485..17b5cf800 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -53,7 +53,8 @@ autolink :: String -> Inlines autolink = autolinkWith ("",["uri"],[]) autolinkWith :: Attr -> String -> Inlines -autolinkWith attr s = linkWith attr s "" (str s) +autolinkWith attr s = linkWith attr s' "" (str s') + where s' = T.pack s bareLinkTests :: [(Text, Inlines)] bareLinkTests = diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 9dc93c92e..cecb9a353 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -1,4 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Tests.Readers.Odt Copyright : © 2015-2019 John MacFarlane diff --git a/test/Tests/Readers/Org/Block.hs b/test/Tests/Readers/Org/Block.hs index 35fd4c1fa..8cf9a0e56 100644 --- a/test/Tests/Readers/Org/Block.hs +++ b/test/Tests/Readers/Org/Block.hs @@ -179,7 +179,7 @@ tests = , "\\end{equation}" ] =?> rawBlock "latex" - (unlines [ "\\begin{equation}" + (T.unlines [ "\\begin{equation}" , "X_i = \\begin{cases}" , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <> " \\alpha(i)\\\\" diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs b/test/Tests/Readers/Org/Block/CodeBlock.hs index 7f50a1c81..01c89642e 100644 --- a/test/Tests/Readers/Org/Block/CodeBlock.hs +++ b/test/Tests/Readers/Org/Block/CodeBlock.hs @@ -80,7 +80,7 @@ tests = params = [ ("org-language", "emacs-lisp") , ("exports", "both") ] - code' = unlines [ "(progn (message \"Hello, World!\")" + code' = T.unlines [ "(progn (message \"Hello, World!\")" , " (+ 23 42))" ] in codeBlockWith ("", classes, params) code' @@ -96,8 +96,8 @@ tests = params = [ ("org-language", "emacs-lisp") , ("exports", "both") ] - code' = unlines [ "(progn (message \"Hello, World!\")" - , " (+ 23 42))" ] + code' = T.unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] results' = "65\n" in codeBlockWith ("", classes, params) code' <> @@ -115,8 +115,8 @@ tests = params = [ ("org-language", "emacs-lisp") , ("exports", "code") ] - code' = unlines [ "(progn (message \"Hello, World!\")" - , " (+ 23 42))" ] + code' = T.unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] in codeBlockWith ("", classes, params) code' , "Source block with results and :exports results" =: @@ -190,9 +190,9 @@ tests = (plain $ spanWith ("", ["label"], []) (spcSep [ "Functor", "laws", "in", "Haskell" ])) (codeBlockWith ("functor-laws", ["haskell"], []) - (unlines [ "fmap id = id" - , "fmap (p . q) = (fmap p) . (fmap q)" - ]))) + (T.unlines [ "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + ]))) , "Non-letter chars in source block parameters" =: T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" diff --git a/test/Tests/Readers/Org/Shared.hs b/test/Tests/Readers/Org/Shared.hs index f26442621..aa253aa36 100644 --- a/test/Tests/Readers/Org/Shared.hs +++ b/test/Tests/Readers/Org/Shared.hs @@ -1,4 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Tests.Readers.Org.Shared Copyright : © 2014-2019 Albert Krewinkel @@ -38,5 +39,5 @@ spcSep :: [Inlines] -> Inlines spcSep = mconcat . intersperse space -- | Create a span for the given tag. -tagSpan :: String -> Inlines +tagSpan :: Text -> Inlines tagSpan t = spanWith ("", ["tag"], [("tag-name", t)]) . smallcaps $ str t diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs index 2a699623c..788dab257 100644 --- a/test/Tests/Shared.hs +++ b/test/Tests/Shared.hs @@ -1,4 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Tests.Shared Copyright : © 2006-2019 John MacFarlane diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs index ea61ed044..75f6e5e97 100644 --- a/test/Tests/Writers/AsciiDoc.hs +++ b/test/Tests/Writers/AsciiDoc.hs @@ -1,4 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} module Tests.Writers.AsciiDoc (tests) where import Prelude @@ -12,29 +13,35 @@ import Text.Pandoc.Builder asciidoc :: (ToPandoc a) => a -> String asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc +testAsciidoc :: (ToString a, ToPandoc a) + => String + -> (a, String) + -> TestTree +testAsciidoc = test asciidoc + tests :: [TestTree] tests = [ testGroup "emphasis" - [ test asciidoc "emph word before" $ + [ testAsciidoc "emph word before" $ para (text "foo" <> emph (text "bar")) =?> "foo__bar__" - , test asciidoc "emph word after" $ + , testAsciidoc "emph word after" $ para (emph (text "foo") <> text "bar") =?> "__foo__bar" - , test asciidoc "emph quoted" $ + , testAsciidoc "emph quoted" $ para (doubleQuoted (emph (text "foo"))) =?> "``__foo__''" - , test asciidoc "strong word before" $ + , testAsciidoc "strong word before" $ para (text "foo" <> strong (text "bar")) =?> "foo**bar**" - , test asciidoc "strong word after" $ + , testAsciidoc "strong word after" $ para (strong (text "foo") <> text "bar") =?> "**foo**bar" - , test asciidoc "strong quoted" $ + , testAsciidoc "strong quoted" $ para (singleQuoted (strong (text "foo"))) =?> "`**foo**'" ] , testGroup "tables" - [ test asciidoc "empty cells" $ + [ testAsciidoc "empty cells" $ simpleTable [] [[mempty],[mempty]] =?> unlines [ "[cols=\"\",]" , "|===" diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index c11e409f8..082ff12fe 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -3,7 +3,7 @@ module Tests.Writers.ConTeXt (tests) where import Prelude -import Data.Text (unpack) +import Data.Text (unpack, pack) import Test.Tasty import Test.Tasty.QuickCheck import Tests.Helpers @@ -46,9 +46,9 @@ tests = [ testGroup "inline code" , "without '}'" =: code "]" =?> "\\type{]}" , testProperty "code property" $ \s -> null s || '\n' `elem` s || if '{' `elem` s || '}' `elem` s - then context' (code s) == "\\mono{" ++ - context' (str s) ++ "}" - else context' (code s) == "\\type{" ++ s ++ "}" + then context' (code $ pack s) == "\\mono{" ++ + context' (str $ pack s) ++ "}" + else context' (code $ pack s) == "\\type{" ++ s ++ "}" ] , testGroup "headers" [ "level 1" =: |