Unit testing environment for SWI-Prolog and SICStus Prolog. For usage,
please visit https://www.swi-prolog.org/pldoc/package/plunit.
set_test_options(+Options)- Specifies how to deal with test suites. Defined options are:
- load(+Load)
- Whether or not the tests must be loaded. Values are
never, always, normal (only if not optimised)
- run(+When)
- When the tests are run. Values are
manual, make
or make(all).
- format(+Mode)
- Currently one of
tty or log. tty uses terminal
control to overwrite successful tests, allowing the
user to see the currently running tests and output
from failed tests. This is the default of the output
is a tty. log prints a full log of the executed
tests and their result and is intended for non-interactive
usage.
- output(+When)
- If
always, emit all output as it is produced, if never,
suppress all output and if on_failure, emit the output
if the test fails.
- show_blocked(+Bool)
- Show individual blocked tests during the report.
- occurs_check(+Mode)
- Defines the default for the
occurs_check flag during
testing.
- cleanup(+Bool)
- If
true (default =false), cleanup report at the end
of run_tests/1. Used to improve cooperation with
memory debuggers such as dmalloc.
- jobs(Num)
- Number of jobs to use for concurrent testing. Default
is one, implying sequential testing.
- timeout(+Seconds)
- Set timeout for each individual test. This acts as a
default that may be overuled at the level of units or
individual tests. A timeout of 0 or negative is handled
as inifinite.
loading_tests[private]- True if tests must be loaded.
begin_tests(+UnitName:atom) is det
begin_tests(+UnitName:atom, Options) is det- Start a test-unit. UnitName is the name of the test set. the
unit is ended by :-
end_tests(UnitName).
end_tests(+Name) is det- Close a unit-test module.
- To be done
- - Run tests/clean module?
- - End of file?
make_unit_module(+Name, -ModuleName) is det[private]
unit_module(+Name, -ModuleName) is det[private]
expand_test(+Name, +Options, +Body, -Clause) is det[private]- Expand
test(Name, Options) :- Body into a clause for
'unit test'/4 and 'unit body'/2.
expand(+Term, -Clauses) is semidet[private]
valid_options(:Pred, +Options) is det[private]- Verify Options to be a list of valid options according to
Pred.
- Errors
- -
type_error or instantiation_error.
test_option(+Option) is semidet[private]- True if Option is a valid option for
test(Name, Options).
test_option(+Option) is semidet[private]- True if Option is a valid option for :-
begin_tests(Name,
Options).
reify_tmo(:Goal, -Result, +Options) is det[private]
reify(:Goal, -Result) is det[private]- Call Goal and unify Result with one of
true, false or
throw(E).
capture_output(:Goal, -Output) is semidet[private]
capture_output(:Goal, -Output, +Options) is semidet[private]-
- Arguments:
-
| Output | - is a pair Msgs-String, where Msgs is a boolean that
is true if there were messages that require a non-zero exit status
and Output contains the output as a string. |
got_messages(:Goal, -Result)[private]
run_tests is semidet
run_tests(+TestSet) is semidet
run_tests(+TestSet, +Options) is semidet- Run tests and report about the results. The predicate run_tests/0
runs all known tests that are not blocked. The predicate run_tests/1
takes a specification of tests to run.
The predicate run_tests/2 is synchronized. Concurrent testing may
be achieved using the relevant options. See
set_test_options/1. Options are passed to set_test_options/1. In
addition the following options are processed:
- summary(-Summary)
- Unify Summary do a dict holding the keys below. The value of
these keys is an integer describing the number of tests. If
this option is given, run_tests/2 does not fail if some tests
failed.
- total
- passed
- failed
- timeout
- blocked
- Arguments:
-
| TestSet | - is either a single specification or a list of
specifications. Each single specification is either the name of a
test-unit or a term <test-unit>:<test>, denoting a single test
within a unit. If TestSet is all, all known tests are executed. |
report_and_cleanup(+Ref, +Time, +Options)[private]- Undo changes to the environment (trapping assertions), report the
results and cleanup.
- run_units_and_check_errors(+Units, +Options) is semidet[private]
- Run all test units and succeed if all tests passed.
runnable_tests(+Spec, -Plan) is det[private]- Change a Unit+Test spec into a plain
Unit:Tests lists, where
blocked tests or tests whose condition fails are already removed.
Each test in Tests is a term @(Test,Line), which serves as a
unique identifier of the test.
count_tests(+Units0, -Units, -Count) is det[private]- Count the number of tests to run. A
forall(Generator, Test) counts
as a single test. During the execution, the concrete tests of the
forall are considered "sub tests".
run_unit(+Unit) is det[private]- Run a single test unit. Unit is a term Unit:Tests, where Tests is a
list of tests to run.
run_tests_in_files(+Files:list) is det[private]- Run all test-units that appear in the given Files.
make_run_tests(+Files)[private]- Called indirectly from make/0 after Files have been reloaded.
run_test(+Unit, +Test) is det[private]- Run a single test.
run_test(+Unit, +Name, +Line, +UnitOptions, +Options, +Body)[private]- Deals with
forall(Generator, Test)
run_test_once6(+Unit, +Name, +Progress, +Line, +UnitOptions, +Options, +Body)[private]- Inherit the
timeout and occurs_check option (Global -> Unit -> Test).
run_test_once(+Unit, +Name, +Progress, +Line, +Options, +Body)[private]- Deal with occurs_check, i.e., running the test multiple times with different
unification settings wrt. the occurs check.
report_result(+Result, +Progress, +Output, +Options) is det[private]
run_test_6(+Unit, +Name, +Line, +Options, :Body, -Result) is det[private]- 6th step of the tests. Deals with tests that must be ignored
(blocked, conditions fails), setup and cleanup at the test level.
Result is one of:
- failure(Unit, Name, Line, How, Time)
- How is one of:
- succeeded
- Exception
time_limit_exceeded(Limit)
cmp_error(Cmp, E)
wrong_answer(Cmp)
- failed
- no_exception
wrong_error(Expect, E)
wrong_answer(Expected, Bindings)
- success(Unit, Name, Line, Determinism, Time)
- setup_failed(Unit, Name, Line)
run_test_7(+Unit, +Name, +Line, +Options, :Body, -Result) is det[private]- This step deals with the expected outcome of the test. It runs
the actual test and then compares the result to the outcome.
There are two main categories: dealing with a single result and
all results.
- non_det_test(+Expected, +Unit, +Name, +Line, +Options, +Body, -Result)[private]
- Run tests on non-deterministic predicates.
result_vars(+Expected, -Vars) is det[private]- Create a term
v(V1, ...) containing all variables at the left
side of the comparison operator on Expected.
nondet_compare(+Expected, +Bindings, +Unit, +Name, +Line) is semidet[private]- Compare list/set results for non-deterministic predicates.
- bug
- - Sort should deal with equivalence on the comparison
operator.
- To be done
- - Properly report errors
cmp(+CmpTerm, -Left, -Op, -Right) is det[private]
call_det(:Goal, -Det) is nondet[private]- True if Goal succeeded. Det is unified to
true if Goal left
no choicepoints and false otherwise.
match_error(+Expected, +Received) is semidet[private]- True if the Received errors matches the expected error. Matching
is based on subsumes_term/2.
setup(+Module, +Context, +Options) is semidet[private]- Call the setup handler and fail if it cannot run for some
reason. The condition handler is similar, but failing is not
considered an error. Context is one of
- unit(Unit)
- If it is the setup handler for a unit
- test(Unit, Name, Line)
- If it is the setup handler for a test
condition(+Module, +Context, +Options) is semidet[private]- Evaluate the test or test unit condition.
call_ex(+Module, +Goal)[private]- Call Goal in Module after applying goal expansion.
cleanup(+Module, +Options) is det[private]- Call the cleanup handler and succeed. Failure or error of the
cleanup handler is reported, but tests continue normally.
failure(+Unit, +Name, +Progress, +Line, +How, +Time, +Output, +Options) is det[private]- Test failed. Report the error.
assert_cyclic(+Term) is det[private]- Assert a possibly cyclic unit clause. Current SWI-Prolog
assert/1 does not handle cyclic terms, so we emulate this using
the recorded database.
- To be done
- - Implement cycle-safe assert and remove this.
setup_jobs(+Count) is det[private]- Setup threads for concurrent testing.
job_wait(?Unit) is det[private]- Wait for all test jobs to finish.
begin_test(+Unit, +Test, +Line, +Progress) is det[private]
end_test(+Unit, +Test, +Line, +Progress) is det[private]- Maintain running/5 and report a test has started/is ended using
a
silent message:
plunit(begin(Unit:Test, File:Line, Progress))
plunit(end(Unit:Test, File:Line, Progress))
- See also
- - message_hook/3 for intercepting these messages
running_tests is det- Print the currently running test.
current_test(?Unit, ?Test, ?Line, ?Body, ?Options) is nondet- True when a test with the specified properties is loaded.
current_test_unit(?Unit, ?Options) is nondet- True when a Unit is a current unit test declared with Options.
test_summary(?Unit, -Summary) is det[private]- True when Summary is a dict that reports the main statistics
about the executed tests.
report(+Time, +Options) is det[private]- Print a summary of the tests that ran.
test_report(+What) is det- Produce reports on test results after the run. Currently only
supports
fixme for What.
unit_file(+Unit, -File) is det[private]
- unit_file(?Unit, ?File) is nondet[private]
- True when the test unit Unit is defined in File.
load_test_files(+Options) is det- Load .plt test-files related to loaded source-files. Options is
currently ignored.
info(+Term)[private]- Runs
print_message(Level, Term), where Level is one of silent or
informational (default).
progress(+UnitTest, +Progress, +Result, +Time) is det[private]- Test Unit:Name completed in Time. Result is the result and is one of
- passed
- failed
- assertion
- nondet
- fixme(passed)
- fixme(nondet)
- fixme(failed)
- forall(end,Nth,FTotal)
- Pseudo result for completion of a
forall(Gen,Test) set. Mapped
to forall(FTotal, FFailed)
test_name_summary(+Term, +MaxLen, -Summary) is det[private]- Given the test id, generate string that summarizes this in MaxLen
characters.
progress_string(+Progress, -S) is det[private]- True when S is a string representation for the test progress.
progress_tag(+Status, -Tag, -Keep, -Style) is det[private]- Given a progress status, determine the status tag, whether we must
preserve the line and the Style we must use to print the status
line.
jobs_redraw is det[private]- Redraw the job window.
job_format(+Style, +Fmt, +Args) is det[private]
job_format(+Job, +Style, +Fmt, +Args, +Save) is det[private]- Point should be below the status window. Format Fmt+Args in the
line Job using Style and return to the position below the window.
job_finish(+Style, +Fmt, +Args) is det[private]
job_finish(+Job, +Style, +Fmt, +Args) is det[private]- Complete the status line for Job. This redraws the original
status line when we are using a job window.
- feedback is semidet[private]
- provide feedback using the
tty format, which reuses the current
output line if the test is successful.
user:message_hook(+Severity, +Message, +Lines) is semidet[multifile]- Redefine printing some messages. It appears SICStus has no way
to get multiple messages at the same line, so we roll our own.
As there is a lot pre-wired and checked in the SICStus message
handling we cannot reuse the lines. Unless I miss something ...