1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% Test module for Prolog predicates
    3
    4:- module(test_prolog, [
    5		run_all_prolog_tests/3  % +BasePath, -Passed, -Failed
    6	]).    7
    8:- use_module(library(lists)).    9:- use_module(library(statistics)).   10:- use_module(library(apply)).   11
   12%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   13
   14
   15
   16%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   17% Main predicates for testing Prolog predicates
   18%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 run_all_prolog_tests(+BasePath, -Passed, -Failed)
Loads all the files for testing Prolog predicates (which must be under the BasePath directory) and runs all their tests using run_prolog_test_files/5.

The total number of tests passed and failed will be returned in Passed and Failed, respectively.

See also
- run_prolog_test_files/5
   33run_all_prolog_tests(BasePath, Passed, Failed) :-
   34	prolog_test_files(Files),
   35	add_path_to_files(Files, FullFiles, BasePath),
   36	run_prolog_test_files(FullFiles, 0, Passed, 0, Failed).
 run_prolog_test_files(+Files, +Passed, -FinalPassed, +Failed, -FinalFailed)
Loads each of the Prolog source code files of the Files list in Prolog and Bousi-Prolog, and runs all the test predicates of their test suites under both systems using run_prolog_test_suites/5.

Passed/FinalPassed and Failed/FinalFailed are two accumulator pairs: FinalPassed will be unified with Passed plus the number of tests passed, whereas FinalFailed will be unified with Failed plus the number of tests failed.

See also
- run_prolog_test_suites/5
   53run_prolog_test_files([], Passed, Passed, Failed, Failed).
   54
   55run_prolog_test_files([File|MoreFiles], Passed, FinalPassed, Failed, FinalFailed) :-
   56	file_base_name(File, BaseFile),
   57	write('------------------------------------------------------------------------------'), nl,
   58	writef('Running Prolog test file %w', [BaseFile]), nl,
   59	write('------------------------------------------------------------------------------'), nl,
   60	(
   61		% Loads the Prolog file both in Prolog and Bousi-Prolog
   62		% (each Prolog file contains several test suites)
   63		catch((
   64			bplShell:ld(File, [f]),
   65			bplShell:last_program_loaded(LoadedFile, ''),
   66			file_base_name(LoadedFile, BaseFile),
   67			[File],
   68			!
   69		% (catcher)
   70		), _Error, (
   71			fail
   72		)),
   73		% Gets the test suites contained in the loaded file and runs them
   74		test_suites(TestSuites),
   75		run_prolog_test_suites(TestSuites, Passed, NewPassed, Failed, NewFailed)
   76	;
   77		% Prolog file couldn't be loaded
   78		writef('Test file %w couldn\'t be loaded.', [BaseFile]), nl,
   79		write('Press any key to continue '),
   80		get_single_char(_),
   81		nl,
   82		NewPassed is Passed,
   83		NewFailed is Failed + 1
   84	),
   85	!,
   86	% Proceeds to the next file
   87	run_prolog_test_files(MoreFiles, NewPassed, FinalPassed, NewFailed, FinalFailed).
 run_prolog_test_suites(+Suites, +Passed, -FinalPassed, +Failed, -FinalFailed)
For each atom in the Suites list, retrieves the test predicates which have a name starting with that atom, and runs them all using run_prolog_tests/5.

Passed/FinalPassed and Failed/FinalFailed are two accumulator pairs: FinalPassed will be unified with Passed plus the number of tests passed, whereas FinalFailed will be unified with Failed plus the number of tests failed.

See also
- run_prolog_tests/5
  104run_prolog_test_suites([], Passed, Passed, Failed, Failed).
  105
  106run_prolog_test_suites([Suite|MoreSuites], Passed, FinalPassed, Failed, FinalFailed) :-
  107	% Looks for the predicates that belong to this test suite
  108	atom_chars(Suite, SuiteChars),
  109	findall(Functor/Arity, (
  110		current_predicate(Functor/Arity),
  111		atom_chars(Functor, FunctorChars),
  112		append(SuiteChars, _, FunctorChars)
  113	), Tests),
  114	% Runs the tests of this test suite
  115	sort(Tests, SortedTests),
  116	run_prolog_tests(SortedTests, Passed, NewPassed, Failed, NewFailed),
  117	% Proceeds to the next test suite
  118	run_prolog_test_suites(MoreSuites, NewPassed, FinalPassed, NewFailed, FinalFailed).
 run_prolog_tests(+Tests, +Passed, -FinalPassed, +Failed, -FinalFailed)
Runs each of the predicates of the Tests list under Prolog and Bousi-Prolog, and compares both the output and the solutions generated by each pair of executions. A test will pass only if the output and the solutions returned by Prolog and Bousi-Prolog are exactly the same.

