1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% Test module for the Bousi-Prolog shell
    3
    4:- module(test_shell, [
    5		run_all_shell_tests/2   % -Passed, -Failed
    6	]).    7
    8:- use_module(library(readutil)).    9
   10%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   11
   12
   13
   14%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   15% Main predicates for testing Bousi-Prolog shell
   16%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 run_all_shell_tests(-Passed, -Failed)
Runs a set of tests for each of the available commands in the Bousi-Prolog shell (except 'ls', 'sh' and 'qt).

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

   28run_all_shell_tests(Passed, Failed) :-
   29	write('------------------------------------------------------------------------------'), nl,
   30	write('Running Bousi-Prolog shell tests'), nl,
   31	write('------------------------------------------------------------------------------'), nl,
   32	assert(passed_tests(0)),
   33	assert(failed_tests(0)),
   34	run_other_tests,
   35	run_hp_tests,
   36	run_cd_tests,
   37	run_pwd_tests,
   38	run_ld_tests,
   39	run_lc_tests,
   40	run_sv_tests,
   41%	run_history_test,
   42	passed_tests(Passed),
   43	failed_tests(Failed),
   44	retract(passed_tests(Passed)),
   45	retract(failed_tests(Failed)).
 run_other_tests
Runs other Bousi-Prolog shell tests.
See also
- run_command_test/3
   55run_other_tests :-
   56	% > Empty command
   57	run_command_test('', [],
   58	                 []),
   59	run_command_test('  ', [],
   60	                 []),
   61	% > Unknown command
   62	run_command_test('foo foo', ['foo foo'],
   63	                 ['Syntax error']).
 run_hp_tests
Runs some tests for the help command ('hp').
See also
- run_command_test/3
   73run_hp_tests :-
   74	% > General help
   75	run_command_test('hp', ['hp'],
   76	                 ['ld', 'sv', 'lc', 'pwd', 'ls', 'cd', 'hp', 'qt', 'sh']),
   77	% > Command help
   78	run_command_test('hp ld', ['hp', 'ld'],
   79	                 ['LOAD']),
   80	run_command_test('hp sv', ['hp', 'sv'],
   81	                 ['SOLVE']),
   82	run_command_test('hp lc', ['hp', 'lc'],
   83	                 ['LAMBDA-CUT']),
   84	run_command_test('hp pwd', ['hp', 'pwd'],
   85	                 ['PRINT WORKING DIRECTORY']),
   86	run_command_test('hp ls', ['hp', 'ls'],
   87	                 ['LIST']),
   88	run_command_test('hp cd', ['hp', 'cd'],
   89	                 ['CHANGE DIR']),
   90	run_command_test('hp hp', ['hp', 'hp'],
   91	                 ['HELP']),
   92	run_command_test('hp qt', ['hp', 'qt'],
   93	                 ['QUIT']),
   94	run_command_test('hp sh', ['hp', 'sh'],
   95	                 ['SHELL']),
   96	% > Error cases
   97	run_command_test('hp foo', ['hp', 'foo'],
   98	                 ['ERROR']),
   99	run_command_test('hp foo foo', ['hp', 'foo', 'foo'],
  100	                 ['Wrong number of arguments']).
 run_cd_tests
Runs some tests for the change directory command ('cd').
See also
- run_command_test/3
  110run_cd_tests :-
  111	% Creates two temporary directories
  112	working_directory(WorkingDir, WorkingDir),
  113	tmp_file('test', TempDir),
  114	make_directory(TempDir),
  115	add_path_to_files(['1 $ 3'], [SpacesTempDir], TempDir),
  116	make_directory(SpacesTempDir),
  117	% > Change to an absolute path
  118	atom_concat('cd ', TempDir, CDCommandTempDir),
  119	run_command_test(CDCommandTempDir, ['cd', TempDir],
  120	                 [TempDir]),
  121	% > Change to a relative path with spaces and non-alphanumeric characters
  122	run_command_test('cd \'1 $ 3\'', ['cd', '1 $ 3'],
  123	                 [SpacesTempDir]),
  124	% > Error cases
  125	run_command_test('cd $foo$', ['cd', '$foo$'],
  126	                 ['ERROR']),
  127	run_command_test('cd $foo$ $foo$', ['cd', '$foo$', '$foo$'],
  128	                 ['Wrong number of arguments']),
  129	% Restores the original working directory
  130	atom_concat('cd ', WorkingDir, CDCommandWorkingDir),
  131	run_command_test(CDCommandWorkingDir, ['cd', WorkingDir],
  132	                 [WorkingDir]),
  133	% Deletes the temporary directories
  134	delete_directory(SpacesTempDir),
  135	delete_directory(TempDir).
 run_pwd_tests
Runs some tests for the print working directory command ('pwd').
See also
- run_command_test/3
  145run_pwd_tests :-
  146	% Creates a temporary directory
  147	working_directory(WorkingDir, WorkingDir),
  148	tmp_file('test', TempDir),
  149	make_directory(TempDir),
  150	% > Print working directory
  151	run_command_test('pwd', ['pwd'],
  152	                 [WorkingDir]),
  153	% > Change directory and print working directory again
  154	atom_concat('cd ', TempDir, CDCommandTempDir),
  155	run_command_test(CDCommandTempDir, ['cd', TempDir],
  156	                 [TempDir]),
  157	run_command_test('pwd', ['pwd'],
  158	                 [TempDir]),
  159	% > Error cases
  160	run_command_test('pwd foo', ['pwd', 'foo'],
  161	                 ['Wrong number of arguments']),
  162	% Restores the original working directory
  163	atom_concat('cd ', WorkingDir, CDCommandWorkingDir),
  164	run_command_test(CDCommandWorkingDir, ['cd', WorkingDir],
  165	                 [WorkingDir]),
  166	% Deletes the temporary directory
  167	delete_directory(TempDir).
 run_ld_tests
Runs some tests for the load command ('ld'). In order for these tests to work, this predicate must be invoked before any program is loaded.
See also
- run_command_test/3
  179run_ld_tests :-
  180	% Creates a temporary folder and several temporary files
  181	working_directory(WorkingDir, WorkingDir),
  182	tmp_file('test', TempDir),
  183	make_directory(TempDir),
  184	add_path_to_files(['program.bpl', 'program.tpl', '1 prog PROG $',
  185	                   'ontology.ont', 'program-ontology.tpl', 'ONT ont 2 $',
  186	                   '1 prog PROG $.tpl', '1 prog PROG $-ONT ont 2 $.tpl',
  187	                   'ontology.ont.tpl'],
  188	                  [BPLProgramPath, TPLProgramPath, SpacesProgramPath,
  189	                   ONTOntologyPath, TPLOntologyPath, SpacesOntologyPath,
  190	                   TPLSpacesProgramPath, TPLSpacesOntologyPath,
  191	                   TPLONTOntologyPath],
  192	                  TempDir),
  193	tell(BPLProgramPath),
  194	write('a.'), nl,
  195	told,
  196	tell(ONTOntologyPath),
  197	write('a ~ b = 0.5.'), nl,
  198	told,
  199	tell(SpacesProgramPath),
  200	write('a.'), nl,
  201	told,
  202	tell(SpacesOntologyPath),
  203	write('a ~ b = 0.5.'), nl,
  204	told,
  205	% Changes current working directory
  206	atom_concat('cd ', TempDir, CDCommandTempDir),
  207	run_command_test(CDCommandTempDir, ['cd', TempDir],
  208	                 [TempDir]),
  209	% > Show loaded program when no program is loaded
  210	run_command_test('ld', ['ld'],
  211	                 ['No program loaded']),
  212	% > Load an ontology when no program is loaded
  213	run_command_test('ld -o ontology.ont', ['ld', '-o', 'ontology.ont'],
  214	                 ['ERROR']),
  215	% > Load a program: TPL file must be created because it doesn't exist
  216	run_command_test('ld program.bpl', ['ld', 'program.bpl'],
  217	                 ['Parsing and translating', 'Program loaded!']),
  218	run_command_test('sv \\+(a)', ['sv', '\\+', '(', 'a', ')'],
  219	                 ['No answers']),
  220	% > Load a program: TPL file exists and can be loaded
  221	run_command_test('ld program.bpl', ['ld', 'program.bpl'],
  222	                 ['\'program.tpl\' already exists', 'Program loaded!']),
  223	% > Load a program with forced rebuild
  224	run_command_test('ld -f program.bpl', ['ld', '-f', 'program.bpl'],
  225	                 ['Parsing and translating', 'Program loaded!']),
  226	% > Load a program: BPL file is newer than TPL so a rebuild is needed
  227	sleep(1),
  228	tell(BPLProgramPath),
  229	write('b.'),
  230	told,
  231	run_command_test('ld program.bpl', ['ld', 'program.bpl'],
  232	                 ['Parsing and translating', 'Program loaded!']),
  233	% > Show loaded program
  234	run_command_test('ld', ['ld'],
  235	                 [BPLProgramPath]),
  236	% > Load an ontology: TPL file must be created because it doesn't exist
  237	run_command_test('ld -o ontology.ont', ['ld', '-o', 'ontology.ont'],
  238	                 ['Parsing and translating', 'Ontology loaded!']),
  239	run_command_test('sv \\+(\\+(a))', ['sv','\\+','(','\\+','(','a',')',')'],
  240	                 ['No answers']),
  241	% > Load an ontology: TPL file exists and can be loaded
  242	run_command_test('ld -o ontology.ont', ['ld', '-o', 'ontology.ont'],
  243	                 ['\'program-ontology.tpl\' already exists', 'Ontology loaded!']),
  244	% > Load an ontology with forced rebuild
  245	run_command_test('ld -fo ontology.ont', ['ld', '-fo', 'ontology.ont'],
  246	                 ['Parsing and translating', 'Ontology loaded!']),
  247	run_command_test('ld -f -o ontology.ont', ['ld', '-f', '-o', 'ontology.ont'],
  248	                 ['Parsing and translating', 'Ontology loaded!']),
  249	run_command_test('ld -o -f ontology.ont', ['ld', '-o', '-f', 'ontology.ont'],
  250	                 ['Parsing and translating', 'Ontology loaded!']),
  251	% > Load an ontology: program's BPL file is newer than TPL so a
  252	%   rebuild is needed
  253	sleep(1),
  254	tell(BPLProgramPath),
  255	write('a.'),
  256	told,
  257	run_command_test('ld -o ontology.ont', ['ld', '-o', 'ontology.ont'],
  258	                 ['Parsing and translating', 'Ontology loaded!']),
  259	% > Load an ontology: ontology's BPL file is newer than TPL so a
  260	%   rebuild is needed
  261	sleep(1),
  262	tell(ONTOntologyPath),
  263	write('a ~ b = 0.8.'),
  264	told,
  265	run_command_test('ld -o ontology.ont', ['ld', '-o', 'ontology.ont'],
  266	                 ['Parsing and translating', 'Ontology loaded!']),
  267	% > Show loaded program and ontology
  268	run_command_test('ld', ['ld'],
  269	                 [BPLProgramPath, ONTOntologyPath]),
  270	% > Load an ontology without the original program's BPL file
  271	delete_file(BPLProgramPath),
  272	run_command_test('ld -o ontology.ont', ['ld', '-o', 'ontology.ont'],
  273	                 ['ERROR']),
  274	% > Load a program without the original BPL file
  275	run_command_test('ld program.bpl', ['ld', 'program.bpl'],
  276	                 ['WARNING']),
  277	% > Load a file with spaces, with non-alphanumeric characters and
  278	%   without extension
  279	run_command_test('ld \'1 prog PROG $\'', ['ld', '1 prog PROG $'],
  280	                 ['Program loaded!']),
  281	run_command_test('ld -o \"ONT ont 2 $\"', ['ld', '-o', 'ONT ont 2 $'],
  282	                 ['Ontology loaded!']),
  283	% > Load a file in another directory with an include/1 directive
  284	sleep(1),
  285	tell(BPLProgramPath),
  286	write(':- include(\'1 prog PROG $\').'),
  287	write('a.'), nl,
  288	told,
  289	tell(ONTOntologyPath),
  290	write('a ~ b = 0.5.'),
  291	told,
  292	atom_concat('cd ', WorkingDir, CDCommandWorkingDir),
  293	run_command_test(CDCommandWorkingDir, ['cd', WorkingDir],
  294	                 [WorkingDir]),
  295	atom_concat('ld ', BPLProgramPath, LDCommandBPL),
  296	run_command_test(LDCommandBPL, ['ld', BPLProgramPath],
  297	                 ['Program loaded!']),
  298	atom_concat('ld -o ', ONTOntologyPath, LDCommandONT),
  299	run_command_test(LDCommandONT, ['ld', '-o', ONTOntologyPath],
  300	                 ['Ontology loaded!']),
  301	% > Load a program without rules (warning)
  302	atom_concat('ld ', ONTOntologyPath, LDCommandONT2),
  303	run_command_test(LDCommandONT2, ['ld', ONTOntologyPath],
  304	                 ['WARNING', 'Program loaded!']),
  305	% > Load an ontology with rules (error)
  306	atom_concat('ld -o ', BPLProgramPath, LDCommandBPL2),
  307	run_command_test(LDCommandBPL2, ['ld', '-o', BPLProgramPath],
  308	                 ['ERROR', 'Ontology not loaded.']),
  309	% > Error cases
  310	run_command_test('ld $foo$', ['ld', '$foo$'],
  311	                 ['ERROR']),
  312	run_command_test('ld -f $foo$', ['ld', '-f', '$foo$'],
  313	                 ['ERROR']),
  314	run_command_test('ld -o $foo$', ['ld', '-o', '$foo$'],
  315	                 ['ERROR']),
  316	run_command_test('ld -x $foo$', ['ld', '-x', '$foo$'],
  317	                 ['ERROR']),
  318	run_command_test('ld $foo$ $foo$', ['ld', '$foo$', '$foo$'],
  319	                 ['Wrong number of arguments']),
  320	% Deletes the temporary files and folders
  321	delete_file(BPLProgramPath),
  322	delete_file(TPLProgramPath),
  323	delete_file(ONTOntologyPath),
  324	delete_file(TPLOntologyPath),
  325	delete_file(TPLONTOntologyPath),
  326	delete_file(SpacesProgramPath),
  327	delete_file(TPLSpacesProgramPath),
  328	delete_file(SpacesOntologyPath),
  329	delete_file(TPLSpacesOntologyPath),
  330	concat_atom(['rm ',TempDir,'/*.tpls'], Cmd),
  331	shell(Cmd),
  332	delete_directory(TempDir).
 run_lc_tests
Runs some tests for the lambda cut command ('lc').
See also
- run_command_test/3
  342run_lc_tests :-
  343	% Creates a temporary folder and a temporary file
  344	working_directory(WorkingDir, WorkingDir),
  345	tmp_file('test', TempDir),
  346	make_directory(TempDir),
  347	add_path_to_files(['lambda.bpl', 'lambda.tpl', 'lambda.tpls'],
  348	                  [BPLProgramPath, TPLProgramPath, TPLSProgramPath],
  349	                  TempDir),
  350	tell(BPLProgramPath),
  351	write(':- transitivity(yes).'), nl,
  352	write('a ~ b = 0.8.'), nl,
  353	write('b ~ c = 0.3.'), nl,
  354	write('a.'), nl,
  355	told,
  356	% > Show lambda cut of current loaded file, which must be 0
  357	atom_concat('ld ', BPLProgramPath, LDCommandBPL),
  358	run_command_test(LDCommandBPL, ['ld', BPLProgramPath],
  359	                 ['Program loaded!']),
  360	run_command_test('lc', ['lc'],
  361	                 ['Current lambda-cut value is: 0']),
  362	run_command_test('sv \\+(\\+(c))', ['sv','\\+','(','\\+','(','c',')',')'],
  363	                 ['No answers']),
  364	% > Change lambda cut
  365	run_command_test('lc 0.5', ['lc', '0.5'],
  366	                 ['New lambda-cut value is: 0.5']),
  367	run_command_test('sv c', ['sv', 'c'],
  368%	                 ['No answers']),
  369                   ['\'<meta-call>\'/1: Undefined procedure: c/0']),
  370	% > Show new lambda cut
  371	run_command_test('lc', ['lc'],
  372	                 ['Current lambda-cut value is: 0.5']),
  373	% > Load file again and show new lambda cut, which must be 0
  374	run_command_test(LDCommandBPL, ['ld', BPLProgramPath],
  375	                 ['Program loaded!']),
  376	run_command_test('lc', ['lc'],
  377	                 ['Current lambda-cut value is: 0']),
  378	% > Error cases
  379	run_command_test('lc -0.5', ['lc', '-0.5'],
  380	                 ['ERROR']),
  381	run_command_test('lc 1.5', ['lc', '1.5'],
  382	                 ['ERROR']),
  383	run_command_test('lc foo', ['lc', 'foo'],
  384	                 ['ERROR']),
  385	run_command_test('lc foo foo', ['lc', 'foo', 'foo'],
  386	                 ['Wrong number of arguments']),
  387	% Deletes the temporary files and folders
  388	delete_file(BPLProgramPath),
  389	delete_file(TPLProgramPath),
  390	delete_file(TPLSProgramPath),
  391	delete_directory(TempDir).
 run_sv_tests
