1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% Test module for error and warning messages
    3
    4:- module(test_errors, [
    5		run_all_error_and_warning_tests/3 % +BasePath, -Passed, -Failed
    6	]).    7
    8:- use_module(library(readutil)).    9:- use_module(library(lists)).   10
   11%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   12
   13
   14
   15%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   16% Main predicates for testing error and warning messages
   17%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 run_all_error_and_warning_tests(+BasePath, -Passed, -Failed)
Loads all the files for testing error and warning messages (which must be under the BasePath directory) and runs all their tests using run_error_test_files/6 and run_warning_test_files/5.

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

See also
- run_error_test_files/6
- run_warning_test_files/5
   33run_all_error_and_warning_tests(BasePath, Passed, Failed) :-
   34	% Error tests
   35	error_test_files(ErrorFiles, ErrorLinesFiles),
   36	add_path_to_files(ErrorFiles, FullErrorFiles, BasePath),
   37	add_path_to_files(ErrorLinesFiles, FullErrorLinesFiles, BasePath),
   38	run_error_test_files(FullErrorFiles, FullErrorLinesFiles, 0, PassedAux, 0, FailedAux),
   39	% Warning tests
   40	warning_test_files(WarningFiles),
   41	add_path_to_files(WarningFiles, FullWarningFiles, BasePath),
   42	run_warning_test_files(FullWarningFiles, PassedAux, Passed, FailedAux, Failed).
 run_error_test_files(+Files, +LinesFiles, +Passed, -FinalPassed, +Failed, -FinalFailed)
Loads each of the Prolog or Bousi-Prolog source code files of the Files list, and verifies that these files have exactly the same errors that are indicated in the files of the LinesFiles (by means of the error_in_line/1 predicate).

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
- compare_lines/7
   60run_error_test_files([], [], FinalPassed, FinalPassed, FinalFailed, FinalFailed).
   61
   62run_error_test_files([File|MoreFiles], [LinesFile|MoreLinesFiles], Passed, FinalPassed, Failed, FinalFailed) :-
   63	file_base_name(File, BaseFile),
   64	file_base_name(LinesFile, BaseLinesFile),
   65	write('------------------------------------------------------------------------------'), nl,
   66	writef('Running error test file %w', [BaseFile]), nl,
   67	write('------------------------------------------------------------------------------'), nl,
   68	(
   69		% Tries to load the file with errors
   70		tmp_file('test', ErrorOutputFile),
   71		catch((
   72			tell(ErrorOutputFile),
   73			bplShell:ld(File, [f]),
   74			bplShell:last_program_loaded(_LoadedBaseFile, ''),
   75			told,
   76			!
   77		% (catcher)
   78		), _Error2, (
   79			fail
   80		)),
   81		% Loads the file that can be used to get the lines
   82		% where the errors are located
   83		catch((
   84			bplShell:ld(LinesFile, [f]),
   85			bplShell:last_program_loaded(LoadedBaseLinesFile, ''),
   86			file_base_name(LoadedBaseLinesFile, BaseLinesFile),
   87			!
   88		% (catcher)
   89		), _Error1, (
   90			fail
   91		)),
   92		% Gets the expected and the actual lists of lines with errors
   93		findall(Line, evaluator:solve_goal(bpl_call(error_in_line(Line))), ExpectedLines),
   94		get_line_numbers(ErrorOutputFile, File, 'ERROR', Lines),
   95		% Compares both lists of line numbers
   96		sort(ExpectedLines, SortedExpectedLines),
   97		sort(Lines, SortedLines),
   98		compare_lines(SortedExpectedLines, SortedLines, error,
   99		              Passed, NewPassed, Failed, NewFailed)
  100	;
  101		% One of the files couldn't be loaded
  102		told,
  103		writef('Test files %w or %w couldn\'t be loaded.', [BaseFile, BaseLinesFile]), nl,
  104		write('Press any key to continue '),
  105		get_single_char(_),
  106		nl,
  107		NewPassed is Passed,
  108		NewFailed is Failed + 1
  109	),
  110	!,
  111	% Proceeds to the next file
  112	run_error_test_files(MoreFiles, MoreLinesFiles,
  113	                     NewPassed, FinalPassed, NewFailed, FinalFailed).
 run_warning_test_files(+Files, +Passed, -FinalPassed, +Failed, -FinalFailed)
