{-# LANGUAGE OverloadedStrings #-} module CustomBinarySpec ( spec ) where import Fixtures (defaultBinPath, simpleFilePath, exceptionString) import System.Exit (ExitCode) import System.IO.Temp (writeSystemTempFile) import System.Process (readProcessWithExitCode) import Test.Hspec import Util (shouldBeRight) import qualified System.IO.ExceptionFree as ExceptionFree data Mode = ExceptionFree | Original deriving (Eq, Enum, Show) type BinPath = FilePath type InputPath = FilePath type StdoutOutput = String type StderrOutput = String callProcessWithXC :: BinPath -> InputPath -> Mode -> IO (ExitCode, StdoutOutput, StderrOutput) callProcessWithXC binPath inputPath mode = readProcessWithExitCode binPath args [] where args = ["-m", show mode, inputPath, "+RTS", "-xc", "-RTS"] main :: IO () main = hspec spec spec :: Spec spec = describe "-xc exception throwing" $ do it "original prints an exception to stderr" $ \_ -> callProcessWithXC defaultBinPath simpleFilePath Original >>= \(_, _, stderr) -> stderr `shouldContain` exceptionString it "exception free does not print exception to stderr" $ \_ -> callProcessWithXC defaultBinPath simpleFilePath ExceptionFree >>= \(_, _, stderr) -> stderr `shouldNotContain` exceptionString