{-# LANGUAGE OverloadedStrings #-} import qualified Data.Map as M import Network.Scraper.State import Test.Tasty (defaultMain, testGroup) import Test.Tasty.HUnit import Text.XML.Cursor trivialTest = testCase "mytest" $ assertEqual "" 1 1 testDisplayNone = testCase "testDisplayNone" $ do assertEqual "" True (hasDisplayNone inp) where inp = toCursor "" testClassHide = testCase "testClassHide" $ do assertEqual "" True (hasHide inp) where inp = toCursor "" testIsDisplayedAll = testCase "testIsDisplayedAll" $ do assertEqual "Not Displayed (has display: none;)" False (isDisplayed dispNone) assertEqual "Not Displayed (has class: hide)" False (isDisplayed classHidden) assertEqual "Not Displayed (has hide and dispNone)" False (isDisplayed dispNoneClassHidden) assertEqual "Is Displayed" True (isDisplayed visibleInp) assertEqual "Parent hidden" False (isDisplayed parentHiddenInps) where dispNone = toCursor "" classHidden = toCursor "" dispNoneClassHidden = toCursor "" visibleInp = toCursor "" parentHiddenInps = toCursor $ "\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
\ \
" testVisibleGetInputs = testCase "testGetInputs" $ do assertEqual "" (getInputs AllVisible form) (M.fromList [("YES","")]) where form = toCursor "
" tests = testGroup "All tests" [ testDisplayNone , testClassHide , testIsDisplayedAll , testVisibleGetInputs ] main :: IO () main = defaultMain tests