Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Proctest
Description
An IO library for testing interactive command line programs.
Read this first:
- Tests using Proctests need to be compiled with
-threaded
for not blocking on process spawns. - Beware that the Haskell GC closes process
Handle
s after their last use. If you don't want to be surprised by this, usehClose
where you want them to be closed (convenience:closeHandles
). Really do this for EVERY process you create, the behaviour of a program writing to a closed handle is undefined. For example,getProcessExitCode
run on such a program somtimes seems to always returnExitSuccess
, no matter what the program actually does. - Make sure handle buffering is set appropriately.
run
setsLineBuffering
by default. Change it withsetBuffering
orhSetBuffering
. - Do not run the program in a shell (e.g.
runInteractiveCommand
) if you want to be able to terminate it reliably (terminateProcess
). Use processes without shells (runInteractiveProcess
) instead.
Example:
Let's say you want to test an interactive command line program like cat
,
and integrate your test into a test framework like Test.HSpec,
using Test.HSpec.HUnit for the IO parts (remember that Proctest is stateful IO).
main = hspec $ describe "cat" $ do it "prints out what we put in" $ do -- Start up the program to test (hIn, hOut, hErr, p) <- run "cat" [] -- Make sure buffering doesn't prevent us from reading what we expect -- ('run' sets LineBuffering by default) setBuffering NoBuffering [hIn, hOut] -- Communicate with the program hPutStrLn hIn "hello world" -- Define a convenient wrapper around 'waitOutput'. -- -- It specifies how long we have to wait -- (malfunctioning programs shall not block automated testing for too long) -- and how many bytes we are sure the expected response fits into -- (malfunctioning programs shall not flood us with garbage either). let catWait h = asUtf8Str <$> waitOutput (seconds 0.01) 1000 h -- Wait max 10 ms, 1000 bytes -- Wait a little to allow `cat` processing the input sleep (seconds 0.00001) -- Read the response response <- catWait hOut -- Test if it is what we want (here using HUnit's 'expectEqual') response @?= "hello world\n"
Synopsis
- asUtf8 :: ByteString -> Text
- asUtf8Str :: ByteString -> String
- type ProcessHandles = (Handle, Handle, Handle, ProcessHandle)
- run :: FilePath -> [String] -> IO (Handle, Handle, Handle, ProcessHandle)
- data RunException = CommandNotFound String
- isRunning :: ProcessHandle -> IO Bool
- terminateProcesses :: [ProcessHandle] -> IO ()
- closeHandles :: [Handle] -> IO ()
- closeProcessHandles :: [ProcessHandles] -> IO ()
- data Timeout = NoTimeout
- data InvalidTimeoutError
- mkTimeoutUs :: Integer -> Timeout
- mkTimeoutMs :: Integral a => a -> Timeout
- mkTimeoutS :: Integral a => a -> Timeout
- seconds :: Double -> Timeout
- data TimeoutException
- timeoutToSystemTimeoutArg :: Timeout -> Int
- withTimeout :: Timeout -> IO a -> IO (Maybe a)
- waitOutput :: Timeout -> Int -> Handle -> IO ByteString
- waitOutputNoEx :: Timeout -> Int -> Handle -> IO (Maybe ByteString)
- setBuffering :: BufferMode -> [Handle] -> IO ()
- sleep :: Timeout -> IO ()
- module System.Exit
- module System.IO
- module System.Process
String conversion
asUtf8 :: ByteString -> Text Source #
Treats a ByteString
as UTF-8 decoded Text
.
asUtf8Str :: ByteString -> String Source #
Treats a ByteString
as UTF-8 decoded String
.
Running and stopping programs
type ProcessHandles = (Handle, Handle, Handle, ProcessHandle) Source #
Short cut. ALWAYS use the order stdin, stdout, stderr, process handle.
run :: FilePath -> [String] -> IO (Handle, Handle, Handle, ProcessHandle) Source #
Runs a program with the given arguemtns.
Returns (stdout, stderr, stdin, process)
. See runInteractiveProcess
.
Directly runs the process, does not use a shell.
Sets the 'BufferMode to LineBuffering
if successful.
Throws CommandNotFound
if the command doesn't exist.
Due to createProcess
not throwing an exception
(http://www.haskell.org/pipermail/haskell-cafe/2012-August/102824.html),
this is currently implemented by checking if the program
returns early with error code 127.
data RunException Source #
Exception to be thrown when a program could not be started.
Constructors
CommandNotFound String |
Instances
Exception RunException Source # | |
Defined in Test.Proctest Methods toException :: RunException -> SomeException # fromException :: SomeException -> Maybe RunException # displayException :: RunException -> String # | |
Show RunException Source # | |
Defined in Test.Proctest Methods showsPrec :: Int -> RunException -> ShowS # show :: RunException -> String # showList :: [RunException] -> ShowS # |
terminateProcesses :: [ProcessHandle] -> IO () Source #
Terminates all processes in the list.
closeHandles :: [Handle] -> IO () Source #
Closes all handles in the list.
closeProcessHandles :: [ProcessHandles] -> IO () Source #
Closes all file handles to all given handle-process-tuples.
Use this to make sure that handles are not closed due to garbage collection (see System.IO) while your processes are still running.
It is safe to call this on processes which have already exited.
Timeouts
A microsecond timeout, or NoTimeout
.
Constructors
NoTimeout |
data InvalidTimeoutError Source #
Instances
Exception InvalidTimeoutError Source # | |
Defined in Test.Proctest Methods toException :: InvalidTimeoutError -> SomeException # fromException :: SomeException -> Maybe InvalidTimeoutError # | |
Show InvalidTimeoutError Source # | |
Defined in Test.Proctest Methods showsPrec :: Int -> InvalidTimeoutError -> ShowS # show :: InvalidTimeoutError -> String # showList :: [InvalidTimeoutError] -> ShowS # |
mkTimeoutUs :: Integer -> Timeout Source #
mkTimeoutMs :: Integral a => a -> Timeout Source #
mkTimeoutS :: Integral a => a -> Timeout Source #
Communicating with programs
data TimeoutException Source #
Exception to be thrown when a program did not terminate within the expected time.
Instances
Exception TimeoutException Source # | |
Defined in Test.Proctest Methods toException :: TimeoutException -> SomeException # | |
Show TimeoutException Source # | |
Defined in Test.Proctest Methods showsPrec :: Int -> TimeoutException -> ShowS # show :: TimeoutException -> String # showList :: [TimeoutException] -> ShowS # |
timeoutToSystemTimeoutArg :: Timeout -> Int Source #
Converts a Timeout
milliseconds suitable to be passed into timeout
.
Arguments
:: Timeout | Timeout after which reading output will be aborted. |
-> Int | Maximum number of bytes after which reading output will be aborted. |
-> Handle | The handle to read from. |
-> IO ByteString | What was read from the handle. |
Blocking wait for output on the given handle.
Throws a TimeoutException
if the timeout is exceeded.
Based on waitOutputNoEx
.
Arguments
:: Timeout | Timeout after which reading output will be aborted. |
-> Int | Maximum number of bytes after which reading output will be aborted. |
-> Handle | The handle to read from. |
-> IO (Maybe ByteString) | What was read from the handle. |
Blocking wait for output on the given handle.
Returns Nothing
timeout is exceeded.
setBuffering :: BufferMode -> [Handle] -> IO () Source #
Sets the buffering of the all given handles to the given BufferMode
.
sleep :: Timeout -> IO () Source #
Suspends execution for the given timeout; uses threadDelay
internally.
For NoTimeout
, threadDelay will not be called.
Convenience module exports
module System.Exit
module System.IO
module System.Process