Runs some tests for the solve command ('sv').
See also
- run_command_test/3
  401run_sv_tests :-
  402	% Creates a temporary folder and a temporary file
  403	working_directory(WorkingDir, WorkingDir),
  404	tmp_file('test', TempDir),
  405	make_directory(TempDir),
  406	add_path_to_files(['solve.bpl', 'solve.tpl', 'solve.tpls'],
  407	                  [BPLProgramPath, TPLProgramPath, TPLSProgramPath],
  408	                  TempDir),
  409	tell(BPLProgramPath),
  410	write('a ~ b = 0.5.'), nl,
  411	write('a(0).'), nl,
  412	write('a(1).'), nl,
  413	write('v(1, 2, 3).'), nl,
  414	write('x :- fail.'), nl,
  415	told,
  416	% > Load a file with some sample predicates
  417	atom_concat('ld ', BPLProgramPath, LDCommandBPL),
  418	run_command_test(LDCommandBPL, ['ld', BPLProgramPath],
  419	                 ['Program loaded!']),
  420	% > Solve a query with no solutions (using / without using the sv
  421	%   command, and ending / without ending in a dot)
  422	run_command_test('sv x', ['sv', 'x'],
  423	                 ['No answers']),
  424	run_command_test('sv x.', ['sv', 'x.'],
  425	                 ['No answers']),
  426	run_command_test('x', ['x'],
  427	                 ['No answers']),
  428	run_command_test('x.', ['x.'],
  429	                 ['No answers']),
  430	run_command_test('sv a(foo)', ['sv', 'a', '(', 'foo', ')'],
  431	                 ['No answers']),
  432	run_command_test('\\+(a(0))', ['\\+', '(', 'a', '(', '0', ')', ')'],
  433	                 ['No answers']),
  434	run_command_test('(10 is 9 + 2 ; fail)', ['(','10','is','9','+','2',';','fail',')'],
  435	                 ['No answers']),
  436  open('test/shell_inputs', read, Stream),
  437  set_stream(Stream, alias(user_input)),
  438	% > Solve a ground query
  439	write('[Press RETURN]'), nl,
  440	run_command_test('sv a(0)', ['sv', 'a', '(', '0', ')'],
  441	                 ['Yes', 'With approximation degree: 1']),
  442	write('[Press RETURN]'), nl,
  443	run_command_test('b(0).', ['b', '(', '0', ')', '.'],
  444	                 ['Yes', 'With approximation degree: 0.5']),
  445	% > Solve a ground query with several subgoals
  446	write('[Press RETURN]'), nl,
  447	run_command_test('sv b(0) ; b(1).', ['sv','b','(','0',')',';','b','(','1',')','.'],
  448	                 ['Yes', 'With approximation degree: 0.5']),
  449	write('[Press RETURN]'), nl,
  450	run_command_test('a(0) ; a(1)', ['a','(','0',')',';','a','(','1',')'],
  451	                 ['Yes', 'With approximation degree: 1']),
  452	% > Solve a non-ground query
  453	write('[Press RETURN]'), nl,
  454	run_command_test('v(A, B, C)', ['v', '(', 'A,', 'B,', 'C', ')'],
  455	                 ['Yes', 'A = 1', 'B = 2', 'C = 3',
  456	                  'With approximation degree: 1']),
  457	write('[Press RETURN]'), nl,
  458	run_command_test('(X is 9 + 2 ; fail)', ['(','X','is','9','+','2',';','fail',')'],
  459	                 ['Yes', 'X = 11', 'With approximation degree: 1']),
  460	% > Solve a non-ground query with several solutions
  461	write('[Press \';\' twice]'), nl,
  462	run_command_test('sv a(X)', ['sv', 'a', '(', 'X', ')'],
  463	                 ['X = 0', 'X = 1', 'With approximation degree: 1']),
  464	write('[Press \';\' twice]'), nl,
  465	run_command_test('sv b(X)', ['sv', 'b', '(', 'X', ')'],
  466	                 ['X = 0', 'X = 1', 'With approximation degree: 0.5']),
  467	close(Stream),
  468	% > Error cases
  469	run_command_test('sv undefined(1, 2)', ['sv', 'undefined', '(', '1', ',', '2', ')'],
  470	                 ['\'<meta-call>\'/1: Undefined procedure: undefined/2']),
  471	run_command_test('call(undefined(_))', ['call', '(', 'undefined', '(', '_', ')', ')'],
  472	                 ['bpl_call/1: Undefined procedure: undefined/1']),
  473	run_command_test('sv a(.', ['sv', 'a', '(', '.'],
  474	                 ['Syntax error in query']),
  475	run_command_test('a(', ['a', '('],
  476	                 ['Syntax error in command or query']),
  477	% Deletes the temporary files and folders
  478	delete_file(BPLProgramPath),
  479	delete_file(TPLProgramPath),
  480	delete_file(TPLSProgramPath),
  481	delete_directory(TempDir).
 run_history_test
