module Test.Tasty.Program (
testProgram
, CatchStderr
) where
import Control.DeepSeq ( deepseq )
import Data.Typeable ( Typeable )
import Data.Proxy ( Proxy (..) )
import System.Directory ( findExecutable )
import System.Exit ( ExitCode(..) )
import System.Process ( runInteractiveProcess, waitForProcess )
import System.IO ( hGetContents )
import Test.Tasty.Providers ( IsTest (..), Result, TestName, TestTree,
singleTest, testPassed, testFailed )
import Test.Tasty.Options ( IsOption (..), OptionDescription(..),
safeRead, lookupOption, flagCLParser )
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 opts (TestProgram program args workingDir) _ = do
execFound <- findExecutable program
let CatchStderr catchStderr = lookupOption opts
case execFound of
Nothing -> return $ execNotFoundFailure program
Just progPath -> runProgram progPath args workingDir catchStderr
testOptions = return [Option (Proxy :: Proxy CatchStderr)]
newtype CatchStderr = CatchStderr Bool deriving (Show, Typeable)
instance IsOption CatchStderr where
defaultValue = CatchStderr False
parseValue = fmap CatchStderr . safeRead
optionName = return "catch-stderr"
optionHelp = return "Catch standart error of programs"
optionCLParser = flagCLParser (Just 'e') (CatchStderr False)
runProgram :: String
-> [String]
-> Maybe FilePath
-> Bool
-> IO Result
runProgram program args workingDir catchStderr = do
(_, _, stderrH, pid) <- runInteractiveProcess program args workingDir Nothing
stderr <- if catchStderr then fmap Just (hGetContents stderrH) else return Nothing
ecode <- stderr `deepseq` waitForProcess pid
case ecode of
ExitSuccess -> return success
ExitFailure code -> return $ exitFailure program code stderr
success :: Result
success = testPassed ""
execNotFoundFailure :: String -> Result
execNotFoundFailure file =
testFailed $ "Cannot locate program " ++ file ++ " in the PATH"
exitFailure :: String -> Int -> Maybe String -> Result
exitFailure file code stderr =
testFailed $ "Program " ++ file ++ " failed with code " ++ show code
++ case stderr of
Nothing -> ""
Just s -> "\n Stderr was: \n" ++ s