2019-01-05 03:36:15 +01:00
|
|
|
{-# LANGUAGE CPP #-}
|
2021-03-20 05:17:13 +01:00
|
|
|
{-# LANGUAGE TupleSections #-}
|
2017-03-04 13:03:41 +01:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2019-02-04 22:52:31 +01:00
|
|
|
{- |
|
|
|
|
Module : Tests.Helpers
|
2021-01-08 18:38:20 +01:00
|
|
|
Copyright : © 2006-2021 John MacFarlane
|
2019-02-04 22:52:31 +01:00
|
|
|
License : GNU GPL, version 2 or above
|
2011-01-13 20:11:55 +01:00
|
|
|
|
2019-02-04 22:52:31 +01:00
|
|
|
Maintainer : John MacFarlane <jgm@berkeley@edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Utility functions for the test suite.
|
|
|
|
-}
|
2013-01-23 17:47:43 +01:00
|
|
|
module Tests.Helpers ( test
|
2017-02-04 21:54:41 +01:00
|
|
|
, TestResult(..)
|
2021-03-20 05:17:13 +01:00
|
|
|
, setupEnvironment
|
2017-02-04 21:54:41 +01:00
|
|
|
, showDiff
|
2021-08-11 07:07:48 +02:00
|
|
|
, testGolden
|
2011-01-22 21:18:59 +01:00
|
|
|
, (=?>)
|
2016-11-27 11:52:42 +01:00
|
|
|
, purely
|
2011-01-22 21:18:59 +01:00
|
|
|
, ToString(..)
|
|
|
|
, ToPandoc(..)
|
|
|
|
)
|
|
|
|
where
|
2011-01-12 14:16:35 +01:00
|
|
|
|
2021-08-11 07:07:48 +02:00
|
|
|
import System.FilePath
|
2017-03-04 13:03:41 +01:00
|
|
|
import Data.Algorithm.Diff
|
|
|
|
import qualified Data.Map as M
|
2021-08-11 07:07:48 +02:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
2017-06-10 18:26:44 +02:00
|
|
|
import Data.Text (Text, unpack)
|
2021-08-11 07:07:48 +02:00
|
|
|
import qualified Data.Text as T
|
2017-03-04 13:03:41 +01:00
|
|
|
import System.Exit
|
2021-03-20 05:17:13 +01:00
|
|
|
import qualified System.Environment as Env
|
2017-03-14 17:05:36 +01:00
|
|
|
import Test.Tasty
|
2021-08-11 07:07:48 +02:00
|
|
|
import Test.Tasty.Golden.Advanced (goldenTest)
|
2017-03-14 17:05:36 +01:00
|
|
|
import Test.Tasty.HUnit
|
2017-03-04 13:03:41 +01:00
|
|
|
import Text.Pandoc.Builder (Blocks, Inlines, doc, plain)
|
|
|
|
import Text.Pandoc.Class
|
|
|
|
import Text.Pandoc.Definition
|
2012-07-27 07:59:56 +02:00
|
|
|
import Text.Pandoc.Options
|
2017-03-04 13:03:41 +01:00
|
|
|
import Text.Pandoc.Shared (trimr)
|
2011-01-22 05:50:18 +01:00
|
|
|
import Text.Pandoc.Writers.Native (writeNative)
|
2017-02-04 21:54:41 +01:00
|
|
|
import Text.Printf
|
2011-01-12 14:16:35 +01:00
|
|
|
|
2021-02-22 23:56:04 +01:00
|
|
|
test :: (ToString a, ToString b, ToString c, HasCallStack)
|
2011-01-22 05:50:18 +01:00
|
|
|
=> (a -> b) -- ^ function to test
|
|
|
|
-> String -- ^ name of test case
|
|
|
|
-> (a, c) -- ^ (input, expected value)
|
2017-03-14 17:05:36 +01:00
|
|
|
-> TestTree
|
2011-01-22 05:50:18 +01:00
|
|
|
test fn name (input, expected) =
|
2017-03-14 17:05:36 +01:00
|
|
|
testCase name' $ assertBool msg (actual' == expected')
|
2011-01-22 23:58:32 +01:00
|
|
|
where msg = nl ++ dashes "input" ++ nl ++ input' ++ nl ++
|
2013-01-12 19:21:07 +01:00
|
|
|
dashes "result" ++ nl ++
|
|
|
|
unlines (map vividize diff) ++
|
2011-01-22 05:50:18 +01:00
|
|
|
dashes ""
|
2011-01-22 23:58:32 +01:00
|
|
|
nl = "\n"
|
2017-03-14 17:05:36 +01:00
|
|
|
name' = if length name > 54
|
|
|
|
then take 52 name ++ "..." -- avoid wide output
|
|
|
|
else name
|
2011-01-22 05:50:18 +01:00
|
|
|
input' = toString input
|
2013-01-12 19:21:07 +01:00
|
|
|
actual' = lines $ toString $ fn input
|
|
|
|
expected' = lines $ toString expected
|
|
|
|
diff = getDiff expected' actual'
|
2011-01-22 23:58:32 +01:00
|
|
|
dashes "" = replicate 72 '-'
|
|
|
|
dashes x = replicate (72 - length x - 5) '-' ++ " " ++ x ++ " ---"
|
|
|
|
|
2021-08-11 07:07:48 +02:00
|
|
|
testGolden :: TestName -> FilePath -> FilePath -> (Text -> IO Text) -> TestTree
|
|
|
|
testGolden name expectedPath inputPath fn =
|
|
|
|
goldenTest
|
|
|
|
name
|
|
|
|
(UTF8.readFile expectedPath)
|
|
|
|
(UTF8.readFile inputPath >>= fn)
|
|
|
|
compareVals
|
|
|
|
(UTF8.writeFile expectedPath)
|
|
|
|
where
|
|
|
|
compareVals expected actual
|
|
|
|
| expected == actual = return Nothing
|
|
|
|
| otherwise = return $ Just $
|
|
|
|
"\n--- " ++ expectedPath ++ "\n+++\n" ++
|
|
|
|
showDiff (1,1)
|
|
|
|
(getDiff (lines . filter (/='\r') $ T.unpack actual)
|
|
|
|
(lines . filter (/='\r') $ T.unpack expected))
|
|
|
|
|
2021-03-20 05:17:13 +01:00
|
|
|
-- | Set up environment for pandoc command tests.
|
|
|
|
setupEnvironment :: FilePath -> IO [(String, String)]
|
|
|
|
setupEnvironment testExePath = do
|
|
|
|
mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
|
|
|
|
mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
|
|
|
|
mpdd <- Env.lookupEnv "pandoc_datadir"
|
|
|
|
-- Note that Cabal sets the pandoc_datadir environment variable
|
|
|
|
-- to point to the source directory, since otherwise getDataFilename
|
|
|
|
-- will look in the data directory into which pandoc will be installed
|
|
|
|
-- (but has not yet been). So when we spawn a new process with
|
|
|
|
-- pandoc, we need to make sure this environment variable is set.
|
|
|
|
return $ ("PATH",takeDirectory testExePath) :
|
|
|
|
("TMP",".") :
|
|
|
|
("LANG","en_US.UTF-8") :
|
|
|
|
("HOME", "./") :
|
|
|
|
maybe [] ((:[]) . ("pandoc_datadir",)) mpdd ++
|
|
|
|
maybe [] ((:[]) . ("LD_LIBRARY_PATH",)) mldpath ++
|
|
|
|
maybe [] ((:[]) . ("DYLD_LIBRARY_PATH",)) mdyldpath
|
|
|
|
|
2017-02-04 21:54:41 +01:00
|
|
|
data TestResult = TestPassed
|
|
|
|
| TestError ExitCode
|
|
|
|
| TestFailed String FilePath [Diff String]
|
|
|
|
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
|
|
|
|
where dash = replicate 72 '-'
|
|
|
|
|
|
|
|
showDiff :: (Int,Int) -> [Diff String] -> String
|
|
|
|
showDiff _ [] = ""
|
|
|
|
showDiff (l,r) (First ln : ds) =
|
|
|
|
printf "+%4d " l ++ ln ++ "\n" ++ showDiff (l+1,r) ds
|
|
|
|
showDiff (l,r) (Second ln : ds) =
|
|
|
|
printf "-%4d " r ++ ln ++ "\n" ++ showDiff (l,r+1) ds
|
|
|
|
showDiff (l,r) (Both _ _ : ds) =
|
|
|
|
showDiff (l+1,r+1) ds
|
|
|
|
|
2013-01-02 20:41:22 +01:00
|
|
|
vividize :: Diff String -> String
|
2013-01-12 19:21:07 +01:00
|
|
|
vividize (Both s _) = " " ++ s
|
|
|
|
vividize (First s) = "- " ++ s
|
|
|
|
vividize (Second s) = "+ " ++ s
|
2011-01-21 19:23:41 +01:00
|
|
|
|
2016-11-27 11:52:42 +01:00
|
|
|
purely :: (b -> PandocPure a) -> b -> a
|
|
|
|
purely f = either (error . show) id . runPure . f
|
|
|
|
|
2012-02-05 22:23:06 +01:00
|
|
|
infix 5 =?>
|
2011-01-22 05:50:18 +01:00
|
|
|
(=?>) :: a -> b -> (a,b)
|
|
|
|
x =?> y = (x, y)
|
2011-01-19 08:34:34 +01:00
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
class ToString a where
|
|
|
|
toString :: a -> String
|
2011-01-19 08:34:34 +01:00
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
instance ToString Pandoc where
|
2017-06-10 23:39:49 +02:00
|
|
|
toString d = unpack $
|
|
|
|
purely (writeNative def{ writerTemplate = s }) $ toPandoc d
|
2011-01-22 05:50:18 +01:00
|
|
|
where s = case d of
|
2013-05-11 07:53:35 +02:00
|
|
|
(Pandoc (Meta m) _)
|
2016-11-30 15:34:58 +01:00
|
|
|
| M.null m -> Nothing
|
2019-07-26 21:00:44 +02:00
|
|
|
| otherwise -> Just mempty -- need this to get meta output
|
2011-01-19 08:34:34 +01:00
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
instance ToString Blocks where
|
2017-06-10 23:39:49 +02:00
|
|
|
toString = unpack . purely (writeNative def) . toPandoc
|
2011-01-19 08:34:34 +01:00
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
instance ToString Inlines where
|
Switch to new pandoc-types and use Text instead of String [API change].
PR #5884.
+ Use pandoc-types 1.20 and texmath 0.12.
+ Text is now used instead of String, with a few exceptions.
+ In the MediaBag module, some of the types using Strings
were switched to use FilePath instead (not Text).
+ In the Parsing module, new parsers `manyChar`, `many1Char`,
`manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`,
`mantyUntilChar` have been added: these are like their
unsuffixed counterparts but pack some or all of their output.
+ `glob` in Text.Pandoc.Class still takes String since it seems
to be intended as an interface to Glob, which uses strings.
It seems to be used only once in the package, in the EPUB writer,
so that is not hard to change.
2019-11-04 22:12:37 +01:00
|
|
|
toString = unpack . trimr . purely (writeNative def) . toPandoc
|
2011-01-19 08:34:34 +01:00
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
instance ToString String where
|
|
|
|
toString = id
|
2011-01-19 08:34:34 +01:00
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
instance ToString Text where
|
|
|
|
toString = unpack
|
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
class ToPandoc a where
|
|
|
|
toPandoc :: a -> Pandoc
|
2011-01-12 14:16:35 +01:00
|
|
|
|
2011-01-22 05:50:18 +01:00
|
|
|
instance ToPandoc Pandoc where
|
2016-12-11 22:09:33 +01:00
|
|
|
toPandoc = id
|
2011-01-22 05:50:18 +01:00
|
|
|
|
|
|
|
instance ToPandoc Blocks where
|
2016-12-11 22:09:33 +01:00
|
|
|
toPandoc = doc
|
2011-01-22 05:50:18 +01:00
|
|
|
|
|
|
|
instance ToPandoc Inlines where
|
2016-12-11 22:09:33 +01:00
|
|
|
toPandoc = doc . plain
|