aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Helpers.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-18 23:34:34 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2011-01-18 23:34:34 -0800
commit0502c0fd28c4ef20f437ad1c8ae50c1e2793cd3b (patch)
treeb23ca56723fa97647360cd9ce8a00be67154f1fb /tests/Tests/Helpers.hs
parent0cfafdec643021ce8b45e07ef826b2c196636fae (diff)
downloadpandoc-0502c0fd28c4ef20f437ad1c8ae50c1e2793cd3b.tar.gz
Revamped tests with new =: and =?> operators + builder.
Left in a couple failing tests for demonstration purposes.
Diffstat (limited to 'tests/Tests/Helpers.hs')
-rw-r--r--tests/Tests/Helpers.hs46
1 files changed, 22 insertions, 24 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index 539b26dcd..08cc9b63b 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -1,34 +1,32 @@
+{-# LANGUAGE TypeSynonymInstances #-}
-- Utility functions for the test suite.
module Tests.Helpers where
import Text.Pandoc
-
+import Text.Pandoc.Builder
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.HUnit hiding (Test)
-data Expect = Inline Inline
- | Inlines [Inline]
- | Block Block
- | Blocks [Block]
-
-assertPandoc :: Expect -> Pandoc -> Assertion
-assertPandoc (Inline e) (Pandoc _ [Para [g]]) = e @=? g
-assertPandoc (Inlines e) (Pandoc _ [Para g] ) = e @=? g
-assertPandoc (Block e) (Pandoc _ [g] ) = e @=? g
-assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g
-assertPandoc _ _ = assertFailure "Wrong structure of Pandoc document."
-
-latexTest :: String -> String -> Expect -> Test
-latexTest = readerTestWithState defaultParserState readLaTeX
-
-readerTestWithState :: ParserState
- -> (ParserState -> String -> Pandoc)
- -> String
- -> String
- -> Expect
- -> Test
-readerTestWithState state reader name string e =
- testCase name $ e `assertPandoc` reader state string
+-- in Helpers
+class Expect a where
+ (=?>) :: Pandoc -> a -> Assertion
+
+infix 8 =?>
+
+(=:) :: TestName -> Assertion -> Test
+(=:) = testCase
+
+infix 6 =:
+
+instance Expect Inlines where
+ (Pandoc _ [Para ils]) =?> e = assertEqual " " (toList e) ils
+ g =?> e = assertEqual " " (doc $ para e) g
+
+instance Expect Blocks where
+ (Pandoc _ bls) =?> e = assertEqual " " (toList e) bls
+
+instance Expect Pandoc where
+ g =?> e = assertEqual " " e g