Loads each of the Prolog or Bousi-Prolog source code files of the Files list, and verifies that these files have exactly the same warnings that are indicated in them (by means of the warning_in_line/1 predicate).

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
- compare_lines/7
  131run_warning_test_files([], FinalPassed, FinalPassed, FinalFailed, FinalFailed).
  132
  133run_warning_test_files([File|MoreFiles], Passed, FinalPassed, Failed, FinalFailed) :-
  134	file_base_name(File, BaseFile),
  135	write('------------------------------------------------------------------------------'), nl,
  136	writef('Running warning test file %w', [BaseFile]), nl,
  137	write('------------------------------------------------------------------------------'), nl,
  138	(
  139		% Loads the file with warnings, which is the same file that
  140		% can be used to get the lines where the warnings are located
  141		tmp_file('test', ErrorOutputFile),
  142		catch((
  143			tell(ErrorOutputFile),
  144			bplShell:ld(File, [f]),
  145			bplShell:last_program_loaded(LoadedFile, ''),
  146			file_base_name(LoadedFile, BaseFile),
  147			told,
  148			!
  149		% (catcher)
  150		), _Error, (
  151			told,
  152			fail
  153		)),
  154		% Gets the expected and the actual lists of lines with warnings
  155		findall(Line, evaluator:solve_goal(bpl_call(warning_in_line(Line))), ExpectedLines),
  156		get_line_numbers(ErrorOutputFile, File, 'WARNING', Lines),
  157		% Compares both lists of line numbers
  158		sort(ExpectedLines, SortedExpectedLines),
  159		sort(Lines, SortedLines),
  160		compare_lines(SortedExpectedLines, SortedLines, warning,
  161		              Passed, NewPassed, Failed, NewFailed)
  162	;
  163		% File couldn't be loaded
  164		told,
  165		writef('Test file %w couldn\'t be loaded.', [BaseFile]), nl,
  166		write('Press any key to continue '),
  167		get_single_char(_),
  168		nl,
  169		NewPassed is Passed,
  170		NewFailed is Failed + 1
  171	),
  172	!,
  173	% Proceeds to the next file
  174	run_warning_test_files(MoreFiles, NewPassed, FinalPassed, NewFailed, FinalFailed).
 compare_lines(+ExpectedLines, +Lines, +MessageType, +Passed, -FinalPassed, +Failed, -FinalFailed)
Compares the line numbers of the ExpectedLines with the line numbers of the Lines lists. Each comparison is a test, which will pass only if the line numbers are exactly the same and are located in the same position in both lists. An extra test will be used to check if one of the lists has more line numbers than the other one.

Passed/FinalPassed and Failed/FinalFailed are two accumulator pairs: FinalPassed will be unified with Passed plus the number of matched lines, whereas FinalFailed will be unified with Failed plus the number of unmatched lines.

  191compare_lines([], [], MessageType,
  192              Passed, FinalPassed, Failed, FinalFailed) :-
  193	% Both error lists are empty, so the last test passed
  194	writef('Testing that there\'re no more %ws... OK', [MessageType]), nl,
  195	FinalPassed is Passed + 1,
  196	FinalFailed is Failed.
  197
  198compare_lines([ExpectedLine|MoreExpectedLines], [], MessageType,
  199              Passed, FinalPassed, Failed, FinalFailed) :-
  200	% Error list is empty but expected error list isn't, so the last test failed
  201	writef('Testing %w in line %w... failed', [MessageType, ExpectedLine]), nl,
  202	length(MoreExpectedLines, UntestedLines),
  203	FinalPassed is Passed,
  204	FinalFailed is Failed + UntestedLines + 1,
  205	% Shows the results of the test
  206	writef('> Next %w was in line ......... (none)', [MessageType]), nl,
  207	writef('> Remaining expected %w lines . %w', [MessageType, MoreExpectedLines]), nl,
  208	writef('> Remaining %w lines .......... (none)', [MessageType]), nl,
  209	write('Press any key to continue '),
  210	get_single_char(_),
  211	nl.
  212
  213compare_lines([], [Line|MoreLines], MessageType,
  214              Passed, FinalPassed, Failed, FinalFailed) :-
  215	% Expected error list is empty but error list isn't, so the last test failed
  216	writef('Testing that there\'re no more %ws... failed', [MessageType]), nl,
  217	FinalPassed is Passed,
  218	FinalFailed is Failed + 1,
  219	% Shows the results of the test
  220	writef('> Next %w was in line ......... %w', [MessageType, Line]), nl,
  221	writef('> Remaining expected %w lines . (none)', [MessageType]), nl,
  222	writef('> Remaining %w lines .......... %w', [MessageType, MoreLines]), nl,
  223	write('Press any key to continue '),
  224	get_single_char(_),
  225	nl.
  226
  227compare_lines([ExpectedLine|MoreExpectedLines], [Line|MoreLines], MessageType,
  228	          Passed, FinalPassed, Failed, FinalFailed) :-
  229	writef('Testing %w in line %w... ', [MessageType, ExpectedLine]),
  230	(
  231		ExpectedLine == Line,
  232		% Test passed
  233		write('OK'), nl,
  234		NewPassed is Passed + 1,
  235		NewFailed is Failed,
  236		% Compares the remaining lines
  237		compare_lines(MoreExpectedLines, MoreLines, MessageType,
  238			          NewPassed, FinalPassed, NewFailed, FinalFailed)
  239	;
  240		% Test failed
  241		write('failed'), nl,
  242% 		length(MoreExpectedLines, UntestedLines), % WARNING: What are these three lines for?
  243% 		NewPassed is Passed, 
  244% 		NewFailed is Failed + UntestedLines + 1,
  245		% Shows the results of the test
  246		writef('> Next %w was in line ......... %w', [MessageType, Line]), nl,
  247		writef('> Remaining expected %w lines . %w', [MessageType, MoreExpectedLines]), nl,
  248		writef('> Remaining %w lines .......... %w', [MessageType, MoreLines]), nl,
  249		write('Press any key to continue '),
  250		get_single_char(_),
  251		nl,
  252		% When an error is found the comparison is stopped
  253		FinalPassed is Passed,
  254		FinalFailed is Failed
  255	).
  256
  257
  258
  259%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  260% Helper predicates
  261%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 get_line_numbers(+File, +SourceFile, +MessageType, -Lines)
