main-tester-0.2.0.1: Capture stdout/stderr/exit code, and replace stdin of your main function.

Safe HaskellSafe
LanguageHaskell2010

Test.Main

Contents

Synopsis

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 main
ProcessResult {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 main
ProcessResult {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 main
ProcessResult {prStdout = "", prStderr = "", prExitCode = ExitFailure 1, prException = Just user error (OMG!)}

Since: 0.2.0.0

data ProcessResult Source #

Used for the result of captureProcessResult.

Instances
Eq ProcessResult Source # 
Instance details

Defined in Test.Main.Internal

Show ProcessResult Source # 
Instance details

Defined in Test.Main.Internal

Generic ProcessResult Source # 
Instance details

Defined in Test.Main.Internal

Associated Types

type Rep ProcessResult :: Type -> Type #

type Rep ProcessResult Source # 
Instance details

Defined in Test.Main.Internal

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" main
edcba

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")] main
Nothing
Just "new_value"
>>> main
Just "value_to_unset"
Just "value_to_overwrite"

Re-export from System.Environment

withArgs :: [String] -> IO a -> IO a #

withArgs args act - while executing action act, have getArgs return args.

Re-export from System.Exit

data ExitCode #

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 
Instance details

Defined in GHC.IO.Exception

Ord ExitCode 
Instance details

Defined in GHC.IO.Exception

Read ExitCode 
Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

type Rep ExitCode 
Instance details

Defined in GHC.IO.Exception

type Rep ExitCode = D1 (MetaData "ExitCode" "GHC.IO.Exception" "base" False) (C1 (MetaCons "ExitSuccess" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ExitFailure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))