1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% Bousi-Prolog system test launcher
    3
    4:- module(test, [
    5		main_test/0             %
    6   ]).    7
    8:- use_module('bousi').    9:- use_module('foreign').   10:- use_module('flags').   11:- use_module('evaluator').   12
   13:- use_module(test_prolog).   14:- use_module(test_bousiprolog).   15:- use_module(test_shell).   16:- use_module(test_errors).   17
   18:- use_module(library(test_cover)).   19:- use_module(library(lists)).   20
   21%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   22
   23
   24
   25%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   26% Main predicate for launching the Bousi-Prolog system tests
   27%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 main_test
Initial predicate of the Bousi-Prolog system test launcher. This predicate initializes the Bousi-Prolog system and runs all the tests designed for it. After all the tests have been completed, a report with the number of tests passed and the code coverage of each module is displayed.
   39main_test :-
   40%	test:run_tests.
   41	show_coverage(test:run_tests).
   42
   43
   44
   45%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   46% Predicate used to run all the tests
   47%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 run_tests
Initializes the Bousi-Prolog system, runs all the tests designed for it and then displays a report with the total number of test passed.
   57run_tests :-
   58	% Initializes the Bousi-Prolog system
   59	foreign:load_foreign_extension,
   60%	bplShell:load_history,
   61	bplShell:set_system_predicates,
   62	flags:reset_bpl_flags,
   63	evaluator:load_tpl(''),
   64	% Gets the full path where the test files are located
   65	working_directory(WorkingDir, WorkingDir),
   66	(concat_atom([_, '/'], WorkingDir) ->
   67		concat_atom([WorkingDir, 'test'], BasePath)
   68	;
   69		concat_atom([WorkingDir, '/', 'test'], BasePath)
   70	),
   71	% Remove compiled .tpl files
   72	concat_atom([BasePath, '/', '*.tpl'], WildCard),
   73	expand_file_name(WildCard, FilesToDelete),
   74	maplist(rm, FilesToDelete),
   75	% Runs all the tests from the four categories
   76	run_all_shell_tests(ShellPassed, ShellFailed),
   77	run_all_bousiprolog_tests(BasePath, BousiPassed, BousiFailed),
   78	run_all_error_and_warning_tests(BasePath, ErrorPassed, ErrorFailed),
   79 	run_all_prolog_tests(BasePath, PrologPassed, PrologFailed),
   80 	TotalPassed is ShellPassed+BousiPassed+ErrorPassed+PrologPassed,
   81 	TotalFailed is ShellFailed+BousiFailed+ErrorFailed+PrologFailed,
   82	% Writes the test report
   83	nl,
   84	write('================================'), nl,
   85	write('          Test Report           '), nl,
   86	write('================================'), nl,
   87	write('Test suites      Passed   Failed'), nl,
   88	write('================================'), nl,
   89	writef('Shell             %4r     %4r', [ShellPassed, ShellFailed]), nl,
   90	writef('Bousi-Prolog      %4r     %4r', [BousiPassed, BousiFailed]), nl,
   91	writef('Error/Warnings    %4r     %4r', [ErrorPassed, ErrorFailed]), nl,
   92 	writef('Prolog            %4r     %4r', [PrologPassed, PrologFailed]), nl,
   93	write('================================'), nl,
   94	writef('Total             %4r     %4r', [TotalPassed, TotalFailed]), nl,
   95	true