| Safe Haskell | None |
|---|
Test.Proctest
Contents
Description
An IO library for testing interactive command line programs.
Read this first:
- Tests using Proctests need to be compiled with
-threadedfor not blocking on process spawns. - Beware that the Haskell GC closes process
Handles after their last use. If you don't want to be surprised by this, usehClosewhere you want them to be closed (convenience:closeHandles). - Make sure handle buffering is set appropriately.
runsetsLineBufferingby default. Change it withsetBufferingorhSetBuffering. - 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"
- asUtf8 :: ByteString -> Text
- asUtf8Str :: ByteString -> String
- run :: FilePath -> [String] -> IO (Handle, Handle, Handle, ProcessHandle)
- terminateProcesses :: [ProcessHandle] -> IO ()
- closeHandles :: [Handle] -> IO ()
- data Timeout = NoTimeout
- data InvalidTimeoutError
- mkTimeoutUs :: Integer -> Timeout
- mkTimeoutMs :: Integral a => a -> Timeout
- mkTimeoutS :: Integral a => a -> Timeout
- seconds :: Float -> Timeout
- data TimeoutException
- 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 -> TextSource
Treats a ByteString as UTF-8 decoded Text.
asUtf8Str :: ByteString -> StringSource
Treats a ByteString as UTF-8 decoded String.
Running and stopping programs
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.
terminateProcesses :: [ProcessHandle] -> IO ()Source
Terminates all processes in the list.
closeHandles :: [Handle] -> IO ()Source
Closes all handles in the list.
Timeouts
data InvalidTimeoutError Source
An error to be thrown if something is to be converted into timeout
that does not fit into Int.
mkTimeoutUs :: Integer -> TimeoutSource
mkTimeoutMs :: Integral a => a -> TimeoutSource
mkTimeoutS :: Integral a => a -> TimeoutSource
Communicating with programs
data TimeoutException Source
Exception to be thrown when a program did not terminate within the expected time.
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