aboutsummaryrefslogtreecommitdiff
path: root/test/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests')
-rw-r--r--test/Tests/Command.hs32
-rw-r--r--test/Tests/Helpers.hs87
-rw-r--r--test/Tests/Lua.hs2
-rw-r--r--test/Tests/Old.hs33
-rw-r--r--test/Tests/Readers/Creole.hs2
-rw-r--r--test/Tests/Readers/Docx.hs14
-rw-r--r--test/Tests/Readers/DokuWiki.hs4
-rw-r--r--test/Tests/Readers/FB2.hs4
-rw-r--r--test/Tests/Readers/HTML.hs4
-rw-r--r--test/Tests/Readers/Jira.hs2
-rw-r--r--test/Tests/Readers/LaTeX.hs16
-rw-r--r--test/Tests/Readers/Man.hs4
-rw-r--r--test/Tests/Readers/Markdown.hs11
-rw-r--r--test/Tests/Readers/Muse.hs25
-rw-r--r--test/Tests/Readers/Odt.hs10
-rw-r--r--test/Tests/Readers/Org/Directive.hs4
-rw-r--r--test/Tests/Readers/Org/Inline/Citation.hs14
-rw-r--r--test/Tests/Readers/Org/Meta.hs18
-rw-r--r--test/Tests/Readers/Org/Shared.hs2
-rw-r--r--test/Tests/Readers/RST.hs2
-rw-r--r--test/Tests/Readers/Txt2Tags.hs2
-rw-r--r--test/Tests/Shared.hs4
-rw-r--r--test/Tests/Writers/AnnotatedTable.hs4
-rw-r--r--test/Tests/Writers/AsciiDoc.hs4
-rw-r--r--test/Tests/Writers/ConTeXt.hs4
-rw-r--r--test/Tests/Writers/Docbook.hs15
-rw-r--r--test/Tests/Writers/FB2.hs10
-rw-r--r--test/Tests/Writers/HTML.hs12
-rw-r--r--test/Tests/Writers/JATS.hs4
-rw-r--r--test/Tests/Writers/Jira.hs2
-rw-r--r--test/Tests/Writers/LaTeX.hs4
-rw-r--r--test/Tests/Writers/Markdown.hs16
-rw-r--r--test/Tests/Writers/Ms.hs4
-rw-r--r--test/Tests/Writers/Muse.hs6
-rw-r--r--test/Tests/Writers/Native.hs5
-rw-r--r--test/Tests/Writers/OOXML.hs57
-rw-r--r--test/Tests/Writers/Org.hs2
-rw-r--r--test/Tests/Writers/Plain.hs4
-rw-r--r--test/Tests/Writers/RST.hs10
-rw-r--r--test/Tests/Writers/TEI.hs2
40 files changed, 237 insertions, 224 deletions
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs
index 59b04eac1..e3d9b636a 100644
--- a/test/Tests/Command.hs
+++ b/test/Tests/Command.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Command
Copyright : © 2006-2021 John MacFarlane
@@ -35,8 +36,8 @@ import qualified Text.Pandoc.UTF8 as UTF8
-- | Run a test with and return output.
execTest :: String -- ^ Path to test executable
-> String -- ^ Shell command
- -> String -- ^ Input text
- -> IO (ExitCode, String) -- ^ Exit code and actual output
+ -> Text -- ^ Input text
+ -> IO (ExitCode, Text) -- ^ Exit code and actual output
execTest testExePath cmd inp = do
mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
@@ -48,9 +49,9 @@ execTest testExePath cmd inp = do
maybe [] ((:[]) . ("LD_LIBRARY_PATH",)) mldpath ++
maybe [] ((:[]) . ("DYLD_LIBRARY_PATH",)) mdyldpath
let pr = (shell (pandocToEmulate True cmd)){ env = Just env' }
- (ec, out', err') <- readCreateProcessWithExitCode pr inp
+ (ec, out', err') <- readCreateProcessWithExitCode pr (T.unpack inp)
-- filter \r so the tests will work on Windows machines
- let out = filter (/= '\r') $ err' ++ out'
+ let out = T.pack $ filter (/= '\r') $ err' ++ out'
case ec of
ExitFailure _ -> hPutStr stderr err'
ExitSuccess -> return ()
@@ -68,8 +69,8 @@ pandocToEmulate _ [] = []
runTest :: String -- ^ Path to test executable
-> String -- ^ Title of test
-> String -- ^ Shell command
- -> String -- ^ Input text
- -> String -- ^ Expected output
+ -> Text -- ^ Input text
+ -> Text -- ^ Expected output
-> TestTree
runTest testExePath testname cmd inp norm = testCase testname $ do
(ec, out) <- execTest testExePath cmd inp
@@ -96,22 +97,23 @@ isCodeBlock :: Block -> Bool
isCodeBlock (CodeBlock _ _) = True
isCodeBlock _ = False
-extractCode :: Block -> String
-extractCode (CodeBlock _ code) = T.unpack code
+extractCode :: Block -> Text
+extractCode (CodeBlock _ code) = code
extractCode _ = ""
dropPercent :: String -> String
dropPercent ('%':xs) = dropWhile (== ' ') xs
dropPercent xs = xs
-runCommandTest :: FilePath -> FilePath -> Int -> String -> TestTree
+runCommandTest :: FilePath -> FilePath -> Int -> Text -> TestTree
runCommandTest testExePath fp num code =
goldenTest testname getExpected getActual compareValues updateGolden
where
testname = "#" <> show num
codelines = lines code
- (continuations, r1) = span ("\\" `isSuffixOf`) codelines
- cmd = dropPercent (unwords (map init continuations ++ take 1 r1))
+ (continuations, r1) = span ("\\" `T.isSuffixOf`) codelines
+ cmd = dropPercent $ T.unpack $ T.unwords $
+ map (T.dropEnd 1) continuations ++ take 1 r1
r2 = drop 1 r1
(inplines, r3) = break (=="^D") r2
normlines = takeWhile (/=".") (drop 1 r3)
@@ -123,14 +125,16 @@ runCommandTest testExePath fp num code =
| actual == expected = return Nothing
| otherwise = return $ Just $ "--- test/command/" ++ fp ++ "\n+++ " ++
cmd ++ "\n" ++ showDiff (1,1)
- (getDiff (lines actual) (lines expected))
+ (getDiff
+ (lines actual)
+ (lines expected))
updateGolden newnorm = do
let fp' = "command" </> fp
raw <- UTF8.readFile fp'
- let cmdline = "% " <> cmd
+ let cmdline = "% " <> T.pack cmd
let x = cmdline <> "\n" <> input <> "^D\n" <> norm
let y = cmdline <> "\n" <> input <> "^D\n" <> newnorm
- let updated = T.replace (T.pack x) (T.pack y) raw
+ let updated = T.replace x y raw
UTF8.writeFile fp' updated
extractCommandTest :: FilePath -> FilePath -> TestTree
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs
index 64c2785ed..c8957a050 100644
--- a/test/Tests/Helpers.hs
+++ b/test/Tests/Helpers.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Helpers
Copyright : © 2006-2021 John MacFarlane
@@ -17,73 +18,77 @@ module Tests.Helpers ( test
, (=?>)
, purely
, ToString(..)
+ , ToText(..)
, ToPandoc(..)
)
where
import Data.Algorithm.Diff
import qualified Data.Map as M
-import Data.Text (Text, unpack)
+import qualified Data.Text as T
import System.Exit
import Test.Tasty
import Test.Tasty.HUnit
-import Text.Pandoc.Builder (Blocks, Inlines, doc, plain)
+import Text.Pandoc.Builder (Blocks, Inlines, doc, plain, nullMeta)
import Text.Pandoc.Class
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared (trimr)
import Text.Pandoc.Writers.Native (writeNative)
import Text.Printf
+import qualified GHC.Show
+import Prelude hiding (First)
-test :: (ToString a, ToString b, ToString c, HasCallStack)
+test :: (ToText a, ToText b, ToText c, HasCallStack)
=> (a -> b) -- ^ function to test
-> String -- ^ name of test case
-> (a, c) -- ^ (input, expected value)
-> TestTree
test fn name (input, expected) =
- testCase name' $ assertBool msg (actual' == expected')
- where msg = nl ++ dashes "input" ++ nl ++ input' ++ nl ++
- dashes "result" ++ nl ++
- unlines (map vividize diff) ++
+ testCase name' $ assertBool (T.unpack msg) (actual' == expected')
+ where msg = nl <> dashes "input" <> nl <> input' <> nl <>
+ dashes "result" <> nl <>
+ T.unlines (map vividize diff) <>
dashes ""
nl = "\n"
name' = if length name > 54
- then take 52 name ++ "..." -- avoid wide output
+ then Prelude.take 52 name ++ "..." -- avoid wide output
else name
- input' = toString input
- actual' = lines $ toString $ fn input
- expected' = lines $ toString expected
+ input' = toText input
+ actual' = T.lines $ toText $ fn input
+ expected' = T.lines $ toText expected
diff = getDiff expected' actual'
- dashes "" = replicate 72 '-'
- dashes x = replicate (72 - length x - 5) '-' ++ " " ++ x ++ " ---"
+ dashes "" = T.replicate 72 "-"
+ dashes x = T.replicate (72 - T.length x - 5) "-" <>
+ " " <> x <> " ---"
data TestResult = TestPassed
| TestError ExitCode
- | TestFailed String FilePath [Diff String]
+ | TestFailed String FilePath [Diff Text]
deriving (Eq)
instance Show TestResult where
show TestPassed = "PASSED"
- show (TestError ec) = "ERROR " ++ show ec
- show (TestFailed cmd file d) = '\n' : dash ++
- "\n--- " ++ file ++
- "\n+++ " ++ cmd ++ "\n" ++ showDiff (1,1) d ++
- dash
+ show (TestError ec) = "ERROR " <> show ec
+ show (TestFailed cmd file d) = "\n" <> dash <>
+ "\n--- " <> file <>
+ "\n+++ " <> cmd <> "\n" <>
+ showDiff (1,1) d <> dash
where dash = replicate 72 '-'
-showDiff :: (Int,Int) -> [Diff String] -> String
+showDiff :: ToString a => (Int,Int) -> [Diff a] -> String
showDiff _ [] = ""
showDiff (l,r) (First ln : ds) =
- printf "+%4d " l ++ ln ++ "\n" ++ showDiff (l+1,r) ds
+ printf "+%4d " l <> toString ln <> "\n" <> showDiff (l+1,r) ds
showDiff (l,r) (Second ln : ds) =
- printf "-%4d " r ++ ln ++ "\n" ++ showDiff (l,r+1) ds
+ printf "-%4d " r <> toString ln <> "\n" <> showDiff (l,r+1) ds
showDiff (l,r) (Both _ _ : ds) =
showDiff (l+1,r+1) ds
-vividize :: Diff String -> String
-vividize (Both s _) = " " ++ s
-vividize (First s) = "- " ++ s
-vividize (Second s) = "+ " ++ s
+vividize :: Diff Text -> Text
+vividize (Both s _) = " " <> s
+vividize (First s) = "- " <> s
+vividize (Second s) = "+ " <> s
purely :: (b -> PandocPure a) -> b -> a
purely f = either (error . show) id . runPure . f
@@ -92,28 +97,28 @@ infix 5 =?>
(=?>) :: a -> b -> (a,b)
x =?> y = (x, y)
-class ToString a where
- toString :: a -> String
-
instance ToString Pandoc where
- toString d = unpack $
- purely (writeNative def{ writerTemplate = s }) $ toPandoc d
- where s = case d of
- (Pandoc (Meta m) _)
- | M.null m -> Nothing
- | otherwise -> Just mempty -- need this to get meta output
+ toString = T.unpack . toText
instance ToString Blocks where
- toString = unpack . purely (writeNative def) . toPandoc
+ toString = T.unpack . toText
instance ToString Inlines where
- toString = unpack . trimr . purely (writeNative def) . toPandoc
+ toString = T.unpack . toText
+
+instance ToText Pandoc where
+ toText d@(Pandoc (Meta m) _)
+ | M.null m
+ = purely (writeNative def) $ toPandoc d
+ toText d@(Pandoc m _)
+ = purely (writeNative def{ writerTemplate = Just mempty }) $ toPandoc d
+ -- need this to get meta output
-instance ToString String where
- toString = id
+instance ToText Blocks where
+ toText = purely (writeNative def) . toPandoc
-instance ToString Text where
- toString = unpack
+instance ToText Inlines where
+ toText = T.stripEnd . purely (writeNative def) . toPandoc
class ToPandoc a where
toPandoc :: a -> Pandoc
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 31c011900..35be57da7 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -230,7 +230,7 @@ roundtripEqual x = (x ==) <$> roundtripped
Lua.push x
size <- Lua.gettop
when (size - oldSize /= 1) $
- error ("not exactly one additional element on the stack: " ++ show size)
+ error ("not exactly one additional element on the stack: " <> show size)
Lua.peek (-1)
runLuaTest :: Lua.Lua a -> IO a
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 160086be2..fefe36795 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Old
Copyright : © 2006-2021 John MacFarlane
@@ -229,10 +230,6 @@ tests pandocPath =
lhsReaderTest' = lhsReaderTest pandocPath
extWriterTests' = extendedWriterTests pandocPath
--- makes sure file is fully closed after reading
-readFile' :: FilePath -> IO String
-readFile' f = do s <- UTF8.readFile f
- return $! (T.length s `seq` T.unpack s)
lhsWriterTests :: FilePath -> String -> [TestTree]
lhsWriterTests pandocPath format
@@ -289,13 +286,9 @@ fb2WriterTest pandocPath title opts inputfile normfile =
testWithNormalize (ignoreBinary . formatXML) pandocPath
title (["-t", "fb2"]++opts) inputfile normfile
where
- formatXML xml = splitTags $ zip xml (drop 1 xml)
- splitTags [] = []
- splitTags [end] = [fst end, snd end]
- splitTags (('>','<'):rest) = ">\n" ++ splitTags rest
- splitTags ((c,_):rest) = c : splitTags rest
+ formatXML = T.replace "><" ">\n<"
ignoreBinary = unlines . filter (not . startsWith "<binary ") . lines
- startsWith tag str = all (uncurry (==)) $ zip tag str
+ startsWith tag str = tag `T.isPrefixOf` str
-- | Run a test without normalize function, return True if test passed.
test :: FilePath -- ^ Path of pandoc executable
@@ -307,7 +300,7 @@ test :: FilePath -- ^ Path of pandoc executable
test = testWithNormalize id
-- | Run a test with normalize function, return True if test passed.
-testWithNormalize :: (String -> String) -- ^ Normalize function for output
+testWithNormalize :: (Text -> Text) -- ^ Normalize function for output
-> FilePath -- ^ Path to pandoc executable
-> String -- ^ Title of test
-> [String] -- ^ Options to pass to pandoc
@@ -317,7 +310,7 @@ testWithNormalize :: (String -> String) -- ^ Normalize function for output
testWithNormalize normalizer pandocPath testname opts inp norm =
goldenTest testname getExpected getActual
(compareValues norm options) updateGolden
- where getExpected = normalizer <$> readFile' norm
+ where getExpected = normalizer <$> UTF8.readFile norm
getActual = do
mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
@@ -330,23 +323,23 @@ testWithNormalize normalizer pandocPath testname opts inp norm =
(ec, out) <- pipeProcess (Just env) pandocPath
("--emulate":options) mempty
if ec == ExitSuccess
- then return $ filter (/='\r') . normalizer
+ then return $ normalizer $ T.pack $ filter (/='\r')
$ UTF8.toStringLazy out
-- filter \r so the tests will work on Windows machines
else fail $ "Pandoc failed with error code " ++ show ec
- updateGolden = UTF8.writeFile norm . T.pack
+ updateGolden = UTF8.writeFile norm
options = ["--data-dir=../data","--quiet"] ++ [inp] ++ opts
-compareValues :: FilePath -> [String] -> String -> String -> IO (Maybe String)
+compareValues :: FilePath -> [String] -> Text -> Text -> IO (Maybe String)
compareValues norm options expected actual = do
testExePath <- getExecutablePath
- let cmd = testExePath ++ " --emulate " ++ unwords options
+ let cmd = testExePath ++ " --emulate " ++ intercalate " " options
let dash = replicate 72 '-'
let diff = getDiff (lines actual) (lines expected)
if expected == actual
then return Nothing
else return $ Just $
- '\n' : dash ++
- "\n--- " ++ norm ++
- "\n+++ " ++ cmd ++ "\n" ++
- showDiff (1,1) diff ++ dash
+ "\n" <> dash <>
+ "\n--- " <> norm <>
+ "\n<>+ " <> cmd <> "\n" <>
+ showDiff (1,1) diff <> dash
diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs
index 3320b78e8..582df693b 100644
--- a/test/Tests/Readers/Creole.hs
+++ b/test/Tests/Readers/Creole.hs
@@ -25,7 +25,7 @@ creole :: Text -> Pandoc
creole = purely $ readCreole def{ readerStandalone = True }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test creole
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 263e04173..59bac0213 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -40,8 +40,8 @@ noNorm = NoNormPandoc
defopts :: ReaderOptions
defopts = def{ readerExtensions = getDefaultExtensions "docx" }
-instance ToString NoNormPandoc where
- toString d = T.unpack $ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+instance ToText NoNormPandoc where
+ toText d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> Nothing
@@ -73,14 +73,14 @@ testCompareWithOpts opts name docxFile nativeFile =
testCompare :: String -> FilePath -> FilePath -> TestTree
testCompare = testCompareWithOpts defopts
-testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO TestTree
+testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [Text] -> IO TestTree
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 (T.unlines warns, unlines expected)
+ return $ test id name (T.unlines warns, T.unlines expected)
-testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> TestTree
+testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [Text] -> TestTree
testForWarningsWithOpts opts name docxFile expected =
unsafePerformIO $ testForWarningsWithOptsIO opts name docxFile expected
@@ -96,10 +96,10 @@ compareMediaPathIO mediaPath mediaBag docxPath = do
docxMedia <- getMedia docxPath mediaPath
let mbBS = case lookupMedia mediaPath mediaBag of
Just (_, bs) -> bs
- Nothing -> error ("couldn't find " ++
+ Nothing -> error $ T.pack ("couldn't find " ++
mediaPath ++
" in media bag")
- docxBS = fromMaybe (error ("couldn't find " ++
+ docxBS = fromMaybe (error $ T.pack ("couldn't find " ++
mediaPath ++
" in media bag")) docxMedia
return $ mbBS == docxBS
diff --git a/test/Tests/Readers/DokuWiki.hs b/test/Tests/Readers/DokuWiki.hs
index 84ba86d46..fa344b910 100644
--- a/test/Tests/Readers/DokuWiki.hs
+++ b/test/Tests/Readers/DokuWiki.hs
@@ -19,13 +19,13 @@ import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
dokuwiki :: Text -> Pandoc
dokuwiki = purely $ readDokuWiki def{ readerStandalone = True }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test dokuwiki
diff --git a/test/Tests/Readers/FB2.hs b/test/Tests/Readers/FB2.hs
index 42054a235..ac7db9be1 100644
--- a/test/Tests/Readers/FB2.hs
+++ b/test/Tests/Readers/FB2.hs
@@ -16,7 +16,7 @@ import Tests.Helpers
import Test.Tasty.Golden (goldenVsString)
import qualified Data.ByteString as BS
import Text.Pandoc
-import Text.Pandoc.UTF8 (toText, fromStringLazy)
+import Text.Pandoc.UTF8 as UTF8
import Data.Text (Text, unpack)
import System.FilePath (replaceExtension)
@@ -25,7 +25,7 @@ fb2ToNative = purely (writeNative def{ writerTemplate = Just mempty }) . purely
fb2Test :: TestName -> FilePath -> TestTree
fb2Test name path = goldenVsString name native
- (fromStringLazy . filter (/='\r') . unpack . fb2ToNative . toText
+ (UTF8.fromStringLazy . filter (/='\r') . unpack . fb2ToNative . UTF8.toText
<$> BS.readFile path)
where native = replaceExtension path ".native"
diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs
index f23af2cb1..6a8a10cef 100644
--- a/test/Tests/Readers/HTML.hs
+++ b/test/Tests/Readers/HTML.hs
@@ -21,7 +21,7 @@ import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Shared (isHeaderBlock)
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
import Text.Pandoc.Walk (walk)
html :: Text -> Pandoc
@@ -47,7 +47,7 @@ removeRawInlines x = x
roundTrip :: Blocks -> Bool
roundTrip b = d'' == d'''
where d = walk removeRawInlines $
- walk makeRoundTrip $ Pandoc nullMeta $ toList b
+ walk makeRoundTrip $ Pandoc nullMeta $ B.toList b
d' = rewrite d
d'' = rewrite d'
d''' = rewrite d''
diff --git a/test/Tests/Readers/Jira.hs b/test/Tests/Readers/Jira.hs
index cb7dde4ea..2881a83e5 100644
--- a/test/Tests/Readers/Jira.hs
+++ b/test/Tests/Readers/Jira.hs
@@ -25,7 +25,7 @@ jira :: Text -> Pandoc
jira = purely $ readJira def
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test jira
diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs
index 4bda15140..a631e55af 100644
--- a/test/Tests/Readers/LaTeX.hs
+++ b/test/Tests/Readers/LaTeX.hs
@@ -18,14 +18,14 @@ import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
latex :: Text -> Pandoc
latex = purely $ readLaTeX def{
readerExtensions = getDefaultExtensions "latex" }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test latex
@@ -338,10 +338,10 @@ natbibCitations = testGroup "natbib"
=?> para (cite [baseCitation] (rt "\\citet{item1}"))
, "suffix" =: "\\citet[p.~30]{item1}"
=?> para
- (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\citet[p.~30]{item1}"))
+ (cite [baseCitation{ citationSuffix = B.toList $ text "p.\160\&30" }] (rt "\\citet[p.~30]{item1}"))
, "suffix long" =: "\\citet[p.~30, with suffix]{item1}"
=?> para (cite [baseCitation{ citationSuffix =
- toList $ text "p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}"))
+ B.toList $ text "p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}"))
, "multiple" =: "\\citeauthor{item1} \\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}"
=?> para (cite [baseCitation{ citationMode = AuthorInText }
,baseCitation{ citationMode = SuppressAuthor
@@ -365,7 +365,7 @@ natbibCitations = testGroup "natbib"
, citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\citep[pp.~33, 35--37, and nowhere else]{item1}"))
, "suffix only" =: "\\citep[and nowhere else]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
- , citationSuffix = toList $ text "and nowhere else" }] (rt "\\citep[and nowhere else]{item1}"))
+ , citationSuffix = B.toList $ text "and nowhere else" }] (rt "\\citep[and nowhere else]{item1}"))
, "no author" =: "\\citeyearpar{item1}, and now Doe with a locator \\citeyearpar[p.~44]{item2}"
=?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\citeyearpar{item1}") <>
text ", and now Doe with a locator " <>
@@ -385,10 +385,10 @@ biblatexCitations = testGroup "biblatex"
=?> para (cite [baseCitation] (rt "\\textcite{item1}"))
, "suffix" =: "\\textcite[p.~30]{item1}"
=?> para
- (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\textcite[p.~30]{item1}"))
+ (cite [baseCitation{ citationSuffix = B.toList $ text "p.\160\&30" }] (rt "\\textcite[p.~30]{item1}"))
, "suffix long" =: "\\textcite[p.~30, with suffix]{item1}"
=?> para (cite [baseCitation{ citationSuffix =
- toList $ text "p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}"))
+ B.toList $ text "p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}"))
, "multiple" =: "\\textcites{item1}[p.~30]{item2}[see also][]{item3}"
=?> para (cite [baseCitation{ citationMode = AuthorInText }
,baseCitation{ citationMode = NormalCitation
@@ -412,7 +412,7 @@ biblatexCitations = testGroup "biblatex"
, citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\autocite[pp.~33, 35--37, and nowhere else]{item1}"))
, "suffix only" =: "\\autocite[and nowhere else]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
- , citationSuffix = toList $ text "and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}"))
+ , citationSuffix = B.toList $ text "and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}"))
, "no author" =: "\\autocite*{item1}, and now Doe with a locator \\autocite*[p.~44]{item2}"
=?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\autocite*{item1}") <>
text ", and now Doe with a locator " <>
diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs
index d36151d58..ff1f14a29 100644
--- a/test/Tests/Readers/Man.hs
+++ b/test/Tests/Readers/Man.hs
@@ -18,14 +18,14 @@ import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
import Text.Pandoc.Readers.Man
man :: Text -> Pandoc
man = purely $ readMan def
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test man
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index 0930deae6..8e6700639 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -19,6 +19,7 @@ import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import qualified Relude.Unsafe as Unsafe
markdown :: Text -> Pandoc
markdown = purely $ readMarkdown def { readerExtensions =
@@ -37,7 +38,7 @@ markdownGH = purely $ readMarkdown def {
readerExtensions = githubMarkdownExtensions }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test markdown
@@ -205,15 +206,15 @@ tests = [ testGroup "inline code"
]
<> [ "lists with newlines and indent in backticks" =:
T.intercalate ("\n" <> T.replicate 4 " ") (zipWith (\i (_, lt, _) -> lt <> i) lis lsts)
- =?> let (_, _, f) = head lsts
- in f [plain $ code $ T.intercalate (T.replicate 5 " ") $ head lis' : zipWith (\i (_, lt, _) -> lt <> i) (tail lis') (tail lsts)]
+ =?> let (_, _, f) = Unsafe.head lsts
+ in f [plain $ code $ T.intercalate (T.replicate 5 " ") $ Unsafe.head lis' : zipWith (\i (_, lt, _) -> lt <> i) (Unsafe.tail lis') (Unsafe.tail lsts)]
| lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists]
]
<> [ "lists with blank lines and indent in backticks" =:
T.intercalate ("\n\n" <> T.replicate 4 " ") (zipWith (\i (_, lt, _) -> lt <> i) lis lsts)
<> "\n"
- =?> let (_, _, f) = head lsts
- in f . pure $ (para . text $ head lis) <> bldLsts para (tail lsts) (tail lis)
+ =?> let (_, _, f) = Unsafe.head lsts
+ in f . pure $ (para . text $ Unsafe.head lis) <> bldLsts para (Unsafe.tail lsts) (Unsafe.tail lis)
| lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists]
]
, testGroup "emph and strong"
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index 68bdc87b4..6304a0dd8 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -22,7 +22,7 @@ import Test.Tasty.Options (IsOption(defaultValue))
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
import Text.Pandoc.Writers.Shared (toLegacyTable)
import Text.Pandoc.Walk
@@ -33,7 +33,7 @@ emacsMuse :: Text -> Pandoc
emacsMuse = purely $ readMuse def { readerExtensions = emptyExtensions }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test amuse
@@ -59,7 +59,8 @@ makeRoundTrip t@(Table tattr blkCapt specs thead tbody tfoot) =
then t
else Para [Str "table was here"]
where (_, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
- numcols = maximum (length aligns : length widths : map length (headers:rows))
+ numcols = maximum1
+ (length aligns :| length widths : map length (headers:rows))
isLineBreak LineBreak = Any True
isLineBreak _ = Any False
hasLineBreak = getAny . query isLineBreak
@@ -107,7 +108,7 @@ makeRoundTrip x = x
-- Currently we remove tables and compare first rewrite to the second.
roundTrip :: Blocks -> Bool
roundTrip b = d' == d''
- where d = walk makeRoundTrip $ Pandoc nullMeta $ toList b
+ where d = walk makeRoundTrip $ Pandoc nullMeta $ B.toList b
d' = rewrite d
d'' = rewrite d'
rewrite = amuse . T.pack . (++ "\n") . T.unpack .
@@ -801,7 +802,7 @@ tests =
, testGroup "Directives"
[ "Title" =:
"#title Document title" =?>
- let titleInline = toList "Document title"
+ let titleInline = B.toList "Document title"
meta = setMeta "title" (MetaInlines titleInline) nullMeta
in Pandoc meta mempty
-- Emacs Muse documentation says that "You can use any combination
@@ -809,25 +810,25 @@ tests =
-- but also allows '-', which is not documented, but used for disable-tables.
, test emacsMuse "Disable tables"
("#disable-tables t" =?>
- Pandoc (setMeta "disable-tables" (MetaInlines $ toList "t") nullMeta) mempty)
+ Pandoc (setMeta "disable-tables" (MetaInlines $ B.toList "t") nullMeta) mempty)
, "Multiple directives" =:
T.unlines [ "#title Document title"
, "#subtitle Document subtitle"
] =?>
- Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $
- setMeta "subtitle" (MetaInlines $ toList "Document subtitle") nullMeta) mempty
+ Pandoc (setMeta "title" (MetaInlines $ B.toList "Document title") $
+ setMeta "subtitle" (MetaInlines $ B.toList "Document subtitle") nullMeta) mempty
, "Multiline directive" =:
T.unlines [ "#title Document title"
, "#notes First line"
, "and second line"
, "#author Name"
] =?>
- Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $
- setMeta "notes" (MetaInlines $ toList "First line\nand second line") $
- setMeta "author" (MetaInlines $ toList "Name") nullMeta) mempty
+ Pandoc (setMeta "title" (MetaInlines $ B.toList "Document title") $
+ setMeta "notes" (MetaInlines $ B.toList "First line\nand second line") $
+ setMeta "author" (MetaInlines $ B.toList "Name") nullMeta) mempty
, "Amusewiki's #cover is translated to pandoc's #cover-image" =:
"#cover cover.png" =?>
- let titleInline = toList "cover.png"
+ let titleInline = B.toList "cover.png"
meta = setMeta "cover-image" (MetaInlines titleInline) nullMeta
in Pandoc meta mempty
]
diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs
index 9b5ec6b9e..f1155d23e 100644
--- a/test/Tests/Readers/Odt.hs
+++ b/test/Tests/Readers/Odt.hs
@@ -17,7 +17,7 @@ import Control.Monad (liftM)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
import qualified Data.Map as M
-import Data.Text (unpack)
+import qualified Data.Text as T
import System.IO.Unsafe (unsafePerformIO)
import Test.Tasty
import Tests.Helpers
@@ -54,9 +54,8 @@ testsComparingToNative = map nameToTest namesOfTestsComparingToNative
newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
deriving ( Show )
-instance ToString NoNormPandoc where
- toString d = unpack $
- purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+instance ToText NoNormPandoc where
+ toText d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> Nothing
@@ -66,7 +65,8 @@ instance ToPandoc NoNormPandoc where
toPandoc = unNoNorm
getNoNormVia :: (a -> Pandoc) -> String -> Either PandocError a -> NoNormPandoc
-getNoNormVia _ readerName (Left _) = error (readerName ++ " reader failed")
+getNoNormVia _ readerName (Left _) =
+ error $ T.pack (readerName ++ " reader failed")
getNoNormVia f _ (Right a) = NoNormPandoc (f a)
type TestCreator = ReaderOptions
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index 85d1bc088..c2409ce80 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -15,14 +15,14 @@ module Tests.Readers.Org.Directive (tests) where
import Data.Time (UTCTime (UTCTime), secondsToDiffTime)
import Data.Time.Calendar (Day (ModifiedJulianDay))
import Test.Tasty (TestTree, testGroup)
-import Tests.Helpers ((=?>), ToString, purely, test)
+import Tests.Helpers ((=?>), ToString, ToText, purely, test)
import Tests.Readers.Org.Shared ((=:), tagSpan)
import Text.Pandoc
import Text.Pandoc.Builder
import qualified Data.ByteString as BS
import qualified Data.Text as T
-testWithFiles :: (ToString c)
+testWithFiles :: (ToText c)
=> [(FilePath, BS.ByteString)]
-> String -- ^ name of test case
-> (T.Text, c) -- ^ (input, expected value)
diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs
index a11804983..fa1560772 100644
--- a/test/Tests/Readers/Org/Inline/Citation.hs
+++ b/test/Tests/Readers/Org/Inline/Citation.hs
@@ -15,7 +15,7 @@ module Tests.Readers.Org.Inline.Citation (tests) where
import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:))
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
tests :: [TestTree]
tests =
@@ -160,8 +160,8 @@ tests =
"[[citep:Dominik201408][See page 20::, for example]]" =?>
let citation = Citation
{ citationId = "Dominik201408"
- , citationPrefix = toList "See page 20"
- , citationSuffix = toList ", for example"
+ , citationPrefix = B.toList "See page 20"
+ , citationSuffix = B.toList ", for example"
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
@@ -198,17 +198,17 @@ tests =
, "Berkeley-style parenthetical citation list" =:
"[(cite): see; @Dominik201408;also @Pandoc; and others]" =?>
let pandocCite' = pandocCite {
- citationPrefix = toList "also"
- , citationSuffix = toList "and others"
+ citationPrefix = B.toList "also"
+ , citationSuffix = B.toList "and others"
}
dominikCite' = dominikCite {
- citationPrefix = toList "see"
+ citationPrefix = B.toList "see"
}
in (para $ cite [dominikCite', pandocCite'] "")
, "Berkeley-style plain citation list" =:
"[cite: See; @Dominik201408; and @Pandoc; and others]" =?>
- let pandocCite' = pandocInText { citationPrefix = toList "and" }
+ let pandocCite' = pandocInText { citationPrefix = B.toList "and" }
in (para $ "See "
<> cite [dominikInText] ""
<> "," <> space
diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs
index 6363d84b0..f38ee7194 100644
--- a/test/Tests/Readers/Org/Meta.hs
+++ b/test/Tests/Readers/Org/Meta.hs
@@ -16,7 +16,7 @@ import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep)
import Text.Pandoc
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
import qualified Data.Text as T
tests :: [TestTree]
@@ -43,14 +43,14 @@ tests =
, testGroup "Export settings"
[ "Title" =:
"#+title: Hello, World" =?>
- let titleInline = toList $ "Hello," <> space <> "World"
+ let titleInline = B.toList $ "Hello," <> space <> "World"
meta = setMeta "title" (MetaInlines titleInline) nullMeta
in Pandoc meta mempty
, testGroup "Author"
[ "sets 'author' field" =:
"#+author: John /Emacs-Fanboy/ Doe" =?>
- let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ]
+ let author = B.toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ]
meta = setMeta "author" (MetaInlines author) nullMeta
in Pandoc meta mempty
@@ -58,8 +58,8 @@ tests =
T.unlines [ "#+author: James Dewey Watson,"
, "#+author: Francis Harry Compton Crick"
] =?>
- let watson = toList "James Dewey Watson,"
- crick = toList "Francis Harry Compton Crick"
+ let watson = B.toList "James Dewey Watson,"
+ crick = B.toList "Francis Harry Compton Crick"
meta = setMeta "author"
(MetaInlines (watson ++ SoftBreak : crick))
nullMeta
@@ -68,7 +68,7 @@ tests =
, "Date" =:
"#+date: Feb. *28*, 2014" =?>
- let date = toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ]
+ let date = B.toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ]
meta = setMeta "date" (MetaInlines date) nullMeta
in Pandoc meta mempty
@@ -102,7 +102,7 @@ tests =
T.unlines [ "#+keywords: pandoc, testing,"
, "#+keywords: Org"
] =?>
- let keywords = toList $ "pandoc, testing," <> softbreak <> "Org"
+ let keywords = B.toList $ "pandoc, testing," <> softbreak <> "Org"
meta = setMeta "keywords" (MetaInlines keywords) nullMeta
in Pandoc meta mempty
@@ -128,7 +128,7 @@ tests =
[ "LATEX_HEADER" =:
"#+latex_header: \\usepackage{tikz}" =?>
let latexInlines = rawInline "latex" "\\usepackage{tikz}"
- inclList = MetaList [MetaInlines (toList latexInlines)]
+ inclList = MetaList [MetaInlines (B.toList latexInlines)]
meta = setMeta "header-includes" inclList nullMeta
in Pandoc meta mempty
@@ -162,7 +162,7 @@ tests =
[ "HTML_HEAD values are added to header-includes" =:
"#+html_head: <meta/>" =?>
let html = rawInline "html" "<meta/>"
- inclList = MetaList [MetaInlines (toList html)]
+ inclList = MetaList [MetaInlines (B.toList html)]
meta = setMeta "header-includes" inclList nullMeta
in Pandoc meta mempty
diff --git a/test/Tests/Readers/Org/Shared.hs b/test/Tests/Readers/Org/Shared.hs
index c584eff19..a1baaf75e 100644
--- a/test/Tests/Readers/Org/Shared.hs
+++ b/test/Tests/Readers/Org/Shared.hs
@@ -29,7 +29,7 @@ org :: Text -> Pandoc
org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test org
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index a12b59fc2..95e64c489 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -25,7 +25,7 @@ rst :: Text -> Pandoc
rst = purely $ readRST def{ readerStandalone = True }
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test rst
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
index 013f29d68..eb96b20ee 100644
--- a/test/Tests/Readers/Txt2Tags.hs
+++ b/test/Tests/Readers/Txt2Tags.hs
@@ -30,7 +30,7 @@ t2t = purely $ \s -> do
readTxt2Tags def s
infix 4 =:
-(=:) :: ToString c
+(=:) :: ToText c
=> String -> (Text, c) -> TestTree
(=:) = test t2t
diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs
index e415ea153..287c3a61b 100644
--- a/test/Tests/Shared.hs
+++ b/test/Tests/Shared.hs
@@ -16,7 +16,7 @@ import System.FilePath.Posix (joinPath)
import Test.Tasty
import Test.Tasty.HUnit (assertBool, testCase, (@?=))
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared (toLegacyTable)
@@ -58,7 +58,7 @@ testLegacyTable =
, testCase "decomposes a table without head" $ gen2 @?= expect2
]
where
- pln = toList . plain . str
+ pln = B.toList . plain . str
cl a h w = Cell ("", [], []) AlignDefault h w $ pln a
rws = map $ Row nullAttr
th = TableHead nullAttr . rws
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\">&gt;&gt;=</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\">&gt;&gt;=</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)