module Test.Tasty.Program (
testProgram
) where
import Data.Typeable ( Typeable )
import System.Directory ( findExecutable )
import System.Exit ( ExitCode(..) )
import System.Process ( runInteractiveProcess, waitForProcess )
import Test.Tasty.Providers ( IsTest (..), Result, TestName, TestTree,
singleTest, testPassed, testFailed )
data TestProgram = TestProgram String [String] (Maybe FilePath)
deriving (Typeable)
testProgram :: TestName
-> String
-> [String]
-> Maybe FilePath
-> TestTree
testProgram testName program opts workingDir =
singleTest testName (TestProgram program opts workingDir)
instance IsTest TestProgram where
run _ (TestProgram program opts workingDir) _ = do
execFound <- findExecutable program
case execFound of
Nothing -> return $ execNotFoundFailure program
Just progPath -> runProgram progPath opts workingDir
testOptions = return []
runProgram :: String
-> [String]
-> Maybe FilePath
-> IO Result
runProgram program opts workingDir = do
(_, _, _, pid) <- runInteractiveProcess program opts workingDir Nothing
ecode <- waitForProcess pid
case ecode of
ExitSuccess -> return success
ExitFailure code -> return $ exitFailure program code
success :: Result
success = testPassed ""
execNotFoundFailure :: String -> Result
execNotFoundFailure file =
testFailed $ "Cannot locate program " ++ file ++ " in the PATH"
exitFailure :: String -> Int -> Result
exitFailure file code =
testFailed $ "Program " ++ file ++ " failed with code " ++ show code