aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Helpers.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-15 09:25:01 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2011-01-15 09:25:01 -0800
commita0e19ba8aaa9304e9b0d1079e8357412e0402d0d (patch)
treeaee2a1569a601a2f32714549ac27a52ce9550c2d /tests/Tests/Helpers.hs
parent8ad6e013fc55013ccdcf0ff4c7fbc9fc5e886ab3 (diff)
parentdc93073804acecaf883d099ef3e1d067a29c9951 (diff)
downloadpandoc-a0e19ba8aaa9304e9b0d1079e8357412e0402d0d.tar.gz
Merge branch 'tests'
Diffstat (limited to 'tests/Tests/Helpers.hs')
-rw-r--r--tests/Tests/Helpers.hs34
1 files changed, 34 insertions, 0 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
new file mode 100644
index 000000000..539b26dcd
--- /dev/null
+++ b/tests/Tests/Helpers.hs
@@ -0,0 +1,34 @@
+-- Utility functions for the test suite.
+
+module Tests.Helpers where
+
+import Text.Pandoc
+
+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
+