diff options
-rw-r--r-- | pandoc.cabal | 5 | ||||
-rw-r--r-- | tests/Helpers.hs | 37 | ||||
-rw-r--r-- | tests/Latex/Reader.hs | 35 | ||||
-rw-r--r-- | tests/test-pandoc.hs | 3 |
4 files changed, 79 insertions, 1 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index 71cb0135b..da855a07d 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -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 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] diff --git a/tests/Latex/Reader.hs b/tests/Latex/Reader.hs new file mode 100644 index 000000000..d313b33eb --- /dev/null +++ b/tests/Latex/Reader.hs @@ -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", "")] + ] + ] + diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index ae367fc53..cf7a7e5e4 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -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 () |