Runs a test for the shell's history file.
  489% run_history_test :-
  490% 	% Creates a temporary folder and a temporary file
  491% 	working_directory(WorkingDir, WorkingDir),
  492% 	tmp_file('test', TempDir),
  493% 	make_directory(TempDir),
  494% 	add_path_to_files(['history.bpl', 'history.tpl', 'history.tpls'],
  495% 	                  [BPLProgramPath, TPLProgramPath, TPLSProgramPath],
  496% 	                  TempDir),
  497% 	tell(BPLProgramPath),
  498% 	write('x :- fail.'), nl,
  499% 	told,
  500% 	% Loads the temporary file
  501% 	bplShell:ld(BPLProgramPath, [f]),
  502% 	(
  503% 		% Backups the current history file and creates a new one
  504% 		utilities:home_directory(HomeDirectory),
  505% 		bplShell:history_filename(File),
  506% 		add_path_to_files([File, '.bpl_history_backup'],
  507% 		                  [HistoryFile, HistoryFileBackup], HomeDirectory),
  508% 		rename_file(HistoryFile, HistoryFileBackup),
  509% 		tell(HistoryFile),
  510% 		told,
  511% 		% Asks the user to enter 'x', a query that will fail
  512% 		bplShell:load_history,
  513% 		write('[Press \'x\' and then ENTER]'), nl,
  514% 		ignore(bplShell:bpl_shell),
  515% 		bplShell:save_history,
  516% 		% Reads the contents of the history file
  517% 		read_file_to_codes(HistoryFile, Codes, []),
  518% 		% Restores the original history file
  519% 		delete_file(HistoryFile),
  520% 		rename_file(HistoryFileBackup, HistoryFile),
  521% 		bplShell:load_history,
  522% 		% Checks if the shell saved an 'x' in the history file
  523% 		atom_codes('x', [ExpectedCode]),
  524% 		Codes = [ExpectedCode|_],
  525% 		% Test passed
  526% 		write('Testing shell history... OK'), nl,
  527% 		passed_tests(Passed),
  528% 		NewPassed is Passed + 1,
  529% 		retract(passed_tests(Passed)),
  530% 		assert(passed_tests(NewPassed))
  531% 	;
  532% 		% Test failed
  533% 		write('Testing shell history... failed'), nl,
  534% 		failed_tests(Failed),
  535% 		NewFailed is Failed + 1,
  536% 		retract(failed_tests(Failed)),
  537% 		assert(failed_tests(NewFailed)),
  538% 		write('Press any key to continue '),
  539% 		get_single_char(_),
  540% 		nl
  541% 	),
  542% 	% Deletes the temporary files and folders
  543% 	delete_file(BPLProgramPath),
  544% 	delete_file(TPLProgramPath),
  545% 	delete_file(TPLSProgramPath),
  546% 	delete_directory(TempDir).
 run_command_test(+String, +Arguments, +ExpectedMessages)
