aboutsummaryrefslogtreecommitdiff
path: root/tests/Helpers.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Helpers.hs')
-rw-r--r--tests/Helpers.hs37
1 files changed, 37 insertions, 0 deletions
diff --git a/tests/Helpers.hs b/tests/Helpers.hs
new file mode 100644
index 000000000..c61207153
--- /dev/null
+++ b/tests/Helpers.hs
@@ -0,0 +1,37 @@
+module 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 structur of Pandoc document."
+
+latexTest :: String-> String -> Expect -> Test
+latexTest = latexTestWithState defaultParserState
+
+latexTestWithState :: ParserState -> String -> String -> Expect -> Test
+latexTestWithState state name string exp = testCase name $ exp `assertPandoc` readLaTeX state string
+
+blocks :: [Block] -> Pandoc
+blocks bs = Pandoc (Meta { docTitle = [], docAuthors = [], docDate = [] }) bs
+
+block :: Block -> Pandoc
+block b = blocks [b]
+
+inlines :: [Inline] -> Pandoc
+inlines is = block $ Para is
+
+inline :: Inline -> Pandoc
+inline i = inlines [i]