module Test.Tasty.Lua.Translate
( translateResultsFromFile
, pathFailure
)
where
import Foreign.Lua (Lua)
import Test.Tasty.Lua.Core (Outcome (..), ResultTree (..), UnnamedTree (..),
runTastyFile)
import qualified Test.Tasty as Tasty
import qualified Test.Tasty.Providers as Tasty
translateResultsFromFile :: FilePath -> Lua Tasty.TestTree
translateResultsFromFile fp = do
result <- runTastyFile fp
case result of
Left errMsg -> return $ pathFailure fp errMsg
Right tree -> return $ Tasty.testGroup fp (map testTree tree)
pathFailure :: FilePath -> String -> Tasty.TestTree
pathFailure fp errMsg = Tasty.singleTest fp (MockTest (Failure errMsg))
testTree :: ResultTree -> Tasty.TestTree
testTree (ResultTree name tree) =
case tree of
SingleTest outcome -> Tasty.singleTest name (MockTest outcome)
TestGroup results -> Tasty.testGroup name (map testTree results)
newtype MockTest = MockTest Outcome
instance Tasty.IsTest MockTest where
run _ (MockTest outcome) _ = return $ case outcome of
Success -> Tasty.testPassed ""
Failure msg -> Tasty.testFailed msg
testOptions = return []