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

The test API for plunit_assert

A unit testing library for Prolog, providing an expressive xUnit-like API for PlUnit.

author
- Simon Harding <github@pointbeing.net>
license
- MIT */
   30:- dynamic prolog:assertion_failed/2.
 assert_true(+Goal) is semidet
Test that Goal succeeds and therefore is truthy
Arguments:
Goal- The goal to be tested
See also
- assertion/1
   39assert_true(Goal) :-
   40    assertion(Goal).
 assert_false(+Goal) is semidet
Test that Goal fails and therefore is falsy
Arguments:
Goal- The goal to be tested
See also
- assertion/1
   48assert_false(Goal) :-
   49    assertion(\+ Goal).
 assert_equals(+A, +B) is semidet
This is a superset of assert_is/2 and arithmetic comparison with =:=
Arguments:
A- The first of the terms to be compared
B- The second of the terms to be compared
   57assert_equals(A, B) :-
   58    assertion(A == B; A =:= B).
 assert_not_equals(+A, +B) is semidet
Test that A and B are not equal terms
Arguments:
A- The first of the terms to be compared
B- The second of the terms to be compared
See also
- assert_equals/2
   67assert_not_equals(A, B) :-
   68    assertion(A \= B).
 assert_is(+A, +B) is semidet
Test that A and B are identical terms

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

Arguments:
A- The first of the terms to be compared
B- The second of the terms to be compared
See also
- assertion/1
- ==/2
   84assert_is(A, B) :-
   85    assertion(A == B).
 assert_is_not(+A, +B) is semidet
Test that A and B are not identical terms
Arguments:
A- The first of the terms to be compared
B- The second of the terms to be compared
See also
- assert_is/2
   94assert_is_not(A, B) :-
   95    assertion(A \== B).
 assert_exception(+Goal) is semidet
Test that an exception is thrown during the invocation of Goal
Arguments:
Goal- The goal to be tested
See also
- assertion/1
  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    ( Gotex -> true; assertion(false) ).
 assert_unbound(+Var) is semidet
Test that Var is unbound

This is analogous to isNull() or isNone() in other xUnit implementations

Arguments:
Var- The variable to be tested for boundness
See also
- assertion/1
  120assert_unbound(Var) :-
  121    assertion(var(Var)).
 assert_not_unbound(+Var) is semidet
Test that Var is not unbound
Arguments:
Var- The variable to be tested for unboundness
See also
- assert_unbound/1
  129assert_not_unbound(Var) :-
  130    assertion(\+ var(Var)).
 assert_in(+Var, +Collection) is semidet
Test that Var is in Collection

This checks for list/set membership, and also whether Var is a valid dictionary key in Collection

Arguments:
Var- The needle
Collection- The haystack
See also
- assertion/1
  143assert_in(Var, Collection) :-
  144    assertion((
  145        member(Var, Collection) ;
  146        get_dict(Var, Collection, _)
  147    )).
 assert_not_in(+Var, +Collection) is semidet
Test that Var is not in Collection

This checks for list/set membership, and also whether Var is a valid dictionary key in Collection

Arguments:
Var- The needle
Collection- The haystack
See also
- assert_in/2
  159assert_not_in(Var, Collection) :-
  160    assertion(\+ (
  161        member(Var, Collection) ;
  162        ( is_dict(Collection), get_dict(Var, Collection, _) )
  163    )).
 assert_type(+Term, +Type) is semidet
Test that Var is of type Type

Supported types are: number, integer, float, atom, compound, list, dict

Arguments:
Term- The term to be tested
Type- The type to be asserted
See also
- assertion/1
To be done
- Compound types
  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)).
 assert_not_type(+Term, +Type) is semidet
Test that Var is not of type Type
Arguments:
Term- The term to be tested
Type- The type to be un-asserted
See also
- assert_type/2
  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)).
 assert_gt(+A, +B) is semidet
Test that A is greater than B
Arguments:
A-
B-
  204assert_gt(A, B) :-
  205    assertion(A > B).
 assert_lt(+A, +B) is semidet
Test that A is less than B
Arguments:
A-
B-
  213assert_lt(A, B) :-
  214    assertion(A < B).
 assert_gte(+A, +B) is semidet
Test that A is greater than or equal to B
Arguments:
A-
B-
  222assert_gte(A, B) :-
  223    assertion(A >= B).
 assert_lte(+A, +B) is semidet
Test that A is less than or equal to B
Arguments:
A-
B-
  231assert_lte(A, B) :-
  232    assertion(A =< B).
  233
  234
  235% meta-tests ------------------------------------------------------------------
 assert_test_fails(+Goal) is semidet
Meta test to check that Goal would trigger a PlUnit test fail
Arguments:
Goal- The goal to be queried in the form of a plunit_assert predicate
  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.
 assert_test_passes(+Goal) is semidet
Meta test to check that Goal would not trigger a PlUnit test fail
Arguments:
Goal- The goal to be queried in the form of a plunit_assert predicate
  261assert_test_passes(Goal) :-
  262    Goal.
  263
  264pa_assertion_failed(_, _) :-
  265    %writeln('Captured test fail'),
  266    !