summaryrefslogtreecommitdiff
path: root/tests/Tests/Helpers.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-02-04 12:56:30 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2017-02-04 12:56:30 +0100
commit18ab8642692caca2716fd9b5a0e6dbfd3d9cf9cc (patch)
tree05f4e9024093e233c131b3494e71265062ffd94a /tests/Tests/Helpers.hs
parent8418c1a7d7e5312dfddbc011adb257552b2a864b (diff)
Moved tests/ -> test/.
Diffstat (limited to 'tests/Tests/Helpers.hs')
-rw-r--r--tests/Tests/Helpers.hs90
1 files changed, 0 insertions, 90 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
deleted file mode 100644
index 84c2394bc..000000000
--- a/tests/Tests/Helpers.hs
+++ /dev/null
@@ -1,90 +0,0 @@
-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
--- Utility functions for the test suite.
-
-module Tests.Helpers ( test
- , (=?>)
- , purely
- , property
- , ToString(..)
- , ToPandoc(..)
- )
- where
-
-import Text.Pandoc.Definition
-import Text.Pandoc.Builder (Inlines, Blocks, doc, plain)
-import Text.Pandoc.Class
-import Test.Framework
-import Test.Framework.Providers.HUnit
-import Test.Framework.Providers.QuickCheck2
-import Test.HUnit (assertBool)
-import Text.Pandoc.Shared (trimr)
-import Text.Pandoc.Options
-import Text.Pandoc.Writers.Native (writeNative)
-import qualified Test.QuickCheck.Property as QP
-import Data.Algorithm.Diff
-import qualified Data.Map as M
-
-test :: (ToString a, ToString b, ToString c)
- => (a -> b) -- ^ function to test
- -> String -- ^ name of test case
- -> (a, c) -- ^ (input, expected value)
- -> Test
-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) ++
- dashes ""
- nl = "\n"
- input' = toString input
- actual' = lines $ toString $ fn input
- expected' = lines $ toString expected
- diff = getDiff expected' actual'
- dashes "" = replicate 72 '-'
- dashes x = replicate (72 - length x - 5) '-' ++ " " ++ x ++ " ---"
-
-vividize :: Diff String -> String
-vividize (Both s _) = " " ++ s
-vividize (First s) = "- " ++ s
-vividize (Second s) = "+ " ++ s
-
-property :: QP.Testable a => TestName -> a -> Test
-property = testProperty
-
-purely :: (b -> PandocPure a) -> b -> a
-purely f = either (error . show) id . runPure . f
-
-infix 5 =?>
-(=?>) :: a -> b -> (a,b)
-x =?> y = (x, y)
-
-class ToString a where
- toString :: a -> String
-
-instance ToString Pandoc where
- toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
- where s = case d of
- (Pandoc (Meta m) _)
- | M.null m -> Nothing
- | otherwise -> Just "" -- need this to get meta output
-
-instance ToString Blocks where
- toString = purely (writeNative def) . toPandoc
-
-instance ToString Inlines where
- toString = trimr . purely (writeNative def) . toPandoc
-
-instance ToString String where
- toString = id
-
-class ToPandoc a where
- toPandoc :: a -> Pandoc
-
-instance ToPandoc Pandoc where
- toPandoc = id
-
-instance ToPandoc Blocks where
- toPandoc = doc
-
-instance ToPandoc Inlines where
- toPandoc = doc . plain