Reads the specified File and looks for lines which start with the following substring: "<MessageType>: <SourceFile>:<Line>". Lines will be unified with a list containing all the Line numbers from these messages.
  272get_line_numbers(File, SourceFile, MessageType, Lines) :-
  273	open(File, read, Stream),
  274	search_messages_in_stream(Stream, SourceFile, MessageType, Lines),
  275	close(Stream).
 search_messages_in_stream(+Stream, +SourceFile, +MessageType, -Lines)
Scans all the lines from the specified Stream and looks for lines which start with the following substring: "<MessageType>: <SourceFile>:<Line>". Lines will be unified with a list containing all the Line numbers from these messages.
  286search_messages_in_stream(Stream, _SourceFile, _MessageType, []) :-
  287	% Checks if EOF has been reached
  288	at_end_of_stream(Stream), !.
  289
  290search_messages_in_stream(Stream, SourceFile, MessageType, Lines) :-
  291	% Gets the next line from the stream
  292	read_line_to_codes(Stream, Codes),
  293	atom_codes(String, Codes),
  294	% Checks if the line contains an error or warning message; these
  295	% messages must be like "ERROR: path/to/file:line:column: message text"
  296	concat_atom([MessageType, ': ', SourceFile, ':'], Substring),
  297	(sub_atom(String, 0, MessageIdx, _, Substring) ->
  298		% Extracts the line number from the error or warning message
  299		sub_atom(String, MessageIdx, NumberLen, _, LineNumberAsAtom),
  300		NumberIdx is MessageIdx + NumberLen,
  301		sub_atom(String, NumberIdx, 1, _, ':'),
  302		!,
  303		% Adds the line number to the list that will be returned
  304		atom_number(LineNumberAsAtom, LineNumber),
  305		Lines = [LineNumber|MoreLines]
  306	;
  307		% No error or warning message was found in this line
  308		Lines = MoreLines
  309	),
  310	% Goes on scanning the stream
  311	search_messages_in_stream(Stream, SourceFile, MessageType, MoreLines).
 add_path_to_files(+Files, -FullPaths, +BasePath)
Concatenates BasePath with each of the filenames in Files and returns the resulting paths in FullPaths.
  320add_path_to_files([], [], _BasePath).
  321
  322add_path_to_files([File|MoreFiles], [FullPath|MoreFullPaths], BasePath) :-
  323	(concat_atom([_, '/'], BasePath) ->
  324		concat_atom([BasePath, File], FullPath)
  325	;
  326		concat_atom([BasePath, '/', File], FullPath)
  327	),
  328	add_path_to_files(MoreFiles, MoreFullPaths, BasePath).
  329
  330
  331
  332%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  333% Constant predicates
  334%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 error_test_files(?Files, ?LinesFiles)
Returns the list of Prolog or Bousi-Prolog source code files that are used by this module to generate error messages, and the list of files that can be used to get the lines where the errors are located.
  345error_test_files(['errors_directives.bpl'], ['errors_directives_lines.bpl']).
  346% error_test_files(['errors_directives.bpl', 'errors_other.bpl',
  347%                   'errors_comments.bpl', 'errors_bpl.bpl'],
  348%                  ['errors_directives_lines.bpl', 'errors_other_lines.bpl',
  349%                   'errors_comments_lines.bpl', 'errors_bpl_lines.bpl']).
 warning_test_files(?Files)
Returns the list of Prolog or Bousi-Prolog source code files that are used by this module to generate warning messages. As files with warnings can be loaded into the database, these files also contain the lines where the warnings are located.
  360warning_test_files(['errors_warnings.bpl'])