| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Test.Main
Contents
Synopsis
- captureProcessResult :: IO () -> IO ProcessResult
 - data ProcessResult = ProcessResult {
- prStdout :: !ByteString
 - prStderr :: !ByteString
 - prExitCode :: !ExitCode
 - prException :: !(Maybe SomeException)
 
 - withStdin :: ByteString -> IO a -> IO a
 - withEnv :: [(String, Maybe String)] -> IO a -> IO a
 - withArgs :: [String] -> IO a -> IO a
 - data ExitCode
 
Utilities for testing your main function
captureProcessResult :: IO () -> IO ProcessResult Source #
Capture stdout, stderr, and exit code of the given IO action.
>>>let main = putStr "hello">>>captureProcessResult mainProcessResult {prStdout = "hello", prStderr = "", prExitCode = ExitSuccess, prException = Nothing}
If the IO action exit with error message, the exit code of result is ExitFailure.
>>>import System.IO>>>import System.Exit>>>let main = hPutStr stderr "OMG!" >> exitWith (ExitFailure 1)>>>captureProcessResult mainProcessResult {prStdout = "", prStderr = "OMG!", prExitCode = ExitFailure 1, prException = Nothing}
Since v0.2.0.0, this function catches SomeException, not only ExitCode
 to prevent it from losing output when an exception other than ExitCode is thrown.
 To get the thrown error, use prException.
Note: prStderr doesn't contain the error message of the thrown exception.
 See the example below.
>>>import Control.Exception>>>let main = ioError $ userError "OMG!">>>captureProcessResult mainProcessResult {prStdout = "", prStderr = "", prExitCode = ExitFailure 1, prException = Just user error (OMG!)}
Since: 0.2.0.0
data ProcessResult Source #
Used for the result of captureProcessResult.
Constructors
| ProcessResult | |
Fields 
  | |
Instances
withStdin :: ByteString -> IO a -> IO a Source #
Pass the ByteString to stdin of the given IO action.
>>>import Data.ByteString.Char8 ()>>>:set -XOverloadedStrings>>>let main = putStrLn . reverse =<< getLine>>>withStdin "abcde" mainedcba
withEnv :: [(String, Maybe String)] -> IO a -> IO a Source #
Run the given IO action with the specified environment variables set.
 The environment variables are specified as pairs of ENV_VAR_NAME and ENV_VAR_VALUE.
 If ENV_VAR_VALUE is Nothing, the ENV_VAR_NAME is unset with unsetEnv.
>>>import System.Environment>>>setEnv "ENV_VAR_TO_UNSET" "value_to_unset">>>setEnv "ENV_VAR_TO_OVERWRITE" "value_to_overwrite">>>let main = (print =<< lookupEnv "ENV_VAR_TO_UNSET") >> (print =<< lookupEnv "ENV_VAR_TO_OVERWRITE")>>>withEnv [("ENV_VAR_TO_UNSET", Nothing), ("ENV_VAR_TO_OVERWRITE" , Just "new_value")] mainNothing Just "new_value">>>mainJust "value_to_unset" Just "value_to_overwrite"
Re-export from System.Environment
Re-export from System.Exit
Defines the exit codes that a program can return.
Constructors
| ExitSuccess | indicates successful termination;  | 
| ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system).  | 
Instances
| Eq ExitCode | |
| Ord ExitCode | |
Defined in GHC.IO.Exception  | |
| Read ExitCode | |
| Show ExitCode | |
| Generic ExitCode | |
| Exception ExitCode | Since: base-4.1.0.0  | 
Defined in GHC.IO.Exception Methods toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String #  | |
| type Rep ExitCode | |
Defined in GHC.IO.Exception  | |