Tests are written in pure Prolog and enclosed within the directives
begin_tests/1,2
and end_tests/1.
They can be embedded inside a normal source module, or be placed in a
separate test-file that loads the files to be tested. Code inside a test
box is normal Prolog code. The entry points are defined by rules using
the head test(Name)
or
test(Name, Options)
, where Name is a ground term
and
Options is a list describing additional properties of the
test. Here is a very simple example:
:- begin_tests(lists). :- use_module(library(lists)). test(reverse) :- reverse([a,b], [b,a]). :- end_tests(lists).
The optional second argument of the test-head defines additional processing options. Defined options are:
fixme(Fixme)
.blocked(Reason)
, but the test it executed
anyway. If it fails, a -
is printed instead of
the .
character. If it passes a +
and if it passes with a choicepoint, !
. A
summary is printed at the end of the test run and the goal
test_report(fixme)
can be used to get details.setup
option. The only difference is that failure of a condition skips the
test and is considered an error when using the setup
option.create_file(Tmp) :- tmp_file(plunit, Tmp), open(Tmp, write, Out), write(Out, 'hello(World).\n'), close(Out). test(read, [ setup(create_file(Tmp)), cleanup(delete_file(Tmp)) ]) :- read_file_to_terms(Tmp, Terms, []), Term = hello(_).
cleanup
option to create and destroy the required
execution environment.name (forall bindings =
<vars> )
,
where
<vars> indicates the bindings of variables in Generator.nondet
keyword. AnswerTerm
is compared to Value using the comparison operator Cmp. Cmp
is typically one of =/2, ==/2, =:=/2 or =@=/2,1The
=@= predicate (denoted structural equivalence) is the same as variant/2
in SICStus. but any test can be used. This is the same as
inserting the test at the end of the conjunction, but it allows the test
engine to distinguish between failure of copy_term/2
and producing the wrong value. Multiple variables must be combined in an
arbitrary compound term. E.g. A1-A2 == v1-v2
test(copy, [ true(Copy =@= hello(X,X)) ]) :- copy_term(hello(Y,Y), Copy).
true(AnswerTerm Cmp Value)
if Cmp
is one of the comparison operators given above.subsumes_term(Error,
ThrownError)
. I.e., the thrown error must be more specific than
the specified Error. See
subsumes_term/2.error(Error, _Context)
. See keyword throws
(as well as predicate throw/1
and library(error)) for details.true(AnswerTerm Cmp Values)
, but used for
non-deterministic predicates. Each element is compared using Cmp.
Order matters. For example:
test(or, all(X == [1,2])) :- ( X = 1 ; X = 2 ).
all(AnswerTerm Cmp Instances)
, but before
testing both the bindings of AnswerTerm and Instances
are sorted using
sort/2. This
removes duplicates and places both sets in the same order.2The
result is only well-defined of Cmp is ==
.false
(default), true
or error
. See the Prolog flag occurs_check
for details.
begin_tests(Name, [])
.Defined options are:
occurs_check
option.
The test-body is ordinary Prolog code. Without any options, the body
must be designed to succeed deterministically. Any other result
is considered a failure. One of the options fail
, true
,
throws
, all
or set
can be used to
specify a different expected result. See section
2 for details. In this section we illustrate typical test-scenarios
by testing SWI-Prolog built-in and library predicates.
Deterministic predicates are predicates that must succeed exactly once and, for well behaved predicates, leave no choicepoints. Typically they have zero or more input- and zero or more output arguments. The test goal supplies proper values for the input arguments and verifies the output arguments. Verification can use test-options or be explicit in the body. The tests in the example below are equivalent.
test(add) :- A is 1 + 2, A =:= 3. test(add, [true(A =:= 3)]) :- A is 1 + 2.
The test engine verifies that the test-body does not leave a choicepoint. We illustrate that using the test below:
test(member) :- member(b, [a,b,c]).
Although this test succeeds, member/2 leaves a choicepoint which is reported by the test subsystem. To make the test silent, use one of the alternatives below.
test(member) :- member(b, [a,b,c]), !. test(member, [nondet]) :- member(b, [a,b,c]).
Semi-deterministic predicates are predicates that either fail or
succeed exactly once and, for well behaved predicates, leave no
choicepoints. Testing such predicates is the same as testing
deterministic predicates. Negative tests must be specified using the
option
fail
or by negating the body using \+/1
.
test(is_set) :- \+ is_set([a,a]). test(is_set, [fail]) :- is_set([a,a]).
Non-deterministic predicates succeed zero or more times. Their
results are tested either using findall/3
or setof/3
followed by a value-check or using the all
or set
options. The following are equivalent tests:
test(member) :- findall(X, member(X, [a,b,c]), Xs), Xs == [a,b,c]. test(member, all(X == [a,b,c])) :- member(X, [a,b,c]).
Error-conditions are tested using the option throws(Error)
or by wrapping the test in a catch/3.
The following tests are equivalent:
test(div0) :- catch(A is 1/0, error(E, _), true), E =@= evaluation_error(zero_divisor). test(div0, [error(evaluation_error(zero_divisor))]) :- A is 1/0.
PlUnit is designed to cooperate with the assertion/1 test provided by library(debug).3This integration was suggested by Günter Kniesel. If an assertion fails in the context of a test, the test framework reports this and considers the test failed, but does not trap the debugger. Using assertion/1 in the test-body is attractive for two scenarios:
Below is a simple example, showing two failing assertions. The first line of the failure message gives the test. The second reports the location of the assertion.4If known. The location is determined by analysing the stack. The second failure shows a case where this does not work because last-call optimization has already removed the context of the test-body. If the assertion call originates from a different file this is reported appropriately. The last line gives the actually failed goal.
:- begin_tests(test). test(a) :- A is 2^3, assertion(float(A)), assertion(A == 9). :- end_tests(test).
?- run_tests. % PL-Unit: test ERROR: /home/jan/src/pl-devel/linux/t.pl:5: test a: assertion at line 7 failed Assertion: float(8) ERROR: /home/jan/src/pl-devel/linux/t.pl:5: test a: assertion failed Assertion: 8==9 . done % 2 assertions failed