Improving unit tests

Hi

apologies for the GDrive permission snag.

Let me just add the code right here (reindent as needed).

/* -*- Mode: Prolog -*- */

/* plunit_reporting.pl --
 * Extra test running and reporting predicates to ease automating
 * multiple tests of similar code.
 *
 * See the file COPYING for coyright and licensing information.
 */

:- module(plunit2,
	  [ run_tests_and_report/1,
	    run_tests_and_report/2
	  ]).
:- use_module(library(plunit)).
:- add_import_module(plunit2, plunit, start).


%!  run_tests_and_report(-Report) is semidet.
%!  run_tests_and_report(+TestSet, -Report) is semidet.
%
%   Run tests and report about the results.  The predicate
%   run_tests_and_report/1 runs all known tests that are not
%   blocked. The predicate run_tests_and_report/1 takes a
%   specification of tests to run.  This 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.

/* The predicates report_and_cleanup2/2 and report2/5 are named so to
 * avoid, for the time being, issues with 'discontinuous' settings.
 */

run_tests_and_report(report(Passed,
			    Failed,
			    FailedAssertions,
			    Blocked,
			    STO)) :-
    cleanup,
    setup_call_cleanup(
        setup_trap_assertions(Ref),
        (   run_current_units2,
            %% writeln(">>> Current units run"),
            true
        ),
        report_and_cleanup2(Ref,
			    report(Passed,
				   Failed,
				   FailedAssertions,
				   Blocked,
				   STO))).


run_current_units2 :-
    forall(current_test_set(Set),
           run_unit(Set)),
    check_for_test_errors2.



report_and_cleanup2(Ref,
		    report(Passed,
			   Failed,
			   FailedAssertions,
			   Blocked,
			   STO)) :-
    cleanup_trap_assertions(Ref),
    %% format(">>> After trap cleanup ~w~n", [Ref]),
    report2(Passed,
	    Failed,
	    FailedAssertions,
	    Blocked,
	    STO),
    /*
    format(">>> ~d ~d ~d ~d ~d~n",
           [Passed,
            Failed,
            FailedAssertions,
            Blocked,
            STO]),
    */
    cleanup_after_test2.


run_tests_and_report(Set,
		     report(Passed,
			    Failed,
			    FailedAssertions,
			    Blocked,
			    STO)) :-
    cleanup,
    setup_call_cleanup(
        setup_trap_assertions(Ref),
        (
            %% format(">>> Current unit running ~w~n", [Set]),
            run_unit_and_check_errors2(Set),
            %% format(">>> Current unit run and errors checked ~w~n", [Set]),
            true
        ),
        report_and_cleanup2(Ref,
			    report(Passed,
				   Failed,
				   FailedAssertions,
				   Blocked,
				   STO))).


run_unit_and_check_errors2(Set) :-
    run_unit(Set),
    %% format(">>> RUCE ~w~n", [Set]),
    check_for_test_errors2,
    %% format(">>> RUCE done~n").
    true.


check_for_test_errors2 :- true.


report2(Passed, Failed, FailedAssertion, Blocked, STO) :-
    number_of_clauses(passed/5, Passed),
    number_of_clauses(failed/4, Failed),
    number_of_clauses(failed_assertion/7, FailedAssertion),
    number_of_clauses(blocked/4, Blocked),
    number_of_clauses(sto/4, STO),
    (   Passed+Failed+FailedAssertion+Blocked+STO =:= 0
    ->  info(plunit(no_tests))
    ;   Failed+FailedAssertion+Blocked+STO =:= 0
    ->  report_fixme,
        info(plunit(all_passed(Passed)))
    ;   report_blocked,
        report_fixme,
        report_failed_assertions,
        report_failed,
        report_sto,
        info(plunit(passed(Passed)))
    ).



cleanup_after_test2 :-
    current_test_flag(test_options, Options),
    %% format(">>> Options ~w~n", [Options]),
    option(cleanup(Cleanup), Options, false),
    %% format(">>> Cleanup ~w~n", [Cleanup]),
    (   Cleanup == true
    ->  cleanup
    ;  (
           %%  writeln(">>> Not cleaning up"),
            true
       )
    ).


/* end of file -- plunit_reporting.pl */
1 Like