Sends the command represented by String and Arguments to the Bousi-Prolog shell, and checks whether its execution generated all the messages in the ExpectedMessages list. This test will pass if the output contains lines starting with each of the strings in the ExpectedMessages list.

The dynamic predicates passed_tests/1 and failed_tests/1 will be modified after executing this test depending on its result.

  561run_command_test(String, Arguments, ExpectedMessages) :-
  562	writef('Testing command \'%w\'... ', [String]),
  563	% Executes the shell command using exactly the same calls as in
  564	% bplShell:bpl_shell/0, and saves its output in a temporary file
  565	tmp_file('test', CommandOutputFile),
  566	tell(CommandOutputFile),
  567	catch((
  568		bplShell:translate_command(String, Arguments, Command),
  569		bplShell:Command,
  570		(Command \== true -> nl ; true)
  571	), Error, (
  572		(Error = translate_error(ErrorMessage) ->
  573			% Invalid command or query
  574			write(ErrorMessage), nl, nl
  575		;
  576			% Exception thrown by SWI-Prolog
  577			message_to_string(Error, Message),
  578			write(Message), nl
  579		)
  580	)),
  581	told,
  582	!,
  583	(
  584		% Checks if the shell command wrote the expected messages
  585		% in the standard output
  586		check_output(CommandOutputFile, ExpectedMessages),
  587		% Test passed
  588		write('OK'), nl,
  589		passed_tests(Passed),
  590		NewPassed is Passed + 1,
  591		retract(passed_tests(Passed)),
  592		assert(passed_tests(NewPassed))
  593	;
  594		% Test failed
  595		write('failed'), nl,
  596		failed_tests(Failed),
  597		NewFailed is Failed + 1,
  598		retract(failed_tests(Failed)),
  599		assert(failed_tests(NewFailed)),
  600		% Shows the results of the test
  601		read_file_to_codes(CommandOutputFile, OutputCodes, []),
  602		atom_codes(OutputString, OutputCodes),
  603		writef('> Output text .......\n%w', [OutputString]), nl,
  604		writef('> Expected messages . %w', [ExpectedMessages]), nl,
  605		write('Press any key to continue '),
  606		get_single_char(_),
  607		nl
  608	),
  609	delete_file(CommandOutputFile),
  610	!.
  611
  612
  613
  614%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  615% Helper predicates
  616%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 check_output(+File, +Texts)
