]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/regtest.ml
Regtest fixed. It can now work also with multiple answers.
[helm.git] / helm / gTopLevel / regtest.ml
1 (* Copyright (C) 2004, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 open Printf
27
28 let argc = Array.length Sys.argv
29
30 let rawsep = "###"
31 let sep = Pcre.regexp (sprintf "^%s" rawsep)
32 let sep2 = Pcre.regexp (sprintf "^%s%s" rawsep rawsep)
33 let print s = print_string s; flush stdout
34 let print_endline s = print_endline s
35 let print_endline_to_channel ch s = output_string ch (s ^ "\n")
36
37 type state = Term | EMetasenv | ETerm | EType | EReduced
38
39 (* regtest file format
40  *    < cic term in concrete syntax >
41  *    separator (* see sep above *)
42  *    < expected metasenv after disambiguation (CicMetaSubst.ppmetasenv)  >
43  *    separator (* see sep above *)
44  *    < expected cic term after disambiguation (CicPp.ppterm) >
45  *    separator (* see sep above *)
46  *    < expected cic type as per type_of (CicPp.ppterm) >
47  *    separator (* see sep above *)
48  *    < expected reduced cic term as (CicPp.ppterm) >
49  *)
50
51 type regtest = {
52   term: string; (* raw cic term *)
53   emetasenv : string; (* expected metasenv *)
54   eterm: string;  (* expected term *)
55   etype: string;  (* expected type *)
56   ereduced: string; (* expected reduced term *)
57 }
58
59 let print_test tests fname =
60   let oc = open_out fname in
61   output_string oc (List.hd tests).term;
62   let i = ref 0 in
63   List.iter
64    (function test ->
65      incr i ;
66      output_string oc
67        (String.concat ""
68          [ sprintf "%s%s INTERPRETATION NUMBER %d %s%s\n" rawsep rawsep !i rawsep rawsep ;
69            sprintf "%s (* METASENV after disambiguation  *)\n" rawsep;
70            test.emetasenv;
71            sprintf "%s (* TERM after disambiguation      *)\n" rawsep;
72            test.eterm;
73            sprintf "%s (* TYPE_OF the disambiguated term *)\n" rawsep;
74            test.etype;
75            sprintf "%s (* REDUCED disambiguated term     *)\n" rawsep;
76            test.ereduced ])
77    ) tests;
78   close_out oc
79
80 let parse_regtest =
81   let term = Buffer.create 1024 in  (* raw term *)
82   let emetasenv = Buffer.create 1024 in  (* expected metasenv *)
83   let eterm = Buffer.create 1024 in (* raw expected term *)
84   let etype = Buffer.create 1024 in (* raw expected type *)
85   let ereduced = Buffer.create 1024 in (* raw expected reducted term *)
86   let state = ref Term in
87   let bump_state () =
88     match !state with
89     | Term -> state := EMetasenv
90     | EMetasenv -> state := ETerm
91     | ETerm -> state := EType
92     | EType -> state := EReduced
93     | EReduced -> assert false
94   in
95   let buffer_of_state = function
96     | Term ->  term | EMetasenv -> emetasenv | ETerm -> eterm | EType -> etype
97     | EReduced -> ereduced
98   in
99   let clear_buffers () =
100     List.iter Buffer.clear [ emetasenv; eterm; etype; ereduced ]
101   in
102   fun fname ->
103     state := Term;
104     let first = ref true in
105     let res = ref [] in
106     let push_res () =
107      res :=
108       { term = Buffer.contents term;
109        emetasenv = Buffer.contents emetasenv;
110        eterm = Buffer.contents eterm;
111        etype = Buffer.contents etype;
112        ereduced = Buffer.contents ereduced } :: !res ;
113     in
114     Buffer.clear term;
115     let ic = open_in fname in
116     (try
117       while true do
118         let line = input_line ic in
119         match line with
120         | l when Pcre.pmatch ~rex:sep2 l ->
121             if !first then first := false else push_res () ;
122             clear_buffers ();
123             state := Term
124         | l when Pcre.pmatch ~rex:sep l -> bump_state ()
125         | l -> Buffer.add_string (buffer_of_state !state) (line ^ "\n")
126       done
127     with End_of_file -> ());
128     push_res () ;
129     List.rev !res
130
131 let as_expected_one och expected found = (* ignores "term" field *)
132   let eterm_ok = expected.eterm = found.eterm in
133   let emetasenv_ok = expected.emetasenv = found.emetasenv in
134   let etype_ok = expected.etype = found.etype in
135   let ereduced_ok = expected.ereduced = found.ereduced in
136   let outcome = eterm_ok && emetasenv_ok && etype_ok && ereduced_ok in
137    begin
138     let print_endline s = print_endline_to_channel (Lazy.force och) s in
139     if not eterm_ok then begin
140       print_endline "### Term mismatch ###";
141       print_endline "# expected:";
142       print_endline ("  " ^ expected.eterm);
143       print_endline "# found:";
144       print_endline ("  " ^ found.eterm);
145     end;
146     if not emetasenv_ok then begin
147       print_endline "### Metasenv mismatch ###";
148       print_endline "# expected:";
149       print_endline ("  " ^ expected.emetasenv);
150       print_endline "# found:";
151       print_endline ("  " ^ found.emetasenv);
152     end;
153     if not etype_ok then begin
154       print_endline "### Type mismatch ###";
155       print_endline "# expected:";
156       print_endline ("  " ^ expected.etype);
157       print_endline "# found:";
158       print_endline ("  " ^ found.etype);
159     end;
160     if expected.ereduced <> found.ereduced then begin
161       print_endline "### Reduced term mismatch ###";
162       print_endline "# expected:";
163       print_endline ("  " ^ expected.ereduced);
164       print_endline "# found:";
165       print_endline ("  " ^ found.ereduced);
166     end;
167    end;
168   outcome
169
170 let as_expected report_fname expected found =
171  (if Sys.file_exists report_fname then Sys.remove report_fname) ;
172  let och = lazy (open_out report_fname) in
173  let print_endline s = print_endline_to_channel (Lazy.force och) s in
174   let rec aux =
175    function
176       [],[] -> true
177     | ex::extl, fo::fotl ->
178        as_expected_one och ex fo &&
179        aux (extl,fotl)
180     | [],found ->
181        print_endline "### Too many interpretations found" ;
182        false
183     | expected,[] ->
184        print_endline "### Too few interpretations found" ;
185        false
186   in
187    let outcome = aux (expected,found) in
188     (if Lazy.lazy_is_val och then close_out (Lazy.force och)) ;
189     outcome
190
191 let test_this mqi_handle uri_pred raw_term =
192   let empty_context = [] in
193   List.map
194    (function (metasenv, cic_term) ->
195      let etype =
196       try
197        CicPp.ppterm
198         (CicTypeChecker.type_of_aux' metasenv empty_context cic_term)
199       with _ -> "MALFORMED"
200      in
201      let ereduced =
202       try
203        CicPp.ppterm (CicReduction.whd empty_context cic_term)
204       with _ -> "MALFORMED"
205      in
206      {
207        term = raw_term;  (* useless *)
208        emetasenv = CicMetaSubst.ppmetasenv metasenv [] ^ "\n";
209        eterm = CicPp.ppterm cic_term ^ "\n";
210        etype = etype ^ "\n";
211        ereduced = ereduced ^ "\n";
212      }
213    ) (BatchParser.parse mqi_handle ~uri_pred raw_term)
214
215 let dump_environment filename =
216   try
217     let oc = open_out filename in
218     CicEnvironment.dump_to_channel oc;
219     close_out oc
220   with exc ->
221     prerr_endline
222      ("DUMP_ENVIRONMENT FAILURE, uncaught excecption " ^
223        Printexc.to_string exc) ;
224     raise exc
225
226 let restore_environment filename =
227   if Sys.file_exists filename then
228    begin
229     try
230       let ic = open_in filename in
231       CicEnvironment.restore_from_channel ic;
232       close_in ic
233     with exc ->
234       prerr_endline
235        ("RESTORE_ENVIRONMENT FAILURE, uncaught excecption " ^
236          Printexc.to_string exc) ;
237       raise exc
238    end
239   else
240    CicEnvironment.empty ()
241
242 let main mqi_handle generate  dump fnames tryvars varsprefix =
243  let uri_pred = BatchParser.uri_pred_of_conf tryvars varsprefix in
244  if generate then
245   begin
246    (* gen mode *)
247    print_endline "[ Gen mode ]";
248    List.iter
249     (function fname ->
250       let test_fname = fname ^ ".test" in
251       let env_fname = fname ^ ".env" in
252       print_endline (sprintf "Generating regtest %s -> %s\n ..."
253         fname test_fname);
254       let raw_term = (List.hd (parse_regtest fname)).term in
255       let results = test_this mqi_handle uri_pred raw_term in
256       print_test results test_fname ;
257       if dump then dump_environment env_fname ;
258     ) fnames
259   end else
260    begin
261     (* regtest mode *)
262     print_endline "[ Regtest mode ]";
263     let (ok, nok) = (ref 0, ref []) in
264     List.iter
265      (function fname ->
266        let env_fname = fname ^ ".env" in
267        let test_fname = fname ^ ".test" in
268        let report_fname = fname ^ ".report" in
269        restore_environment env_fname ;
270        let time = Unix.gettimeofday () in
271        print ("Processing " ^ fname ^":\t") ;
272        let is_ok = 
273         try
274           let expected = parse_regtest test_fname in
275           let actual = test_this mqi_handle uri_pred (List.hd expected).term in
276           if dump then dump_environment env_fname ;
277           if as_expected report_fname expected actual then
278            (incr ok ; true)
279           else
280            (nok := fname :: !nok ; false)
281         with e -> (nok := fname :: !nok ; false)
282        in
283         let timediff = Unix.gettimeofday () -. time in
284          print (sprintf "done in %f seconds\t" timediff) ;
285          print_endline
286           (if is_ok then
287             "\e[01;32m[   OK   ]\e[00m"
288           else
289             "\e[01;31m[ FAILED ]\e[00m")
290      ) fnames ;
291     print_endline "*** Summary ***";
292     print_endline (sprintf "Succeeded: %d" !ok);
293     print_endline (sprintf "Failed: %d" (List.length !nok));
294     List.iter (fun fname -> print_endline (sprintf "  %s failed :-(" fname))
295       (List.rev !nok)
296   end
297
298 let _ =
299
300  Helm_registry.load_from "gTopLevel.conf.xml";
301  HelmLogger.register_log_callback
302   (fun ?(append_NL = true) msg ->
303     (if append_NL then prerr_endline else prerr_string)
304       (HelmLogger.string_of_html_msg msg));
305  
306  let mqi_debug_fun = ignore in
307  let mqi_handle = MQIConn.init ~log:mqi_debug_fun () in
308  
309  let fnames = ref [] in
310  let gen = ref false in
311  let tryvars = ref false in
312  let dump = ref false in
313  let nodump = ref false in
314  let varsprefix = ref "" in
315  let usage = "regtest [OPTION] ... test1 ..." in
316  let spec =
317    ["-gen", Arg.Set gen,
318       "generate the tests; implies -dump (unless -nodump is specified)" ;
319     "--gen", Arg.Set gen,
320       "generate the tests; implies -dump (unless -nodump is specified)" ;
321     "-dump", Arg.Set dump, "dump the final environment" ;
322     "--dump", Arg.Set dump, "dump the final environment" ;
323     "-nodump", Arg.Set nodump, "do not dump the final environment" ;
324     "--nodump", Arg.Set nodump, "do not dump the final environment" ;
325     "-vars", Arg.Set tryvars, "try also variables" ;
326     "-novars", Arg.Clear tryvars, "do not try variables (default)" ;
327     "-varsprefix", Arg.Set_string varsprefix,
328       "limit variable choices to URIs beginning with prefix" ;
329     "--varsprefix", Arg.Set_string varsprefix,
330       "limit variable choices to URIs beginning with prefix" ;
331    ]
332  in
333   Arg.parse spec (fun filename -> fnames := filename::!fnames ) usage ;
334   if !fnames = [] then
335    Arg.usage spec (Sys.argv.(0) ^ ": missing argument test. You must provide at least one test file.\n" ^ usage) ;
336   main mqi_handle !gen ((!gen || !dump) && (not !nodump)) !fnames !tryvars !varsprefix;
337   MQIConn.close mqi_handle