1:- module(plunit_assert, [
2 assert_equals/2,
3 assert_not_equals/2,
4 assert_gt/2,
5 assert_gte/2,
6 assert_lt/2,
7 assert_lte/2,
8 assert_is/2,
9 assert_is_not/2,
10 assert_exception/1,
11 assert_false/1,
12 assert_true/1,
13 assert_unbound/1,
14 assert_not_unbound/1,
15 assert_in/2,
16 assert_not_in/2,
17 assert_type/2,
18 assert_not_type/2,
19 % Meta stuff - not really part of the plunit_assert API
20 assert_test_fails/1,
21 assert_test_passes/1
22]).
30:- dynamic prolog:assertion_failed/2.
39assert_true(Goal) :-
40 assertion(Goal).
48assert_false(Goal) :-
49 assertion(\+ Goal).
57assert_equals(A, B) :-
58 assertion(A == B; A =:= B).
67assert_not_equals(A, B) :-
68 assertion(A \= B).
Uses ==/2 to check for term identity, which means it compares the terms A and B structurally, including the functor and arity (number of arguments) of the terms and the equality of each corresponding argument. Thus, succeeds if A and B are identical terms, without attempting to unify variables or perform any arithmetic evaluations
84assert_is(A, B) :-
85 assertion(A == B).
94assert_is_not(A, B) :-
95 assertion(A \== B).
103assert_exception(Goal) :-
104 setup_call_cleanup(
105 nb_setval(got_exception, false),
106 catch(Goal, _, nb_setval(got_exception, true)),
107 true
108 ),
109 nb_getval(got_exception, Gotex),
110 ( -> true; assertion(false) ).
This is analogous to isNull()
or isNone()
in other xUnit implementations
120assert_unbound(Var) :-
121 assertion(var(Var)).
129assert_not_unbound(Var) :-
130 assertion(\+ var(Var)).
This checks for list/set membership, and also whether Var is a valid dictionary key in Collection
143assert_in(Var, Collection) :-
144 assertion((
145 member(Var, Collection) ;
146 get_dict(Var, Collection, _)
147 )).
This checks for list/set membership, and also whether Var is a valid dictionary key in Collection
159assert_not_in(Var, Collection) :-
160 assertion(\+ (
161 member(Var, Collection) ;
162 ( is_dict(Collection), get_dict(Var, Collection, _) )
163 )).
Supported types are: number, integer, float, atom, compound, list, dict
175assert_type(Term, float) :- assertion(float(Term)). 176assert_type(Term, integer) :- assertion(integer(Term)). 177assert_type(Term, number) :- assertion(number(Term)). 178assert_type(Term, atom) :- assertion(atom(Term)). 179assert_type(Term, compound) :- assertion(compound(Term)). 180assert_type(Term, list) :- assertion(is_list(Term)). 181assert_type(Term, dict) :- assertion(is_dict(Term)).
190assert_not_type(Term, float) :- assertion(\+ float(Term)). 191assert_not_type(Term, integer) :- assertion(\+ integer(Term)). 192assert_not_type(Term, number) :- assertion(\+ number(Term)). 193assert_not_type(Term, atom) :- assertion(\+ atom(Term)). 194assert_not_type(Term, compound) :- assertion(\+ compound(Term)). 195assert_not_type(Term, list) :- assertion(\+ is_list(Term)). 196assert_not_type(Term, dict) :- assertion(\+ is_dict(Term)).
204assert_gt(A, B) :-
205 assertion(A > B).
213assert_lt(A, B) :-
214 assertion(A < B).
222assert_gte(A, B) :-
223 assertion(A >= B).
231assert_lte(A, B) :- 232 assertion(A =< B). 233 234 235% meta-tests ------------------------------------------------------------------
243assert_test_fails(Goal) :-
244 setup_call_cleanup(
245 asserta((prolog:assertion_failed(Reason, Somegoal) :-
246 pa_assertion_failed(Reason, Somegoal),
247 nb_setval(assertion_failed, true)),
248 Ref),
249 (nb_setval(assertion_failed, false),
250 catch(Goal, _, true),
251 nb_getval(assertion_failed, Failed)),
252 erase(Ref)
253 ),
254 Failed == true.
261assert_test_passes(Goal) :- 262 . 263 264pa_assertion_failed(_, _) :- 265 %writeln('Captured test fail'), 266 !
The test API for plunit_assert
A unit testing library for Prolog, providing an expressive xUnit-like API for PlUnit.