Merge branch 'master' of /home/pl/chr
[chr.git] / chr_test.pl
blob182a14a527e6ef305e566bbf84ca639e24149efb
1 /* $Id$
3 Part of CHR (Constraint Handling Rules)
5 Author: Jan Wielemaker
6 E-mail: wielemak@science.uva.nl
7 WWW: http://www.swi-prolog.org
8 Copyright (C): 2005,2006, University of Amsterdam
10 This program is free software; you can redistribute it and/or
11 modify it under the terms of the GNU General Public License
12 as published by the Free Software Foundation; either version 2
13 of the License, or (at your option) any later version.
15 This program is distributed in the hope that it will be useful,
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
18 GNU General Public License for more details.
20 You should have received a copy of the GNU Lesser General Public
21 License along with this library; if not, write to the Free Software
22 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
24 As a special exception, if you link this library with other files,
25 compiled with a Free Software compiler, to produce an executable, this
26 library does not by itself cause the resulting executable to be covered
27 by the GNU General Public License. This exception does not however
28 invalidate any other reasons why the executable file might be covered by
29 the GNU General Public License.
32 :- asserta(user:file_search_path(chr, '.')).
33 :- asserta(user:file_search_path(library, '.')).
34 :- use_module(library(chr)).
35 %% :- use_module(chr). % == library(chr)
37 :- set_prolog_flag(optimise, true).
38 %:- set_prolog_flag(trace_gc, true).
40 :- format('CHR test suite. To run all tests run ?- test.~n~n', []).
42 /*******************************
43 * SCRIPTS *
44 *******************************/
47 :- dynamic
48 script_dir/1.
50 set_script_dir :-
51 script_dir(_), !.
52 set_script_dir :-
53 find_script_dir(Dir),
54 assert(script_dir(Dir)).
56 find_script_dir(Dir) :-
57 prolog_load_context(file, File),
58 follow_links(File, RealFile),
59 file_directory_name(RealFile, Dir).
61 follow_links(File, RealFile) :-
62 read_link(File, _, RealFile), !.
63 follow_links(File, File).
66 :- set_script_dir.
68 run_test_script(Script) :-
69 file_base_name(Script, Base),
70 file_name_extension(Pred, _, Base),
71 format(' ~w~n',[Script]),
72 load_files(Script, []), %[silent(true)]),
73 Pred.
75 run_test_scripts(Directory) :-
76 ( script_dir(ScriptDir),
77 concat_atom([ScriptDir, /, Directory], Dir),
78 exists_directory(Dir)
79 -> true
80 ; Dir = Directory
82 atom_concat(Dir, '/*.chr', Pattern),
83 expand_file_name(Pattern, Files),
84 file_base_name(Dir, BaseDir),
85 format('Running scripts from ~w ', [BaseDir]), flush,
86 run_scripts(Files),
87 format(' done~n').
89 run_scripts([]).
90 run_scripts([H|T]) :-
91 ( catch(run_test_script(H), Except, true)
92 -> ( var(Except)
93 -> put(.), flush
94 ; Except = blocked(Reason)
95 -> assert(blocked(H, Reason)),
96 put(!), flush
97 ; script_failed(H, Except)
99 ; script_failed(H, fail)
101 run_scripts(T).
103 script_failed(File, fail) :-
104 format('~NScript ~w failed~n', [File]),
105 assert(failed(script(File))).
106 script_failed(File, Except) :-
107 message_to_string(Except, Error),
108 format('~NScript ~w failed: ~w~n', [File, Error]),
109 assert(failed(script(File))).
112 /*******************************
113 * TEST MAIN-LOOP *
114 *******************************/
116 testdir('Tests').
118 :- dynamic
119 failed/1,
120 blocked/2.
122 test :-
123 retractall(failed(_)),
124 retractall(blocked(_,_)),
125 scripts,
126 report_blocked,
127 report_failed.
129 scripts :-
130 forall(testdir(Dir), run_test_scripts(Dir)).
133 report_blocked :-
134 findall(Head-Reason, blocked(Head, Reason), L),
135 ( L \== []
136 -> format('~nThe following tests are blocked:~n', []),
137 ( member(Head-Reason, L),
138 format(' ~p~t~40|~w~n', [Head, Reason]),
139 fail
140 ; true
142 ; true
144 report_failed :-
145 findall(X, failed(X), L),
146 length(L, Len),
147 ( Len > 0
148 -> format('~n*** ~w tests failed ***~n', [Len]),
149 fail
150 ; format('~nAll tests passed~n', [])
153 test_failed(R, Except) :-
154 clause(Head, _, R),
155 functor(Head, Name, 1),
156 arg(1, Head, TestName),
157 clause_property(R, line_count(Line)),
158 clause_property(R, file(File)),
159 ( Except == fail
160 -> format('~N~w:~d: Test ~w(~w) failed~n',
161 [File, Line, Name, TestName])
162 ; message_to_string(Except, Error),
163 format('~N~w:~d: Test ~w(~w):~n~t~8|ERROR: ~w~n',
164 [File, Line, Name, TestName, Error])
166 assert(failed(Head)).
168 blocked(Reason) :-
169 throw(blocked(Reason)).