Copyright | (c) Tim Watson, Jeff Epstein 2013 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | Tim Watson |
Stability | experimental |
Portability | non-portable (requires concurrency) |
Safe Haskell | None |
Language | Haskell98 |
This module provides basic building blocks for testing Cloud Haskell programs.
- type TestResult a = MVar a
- data Ping = Ping
- ping :: ProcessId -> Process ()
- shouldBe :: a -> Matcher a -> Process ()
- shouldMatch :: a -> Matcher a -> Process ()
- shouldContain :: (Show a, Eq a) => [a] -> a -> Process ()
- shouldNotContain :: (Show a, Eq a) => [a] -> a -> Process ()
- expectThat :: a -> Matcher a -> Process ()
- synchronisedAssertion :: Eq a => String -> LocalNode -> a -> (TestResult a -> Process ()) -> MVar () -> Assertion
- data TestProcessControl
- startTestProcess :: Process () -> Process ProcessId
- runTestProcess :: Process () -> Process ()
- testProcessGo :: ProcessId -> Process ()
- testProcessStop :: ProcessId -> Process ()
- testProcessReport :: ProcessId -> Process ()
- delayedAssertion :: Eq a => String -> LocalNode -> a -> (TestResult a -> Process ()) -> Assertion
- assertComplete :: Eq a => String -> MVar a -> a -> IO ()
- data Logger
- newLogger :: IO Logger
- putLogMsg :: Logger -> String -> Process ()
- stopLogger :: Logger -> IO ()
- tryRunProcess :: LocalNode -> Process () -> IO ()
- tryForkProcess :: LocalNode -> Process () -> IO ProcessId
- noop :: Process ()
- stash :: TestResult a -> a -> Process ()
Documentation
type TestResult a = MVar a Source
A mutable cell containing a test result.
A simple Ping
signal
shouldMatch :: a -> Matcher a -> Process () Source
shouldContain :: (Show a, Eq a) => [a] -> a -> Process () Source
shouldNotContain :: (Show a, Eq a) => [a] -> a -> Process () Source
expectThat :: a -> Matcher a -> Process () Source
synchronisedAssertion :: Eq a => String -> LocalNode -> a -> (TestResult a -> Process ()) -> MVar () -> Assertion Source
data TestProcessControl Source
Control signals used to manage test processes
startTestProcess :: Process () -> Process ProcessId Source
Starts a test process on the local node.
runTestProcess :: Process () -> Process () Source
Runs a test process around the supplied proc
, which is executed
whenever the outer process loop receives a Go
signal.
testProcessGo :: ProcessId -> Process () Source
Tell a test process to continue executing
testProcessStop :: ProcessId -> Process () Source
Tell a test process to stop (i.e., terminate
)
testProcessReport :: ProcessId -> Process () Source
Tell a test process to send a report (message) back to the calling process
delayedAssertion :: Eq a => String -> LocalNode -> a -> (TestResult a -> Process ()) -> Assertion Source
Run the supplied testProc
using an MVar
to collect and assert
against its result. Uses the supplied note
if the assertion fails.
assertComplete :: Eq a => String -> MVar a -> a -> IO () Source
Takes the value of mv
(using takeMVar
) and asserts that it matches a
Create a new Logger.
Logger uses a TQueue
to receive and process messages on a worker thread.
stopLogger :: Logger -> IO () Source
Stop the worker thread for the given Logger
tryRunProcess :: LocalNode -> Process () -> IO () Source
stash :: TestResult a -> a -> Process () Source