pandoc/tests/Tests/Helpers.hs

35 lines
1.1 KiB
Haskell
Raw Normal View History

2011-01-13 11:11:55 -08:00
-- 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."
2011-01-14 18:09:16 -08:00
latexTest :: String -> String -> Expect -> Test
latexTest = readerTestWithState defaultParserState readLaTeX
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