module Test.FIT.FixtureTest where
import Test.HUnit
import Test.FIT.Fixture
import Test.FIT.Parse
import Test.FIT.LoadFixture
import Data.HashTable as Hash
fixtureTests = TestList
[ testTraverseOneTable
, testTraverseTwoRows ]
testTraverseTwoRows = TestCase $ do
let
inputHtml =
-- we need at least three rows in the fixture
-- because the first two are skipped
"
"
++ "Test.FIT.Fixture | two | three |
"
++ "one | two | three |
"
++ "one | two | three |
"
++ "
"
++ ""
++ "Test.FIT.Fixture | two | three |
"
++ "one | two | three |
"
++ "one | two | three |
"
++ "
"
expectHtml =
""
++ "Test.FIT.Fixture | two | three |
"
++ "one | two | three |
"
++ "one | "
++ "two | "
++ "three |
"
++ "
"
++ ""
++ "Test.FIT.Fixture | two | three |
"
++ "one | two | three |
"
++ "one | "
++ "two | "
++ "three |
"
++ "
"
case parse inputHtml ["table", "tr", "td"] 0 0 of
Left e -> assertFailure e
Right p -> do
summary <- Hash.new (==) hashString
p' <- doTables p summary "" -- >>= return . fixtureParse
assertEqual "traverse" expectHtml (printParse p')
return ()
testTraverseOneTable = TestCase $ do
let
inputHtml =
""
++ "Test.FIT.Fixture | two | three |
"
-- ++ "one | two | three |
"
++ "
"
expectHtml =
""
++ "Test.FIT.Fixture | two | three |
"
-- ++ "one | two | three |
"
++ "
"
case parse inputHtml ["table", "tr", "td"] 0 0 of
Left e -> assertFailure e
Right p -> do
summary <- Hash.new (==) hashString
p' <- doTables p summary "" -- >>= return . fixtureParse
assertEqual "traverse" expectHtml (printParse p')
return ()