Added some basic testing infrastructure and some latex reader tests.

This commit is contained in:
Nathan Gass 2011-01-12 14:16:35 +01:00
parent 4f6099f350
commit ec4deb2532
4 changed files with 79 additions and 1 deletions

View file

@ -298,7 +298,10 @@ Executable test-pandoc
if !flag(tests)
Buildable: False
else
Ghc-Options: -Wall
if impl(ghc >= 6.12)
Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind
else
Ghc-Options: -O2 -Wall
Extensions: CPP
Build-Depends: base >= 4 && < 5, Diff, test-framework, test-framework-hunit, HUnit
Other-Modules: Text.Pandoc.Shared, Text.Pandoc.Highlighting, Text.Pandoc.Writers.Native

37
tests/Helpers.hs Normal file
View file

@ -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]

35
tests/Latex/Reader.hs Normal file
View file

@ -0,0 +1,35 @@
module Latex.Reader (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Helpers
tests :: [Test]
tests = [ testGroup "basic" [ latexTest "simplest" "word"
(Inline $ Str "word")
, latexTest "space" "some text"
(Inlines $ [Str "some", Space, Str "text"])
, latexTest "emphasis" "\\emph{emphasized}"
(Inline $ Emph [Str "emphasized"])
]
, testGroup "headers" [ latexTest "1. level" "\\section{header}"
$ Block $ Header 1 [Str "header"]
, latexTest "2. level" "\\subsection{header}"
$ Block $ Header 2 [Str "header"]
, latexTest "3. level" "\\subsubsection{header}"
$ Block $ Header 3 [Str "header"]
, latexTest "with emphasis" "\\section{text \\emph{emph}}"
$ Block $ Header 1 [Str "text", Space, Emph [Str "emph"]]
, latexTest "with link" "\\section{text \\href{/url}{link}}"
$ Block $ Header 1 [Str "text", Space, Link [Str "link"] ("/url", "")]
]
]

View file

@ -5,9 +5,12 @@ module Main where
import Test.Framework
import qualified Old
import qualified Latex.Reader
tests :: [Test]
tests = [ testGroup "Old" Old.tests
, testGroup "Latex" [ testGroup "Reader" Latex.Reader.tests
]
]
main :: IO ()