Prolog Unit Tests
All Application Manual Name SummaryHelp

  • Documentation
    • Reference manual
    • Packages
      • Prolog Unit Tests
        • Introduction
        • A Unit Test box
          • Test Unit options
          • Writing the test body
        • Using separate test files
        • Running the test-suite
        • Tests and production systems
        • Controlling the test suite
        • Auto-generating tests
        • Portability of the test-suite
        • Motivation of choices

2 A Unit Test box

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:

blocked(+Reason:atom)
The test is currently disabled. Tests are flagged as blocked if they cannot be run for some reason. E.g. they crash Prolog, they rely on some service that is not available, they take too much resources, etc. Tests that fail but do not crash, etc. should be flagged using fixme(Fixme).
fixme(+Reason:atom)
Similar to 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.
condition(:Goal)
Pre-condition for running the test. If the condition fails the test is skipped. The condition can be used as an alternative to the setup option. The only difference is that failure of a condition skips the test and is considered an error when using the setup option.
cleanup(:Goal)
Goal is always called after completion of the test-body, regardless of whether it fails, succeeds or throws an exception. This option or call_cleanup/2 must be used by tests that require side-effects that must be reverted after the test completes. Goal may share variables with the test body.
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(_).
setup(:Goal)
Goal is run before the test-body. Typically used together with the cleanup option to create and destroy the required execution environment.
forall(:Generator)
Run the same test for each solution of Generator. Each run invokes the setup and cleanup handlers. This can be used to run the same test with different inputs. If an error occurs, the test is reported as name (forall bindings = <vars> ), where <vars> indicates the bindings of variables in Generator.
true(AnswerTerm Cmp Value)
Body should succeed deterministically. If a choicepoint is left open, a warning is printed to STDERR ("Test succeeded with choicepoint"). That warning can be suppressed by adding the 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).
AnswerTerm Cmp Value(E)
quivalent to true(AnswerTerm Cmp Value) if Cmp is one of the comparison operators given above.
fail
Body must fail.
throws(Error)
Body must throw Error. The thrown error term is matched against term Error using subsumes_term(Error, ThrownError). I.e., the thrown error must be more specific than the specified Error. See subsumes_term/2.
error(Error)
Body must throw error(Error, _Context). See keyword throws (as well as predicate throw/1 and library(error)) for details.
all(AnswerTerm Cmp Instances)
Similar to 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 ).
set(AnswerTerm Cmp Instances)
Similar to 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 ==.
nondet
If this keyword appears in the option list, non-deterministic success of the body is not considered an error.
occurs_check(Mode)
Run the test in a particular occurs check mode. Mode is one of false (default), true or error. See the Prolog flag occurs_check for details.

2.1 Test Unit options

begin_tests(+Name)
Start named test-unit. Same as begin_tests(Name, []).
begin_tests(+Name, +Options)
Start named test-unit with options. Options provide conditional processing, setup and cleanup similar to individual tests (second argument of test/2 rules).

Defined options are:

blocked(+Reason)
Test-unit has been blocked for the given Reason.
condition(:Goal)
Executed before executing any of the tests. If Goal fails, the test of this unit is skipped.
setup(:Goal)
Executed before executing any of the tests.
cleanup(:Goal)
Executed after completion of all tests in the unit.
occurs_check(+Mode)
Specify default for subject-to-occurs-check mode. See section 2 for details on the occurs_check option.

2.2 Writing the test body

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.

2.2.1 Testing deterministic 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]).

2.2.2 Testing semi-deterministic predicates

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]).

2.2.3 Testing non-deterministic predicates

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]).

2.2.4 Testing error conditions

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.

2.2.5 One body with multiple tests using assertions

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:

  • Confirm that multiple claims hold. Where multiple claims about variable bindings can be tested using the == option in the test header, arbitrary boolean tests, notably about the state of the database, are harder to combine. Simply adding them in the body of the test has two disadvantages: it is less obvious to distinguish the tested code from the test and if one of the tests fails there is no easy way to find out which one.
  • Testing‘scenarios’or sequences of actions. If one step in such a sequence fails there is again no easy way to find out which one. By inserting assertions into the sequence this becomes obvious.

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