Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides functions and a TestControl effect for implmenting
unit tests with Converse
.
- type TestControl = Exc TestExitStatus
- runTestControl :: (String -> Eff r a) -> Eff r a -> Eff (TestControl ': r) a -> Eff r a
- runTestControlData :: Eff (TestControl ': r) a -> Eff r (Either String (Maybe a))
- runTestControlData_ :: Eff (TestControl ': r) a -> Eff r (Either String ())
- runTestControlError :: Eff (TestControl ': r) () -> Eff r ()
- data TestExitStatus
- fulfilled :: Member TestControl r => Eff r a
- throwUnexpected :: (ShowP f, Member TestControl r) => f a -> Eff r b
- throwExpecting :: (ShowP f, Member TestControl r) => String -> f a -> Eff r b
- failure :: (Member TestControl r, Show v, ShowP f) => String -> Eff (Converse f r v ': r) a
- expect :: Member TestControl r => (forall a. f a -> Eff r (a, b)) -> Eff (Converse f r v ': r) b
- collect :: (forall a. f a -> Eff r (Maybe (a, b))) -> Eff (Converse f r v ': r) [b]
- stub :: Member TestControl r => (forall b. f b -> Eff r b) -> Eff (Converse f r v ': r) ()
- stubs :: (forall b. f b -> Eff r (Maybe b)) -> Eff (Converse f r v ': r) ()
- result :: (Member TestControl r, ShowP f) => Eff (Converse f r v ': r) v
- result_ :: Member TestControl r => Eff (Converse f r v ': r) v
- converse :: (forall x. f x -> Eff r (Maybe x, b)) -> (v -> Eff r b) -> Eff (Converse f r v ': r) b
- spy :: (Monad m, Monoid mm) => a -> m (mm, a)
Documentation
type TestControl = Exc TestExitStatus Source #
An effect for terminating the test when either the test has failed, or the goal of the test has been fulfilled without problems but need not continue the normal flow of execution.
:: (String -> Eff r a) | On failure |
-> Eff r a | On fulfill |
-> Eff (TestControl ': r) a | The test, with |
-> Eff r a | The test, without |
Handler for TestControl
effects. Runs the computation (a test) and
- calls into the first argument on failure,
- calls into the second argument on
fulfilled
or - returns the value produced by the test (often just '()').
Note that the r
parameter determines what (computational or I/O)
effects are required/allowed for running the test. This makes it
possible to write pure tests, tests that explore all branches of
nondeterministic choices, tests that read from files dynamically,
etc.
runTestControlData :: Eff (TestControl ': r) a -> Eff r (Either String (Maybe a)) Source #
Runs a test, letting it terminate early, as appropriate.
Like runTestControl
but for those who like to pattern match instead.
runTestControlData_ :: Eff (TestControl ': r) a -> Eff r (Either String ()) Source #
Runs a test, letting it terminate early, as appropriate.
Like runTestControlData
but will not return a value from the test.
runTestControlError :: Eff (TestControl ': r) () -> Eff r () Source #
Runs a test, letting it terminate early, as appropriate.
Throws an error with error
on failure.
data TestExitStatus Source #
Interruption of a test run.
TestFulfilled | The goal of the test was accomplished and the test need not continue. |
TestFailed String | A problem was detected |
Controlling the test
fulfilled :: Member TestControl r => Eff r a Source #
The goal of the test has been accomplished. Stops further execution of the test. Results in a successful test result.
throwUnexpected :: (ShowP f, Member TestControl r) => f a -> Eff r b Source #
Throw an unexpected event error
:: (ShowP f, Member TestControl r) | |
=> String | Noun phrase describing expectation |
-> f a | Unexpected event |
-> Eff r b |
Terminates test as a failure by showing the expectation and the event.
:: (Member TestControl r, Show v, ShowP f) | |
=> String | Reason for test failure |
-> Eff (Converse f r v ': r) a |
Terminates the test with error, showing provided reason and next event.
Interacting with the test subject
expect :: Member TestControl r => (forall a. f a -> Eff r (a, b)) -> Eff (Converse f r v ': r) b Source #
When an event occurs, provide a value a
for the test subject and a value b
for the test script.
collect :: (forall a. f a -> Eff r (Maybe (a, b))) -> Eff (Converse f r v ': r) [b] Source #
Provide a value to the test subject, if and as long as matching events occur. Matching stops when Nothing is returned from the passed function.
Returns the number of events that have been matched.
stub :: Member TestControl r => (forall b. f b -> Eff r b) -> Eff (Converse f r v ': r) () Source #
When an event occurs, provide a value to the test subject.
Like expect
, but does not return a value to the test script.
stubs :: (forall b. f b -> Eff r (Maybe b)) -> Eff (Converse f r v ': r) () Source #
Like collect
, but simpler because it does not return a value to
the test script.
result :: (Member TestControl r, ShowP f) => Eff (Converse f r v ': r) v Source #
Retrieve the result of the program. Fails if an effect of type
f
is still pending.
result_ :: Member TestControl r => Eff (Converse f r v ': r) v Source #
Like result
but more generic because it does not attempt to
show the unexpected effect in the error message.
:: (forall x. f x -> Eff r (Maybe x, b)) | Handle an effect emitted by the normal computation. This may produce other effects in |
-> (v -> Eff r b) | Handle the case where the normal computation has completed and returned a value of type |
-> Eff (Converse f r v ': r) b | A computation that should run in the handling computation. |
Called by the handling computation, to interact with the normal
computation. (See module description for definitions)
This is the most general way of interacting with the normal computation, reflecting the constructor of the Converse
type.