2011-01-13 11:11:55 -08:00
|
|
|
-- Utility functions for the test suite.
|
|
|
|
|
2011-01-13 10:59:44 -08:00
|
|
|
module Tests.Helpers where
|
2011-01-12 14:16:35 +01:00
|
|
|
|
|
|
|
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
|
2011-01-12 14:44:32 +01:00
|
|
|
assertPandoc (Inline e) (Pandoc _ [Para [g]]) = e @=? g
|
2011-01-12 14:16:35 +01:00
|
|
|
assertPandoc (Inlines e) (Pandoc _ [Para g] ) = e @=? g
|
2011-01-12 14:44:32 +01:00
|
|
|
assertPandoc (Block e) (Pandoc _ [g] ) = e @=? g
|
|
|
|
assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g
|
|
|
|
assertPandoc _ _ = assertFailure "Wrong structure of Pandoc document."
|
2011-01-12 14:16:35 +01:00
|
|
|
|
2011-01-14 18:09:16 -08:00
|
|
|
latexTest :: String -> String -> Expect -> Test
|
2011-01-12 19:32:26 +01:00
|
|
|
latexTest = readerTestWithState defaultParserState readLaTeX
|
2011-01-12 14:16:35 +01:00
|
|
|
|
2011-01-14 18:09:16 -08:00
|
|
|
readerTestWithState :: ParserState
|
|
|
|
-> (ParserState -> String -> Pandoc)
|
|
|
|
-> String
|
|
|
|
-> String
|
|
|
|
-> Expect
|
|
|
|
-> Test
|
|
|
|
readerTestWithState state reader name string e =
|
|
|
|
testCase name $ e `assertPandoc` reader state string
|
2011-01-12 14:16:35 +01:00
|
|
|
|