Passed/FinalPassed and Failed/FinalFailed are two accumulator pairs: FinalPassed will be unified with Passed plus the number of tests passed, whereas FinalFailed will be unified with Failed plus the number of tests failed.

See also
- execute_test/3
  137run_prolog_tests([], Passed, Passed, Failed, Failed).
  138
  139run_prolog_tests([Test|MoreTests], Passed, FinalPassed, Failed, FinalFailed) :-
  140	Test = Functor/Arity,
  141	writef('Testing %w/%w... ', [Functor, Arity]),
  142	% Builds the goal that will be used to launch the test
  143	length(Args, Arity),
  144	Goal =.. [Functor|Args],
  145	% Executes the test under Prolog
  146	tmp_file('test', PrologOutputFile),
  147	tell(PrologOutputFile),
  148	execute_test(Goal, Args, PrologSolutions),
  149	told,
  150	!,
  151	% Executes the test under Bousi-Prolog
  152	tmp_file('test', BousiPrologOutputFile),
  153	tell(BousiPrologOutputFile),
  154	execute_test(evaluator:solve_goal(bpl_call(Goal)), Args, BousiPrologSolutions),
  155	told,
  156	!,
  157	% Reads the output of both executions
  158	read_file_to_codes(PrologOutputFile, PrologOutput, []),
  159	read_file_to_codes(BousiPrologOutputFile, BousiPrologOutput, []),
  160	(
  161		% Compares the output and the solutions of both executions
  162		PrologOutput =@= BousiPrologOutput,
  163		PrologSolutions =@= BousiPrologSolutions,
  164		(throws_exception(Functor) ->
  165			PrologSolutions == [exception_thrown]
  166		;
  167			PrologSolutions \== [exception_thrown]
  168		),
  169		% Test passed
  170		write('OK'), nl,
  171		NewPassed is Passed + 1,
  172		NewFailed is Failed
  173	;
  174		% Test failed
  175		write('failed'), nl,
  176		NewPassed is Passed,
  177		NewFailed is Failed + 1,
  178		% Shows the results of the test
  179		atom_codes(PrologOutputAtom, PrologOutput),
  180		atom_codes(BousiPrologOutputAtom, BousiPrologOutput),
  181		writef('> Prolog solutions ....... %w', [PrologSolutions]), nl,
  182		writef('> Bousi-Prolog solutions . %w', [BousiPrologSolutions]), nl,
  183		writef('> Prolog output .......... \'%w\'', [PrologOutputAtom]), nl,
  184		writef('> Bousi-Prolog output .... \'%w\'', [BousiPrologOutputAtom]), nl,
  185		(throws_exception(Functor) ->
  186			write('> Exception expected ..... Yes'), nl
  187		;
  188			write('> Exception expected ..... No'), nl
  189		),
  190		write('Press any key to continue '),
  191		get_single_char(_),
  192		nl
  193	),
  194	delete_file(PrologOutputFile),
  195	delete_file(BousiPrologOutputFile),
  196	!,
  197	% Proceeds to the next test
  198	run_prolog_tests(MoreTests, NewPassed, FinalPassed, NewFailed, FinalFailed).
  199
  200
  201
  202%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  203% Helper predicates
  204%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 execute_test(+Goal, +Args, -Solutions)
Invokes Goal as a goal and unifies Solutions with a list of the instantiations that Args gets successively on backtracking over Goal. If Goal throws an unhandled exception, this predicate will catch it and a list with the single atom 'exception_thrown' will be returned in Solutions.
  216execute_test(Goal, Args, Solutions) :-
  217	catch((
  218		findall(Args, Goal, Solutions)
  219	% (catcher)
  220	), _Error, (
  221		Solutions = [exception_thrown]
  222	)).
 add_path_to_files(+Files, -FullPaths, +BasePath)
Concatenates BasePath with each of the filenames in Files and returns the resulting paths in FullPaths.
  231add_path_to_files([], [], _BasePath).
  232
  233add_path_to_files([File|MoreFiles], [FullPath|MoreFullPaths], BasePath) :-
  234	(concat_atom([_, '/'], BasePath) ->
  235		concat_atom([BasePath, File], FullPath)
  236	;
  237		concat_atom([BasePath, '/', File], FullPath)
  238	),
  239	add_path_to_files(MoreFiles, MoreFullPaths, BasePath).
  240
  241
  242
  243%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  244% Constant predicates
  245%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 prolog_test_files(?Files)
Returns the list of Prolog source code files that contain the test suites used by this module.
  254prolog_test_files(['pl_arithmetic.pl', 'pl_control.pl', 'pl_dynamic.pl',
  255                   'pl_findall.pl', 'pl_higherorder.pl', 'pl_io.pl',
  256                   'pl_lists.pl', 'pl_terms.pl', 'pl_typetest.pl',
  257                   'pl_unification.pl', 'pl_other.pl'])