summaryrefslogtreecommitdiff
path: root/tests/Tests/Helpers.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Helpers.hs')
-rw-r--r--tests/Tests/Helpers.hs16
1 files changed, 14 insertions, 2 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index 028f93fe7..91243e1ce 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -1,17 +1,26 @@
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, TemplateHaskell #-}
-- Utility functions for the test suite.
-module Tests.Helpers where
+module Tests.Helpers ( lit
+ , test
+ , (=?>)
+ , property
+ , ToString(..)
+ , ToPandoc(..)
+ )
+ where
import Text.Pandoc.Definition
import Text.Pandoc.Builder (Inlines, Blocks, doc, plain)
import Test.Framework
import Test.Framework.Providers.HUnit
-import Test.HUnit hiding (Test)
+import Test.Framework.Providers.QuickCheck2
+import Test.HUnit (assertBool)
import Text.Pandoc.Shared (normalize, defaultWriterOptions,
WriterOptions(..), removeTrailingSpace)
import Text.Pandoc.Writers.Native (writeNative)
import Language.Haskell.TH.Quote
+import qualified Test.QuickCheck.Property as QP
lit :: QuasiQuoter
lit = QuasiQuoter ((\a -> let b = rnl a in [|b|]) . filter (/= '\r')) $
@@ -37,6 +46,9 @@ test fn name (input, expected) =
dashes x = '\n' : replicate (72 - length x - 5) '-' ++ " " ++
x ++ " ---\n"
+property :: QP.Testable a => TestName -> a -> Test
+property = testProperty
+
infix 6 =?>
(=?>) :: a -> b -> (a,b)
x =?> y = (x, y)