Succeeds if File contains lines starting with each of the strings in the Texts lists.
  625check_output(_File, []).
  626
  627check_output(File, [Text|MoreTexts]) :-
  628	open(File, read, Stream),
  629	search_text_in_stream(Stream, Text),
  630	close(Stream),
  631	check_output(File, MoreTexts).
 search_text_in_stream(+Stream, +Text)
Succeeds if a line starting with Text can be found in the specified Stream. Stream will be automatically closed if the predicate fails, but will remain open if it succeeds.
  641search_text_in_stream(Stream, _Text) :-
  642	% Checks if EOF has been reached
  643	at_end_of_stream(Stream), !,
  644	% Text wasn't found in Stream
  645	close(Stream),
  646	fail.
  647
  648search_text_in_stream(Stream, Text) :-
  649	% Gets the next line from the stream
  650	read_line_to_codes(Stream, Codes),
  651	atom_codes(String, Codes),
  652	% Checks if the line starts with Text
  653	(sub_atom(String, 0, _, _, Text) ->
  654		% Text was found in this line, so the predicate must succeed
  655		!
  656	;
  657		% Text wasn't found in this line, so we must keep searching
  658		search_text_in_stream(Stream, Text)
  659	).
 add_path_to_files(+Files, -FullPaths, +BasePath)
Concatenates BasePath with each of the filenames in Files and returns the resulting paths in FullPaths.
  668add_path_to_files([], [], _BasePath).
  669
  670add_path_to_files([File|MoreFiles], [FullPath|MoreFullPaths], BasePath) :-
  671	(concat_atom([_, '/'], BasePath) ->
  672		concat_atom([BasePath, File], FullPath)
  673	;
  674		concat_atom([BasePath, '/', File], FullPath)
  675	),
  676	add_path_to_files(MoreFiles, MoreFullPaths, BasePath).
  677
  678
  679
  680%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  681% Dynamic predicates
  682%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Contains the number of tests passed.
  690:- dynamic passed_tests/1.
Contains the number of tests failed.
  698:- dynamic failed_tests/1.