summaryrefslogtreecommitdiff
path: root/tests
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-22 12:18:59 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2011-01-22 12:18:59 -0800
commit209b300d6adeb2427c0058b808945ac39f851b24 (patch)
tree6ba5f255711fdd58fdf6d9d219d55e30b7f0a362 /tests
parentd86d9260df7fc9addccd289df7a15d9b36b21ae1 (diff)
Added 'property' in Tests.Helpers & some quickcheck tests.
Diffstat (limited to 'tests')
-rw-r--r--tests/Tests/Helpers.hs16
-rw-r--r--tests/Tests/Readers/LaTeX.hs1
-rw-r--r--tests/Tests/Writers/ConTeXt.hs12
3 files changed, 27 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)
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index 9db909b17..c152614dd 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -4,6 +4,7 @@ module Tests.Readers.LaTeX (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
+import Tests.Arbitrary
import Text.Pandoc.Builder
import Text.Pandoc
diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs
index 9b59c617d..6f380713c 100644
--- a/tests/Tests/Writers/ConTeXt.hs
+++ b/tests/Tests/Writers/ConTeXt.hs
@@ -5,10 +5,15 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
+import Tests.Arbitrary()
context :: (ToString a, ToPandoc a) => a -> String
context = writeConTeXt defaultWriterOptions . toPandoc
+context' :: (ToString a, ToPandoc a) => a -> String
+context' = writeConTeXt defaultWriterOptions{ writerWrapText = False }
+ . toPandoc
+
{-
"my test" =: X =?> Y
@@ -30,10 +35,17 @@ tests :: [Test]
tests = [ testGroup "inline code"
[ "with '}'" =: code "}" =?> "\\mono{\\letterclosebrace{}}"
, "without '}'" =: code "]" =?> "\\type{]}"
+ , property "code property" $ \s -> null s ||
+ if '{' `elem` s || '}' `elem` s
+ then (context' $ code s) == "\\mono{" ++
+ (context' $ str s) ++ "}"
+ else (context' $ code s) == "\\type{" ++ s ++ "}"
]
, testGroup "headers"
[ "level 1" =:
header 1 "My header" =?> "\\subject{My header}"
+ , property "header 1 property" $ \ils ->
+ context' (header 1 ils) == "\\subject{" ++ context' ils ++ "}"
]
, testGroup "bullet lists"
[ "nested" =: