pandoc/tests/test-pandoc.hs

54 lines
1.8 KiB
Haskell
Raw Normal View History

{-# OPTIONS_GHC -Wall #-}
module Main where
import Test.Framework
import GHC.IO.Encoding
2011-01-12 19:10:56 +01:00
import qualified Tests.Old
import qualified Tests.Readers.LaTeX
2011-01-27 07:09:09 +01:00
import qualified Tests.Readers.Markdown
import qualified Tests.Readers.Org
2011-01-26 18:10:39 +01:00
import qualified Tests.Readers.RST
import qualified Tests.Readers.Docx
import qualified Tests.Writers.ConTeXt
import qualified Tests.Writers.LaTeX
import qualified Tests.Writers.HTML
import qualified Tests.Writers.Docbook
2011-01-22 21:28:30 +01:00
import qualified Tests.Writers.Native
import qualified Tests.Writers.Markdown
import qualified Tests.Writers.AsciiDoc
import qualified Tests.Shared
import qualified Tests.Walk
import Text.Pandoc.Shared (inDirectory)
tests :: [Test]
2011-01-12 19:10:56 +01:00
tests = [ testGroup "Old" Tests.Old.tests
, testGroup "Shared" Tests.Shared.tests
, testGroup "Walk" Tests.Walk.tests
, testGroup "Writers"
[ testGroup "Native" Tests.Writers.Native.tests
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests
, testGroup "LaTeX" Tests.Writers.LaTeX.tests
, testGroup "HTML" Tests.Writers.HTML.tests
, testGroup "Docbook" Tests.Writers.Docbook.tests
, testGroup "Markdown" Tests.Writers.Markdown.tests
, testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests
]
, testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests
2011-01-27 07:09:09 +01:00
, testGroup "Markdown" Tests.Readers.Markdown.tests
, testGroup "Org" Tests.Readers.Org.tests
2011-01-26 18:10:39 +01:00
, testGroup "RST" Tests.Readers.RST.tests
, testGroup "Docx" Tests.Readers.Docx.tests
2014-06-15 21:00:04 +02:00
]
]
main :: IO ()
main = do
setLocaleEncoding utf8
-- we ignore command-line arguments, since we're having cabal pass
-- the build directory as first argument, and we don't want test-framework
-- to choke on that.
inDirectory "tests" $ defaultMainWithArgs tests []