]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/regtest.ml
The disambiguation now returns a list of interpretations.
[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 print s = print_string s; flush stdout
33 let print_endline s = print_endline s
34 let print_endline_to_channel ch s = output_string ch (s ^ "\n")
35
36 type state = Term | EMetasenv | ETerm | EType | EReduced
37
38 (* regtest file format
39  *    < cic term in concrete syntax >
40  *    separator (* see sep above *)
41  *    < expected metasenv after disambiguation (CicMetaSubst.ppmetasenv)  >
42  *    separator (* see sep above *)
43  *    < expected cic term after disambiguation (CicPp.ppterm) >
44  *    separator (* see sep above *)
45  *    < expected cic type as per type_of (CicPp.ppterm) >
46  *    separator (* see sep above *)
47  *    < expected reduced cic term as (CicPp.ppterm) >
48  *)
49
50 type regtest = {
51   term: string; (* raw cic term *)
52   emetasenv : string; (* expected metasenv *)
53   eterm: string;  (* expected term *)
54   etype: string;  (* expected type *)
55   ereduced: string; (* expected reduced term *)
56 }
57
58 let print_test tests fname =
59   let oc = open_out fname in
60   output_string oc (List.hd tests).term;
61   let i = ref 0 in
62   List.iter
63    (function test ->
64      incr i ;
65      output_string oc
66        (String.concat ""
67          [ sprintf "INTERPRETATION NUMBER %d\n" !i;
68            sprintf "%s (* METASENV after disambiguation  *)\n" rawsep;
69            test.emetasenv;
70            sprintf "%s (* TERM after disambiguation      *)\n" rawsep;
71            test.eterm;
72            sprintf "%s (* TYPE_OF the disambiguated term *)\n" rawsep;
73            test.etype;
74            sprintf "%s (* REDUCED disambiguated term     *)\n" rawsep;
75            test.ereduced;
76            "\n" ])
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 [ term; emetasenv; eterm; etype; ereduced ]
101   in
102   fun fname ->
103     state := Term;
104     clear_buffers ();
105     let ic = open_in fname in
106     (try
107       while true do
108         let line = input_line ic in
109         match line with
110         | l when Pcre.pmatch ~rex:sep l -> bump_state ()
111         | l -> Buffer.add_string (buffer_of_state !state) (line ^ "\n")
112       done
113     with End_of_file -> ());
114     [{ term = Buffer.contents term;
115       emetasenv = Buffer.contents emetasenv;
116       eterm = Buffer.contents eterm;
117       etype = Buffer.contents etype;
118       ereduced = Buffer.contents ereduced }]
119
120 let as_expected_one och expected found = (* ignores "term" field *)
121   let eterm_ok = expected.eterm = found.eterm in
122   let emetasenv_ok = expected.emetasenv = found.emetasenv in
123   let etype_ok = expected.etype = found.etype in
124   let ereduced_ok = expected.ereduced = found.ereduced in
125   let outcome = eterm_ok && emetasenv_ok && etype_ok && ereduced_ok in
126    begin
127     let print_endline = print_endline_to_channel (Lazy.force och) in
128     if not eterm_ok then begin
129       print_endline "### Term mismatch ###";
130       print_endline "# expected:";
131       print_endline ("  " ^ expected.eterm);
132       print_endline "# found:";
133       print_endline ("  " ^ found.eterm);
134     end;
135     if not emetasenv_ok then begin
136       print_endline "### Metasenv mismatch ###";
137       print_endline "# expected:";
138       print_endline ("  " ^ expected.emetasenv);
139       print_endline "# found:";
140       print_endline ("  " ^ found.emetasenv);
141     end;
142     if not etype_ok then begin
143       print_endline "### Type mismatch ###";
144       print_endline "# expected:";
145       print_endline ("  " ^ expected.etype);
146       print_endline "# found:";
147       print_endline ("  " ^ found.etype);
148     end;
149     if expected.ereduced <> found.ereduced then begin
150       print_endline "### Reduced term mismatch ###";
151       print_endline "# expected:";
152       print_endline ("  " ^ expected.ereduced);
153       print_endline "# found:";
154       print_endline ("  " ^ found.ereduced);
155     end;
156    end;
157   outcome
158
159 let as_expected report_fname expected found =
160  (if Sys.file_exists report_fname then Sys.remove report_fname) ;
161  let och = lazy (open_out report_fname) in
162  let print_endline = print_endline_to_channel (Lazy.force och) in
163   let rec aux =
164    function
165       [],[] -> true
166     | ex::extl, fo::fotl ->
167        as_expected_one och ex fo &&
168        aux (extl,fotl)
169     | [],found ->
170        print_endline "### Too many interpretations found" ;
171        false
172     | expected,[] ->
173        print_endline "### Too few interpretations found" ;
174        false
175   in
176    let outcome = aux (expected,found) in
177     (if Lazy.lazy_is_val och then close_out (Lazy.force och)) ;
178     outcome
179
180 let test_this mqi_handle uri_pred raw_term =
181   let empty_context = [] in
182   List.map
183    (function (metasenv, cic_term) ->
184      let etype =
185       try
186        CicPp.ppterm
187         (CicTypeChecker.type_of_aux' metasenv empty_context cic_term)
188       with _ -> "MALFORMED"
189      in
190      let ereduced =
191       try
192        CicPp.ppterm (CicReduction.whd empty_context cic_term)
193       with _ -> "MALFORMED"
194      in
195      {
196        term = raw_term;  (* useless *)
197        emetasenv = CicMetaSubst.ppmetasenv metasenv [] ^ "\n";
198        eterm = CicPp.ppterm cic_term ^ "\n";
199        etype = etype ^ "\n";
200        ereduced = ereduced ^ "\n";
201      }
202    ) (BatchParser.parse mqi_handle ~uri_pred raw_term)
203
204 let dump_environment filename =
205   try
206     let oc = open_out filename in
207     CicEnvironment.dump_to_channel oc;
208     close_out oc
209   with exc ->
210     prerr_endline
211      ("DUMP_ENVIRONMENT FAILURE, uncaught excecption " ^
212        Printexc.to_string exc) ;
213     raise exc
214
215 let restore_environment filename =
216   if Sys.file_exists filename then
217    begin
218     try
219       let ic = open_in filename in
220       CicEnvironment.restore_from_channel ic;
221       close_in ic
222     with exc ->
223       prerr_endline
224        ("RESTORE_ENVIRONMENT FAILURE, uncaught excecption " ^
225          Printexc.to_string exc) ;
226       raise exc
227    end
228   else
229    CicEnvironment.empty ()
230
231 let main mqi_handle generate  dump fnames tryvars varsprefix =
232  let uri_pred = BatchParser.uri_pred_of_conf tryvars varsprefix in
233  if generate then
234   begin
235    (* gen mode *)
236    print_endline "[ Gen mode ]";
237    List.iter
238     (function fname ->
239       let test_fname = fname ^ ".test" in
240       let env_fname = fname ^ ".env" in
241       print_endline (sprintf "Generating regtest %s -> %s\n ..."
242         fname test_fname);
243       let raw_term = (List.hd (parse_regtest fname)).term in
244       let results = test_this mqi_handle uri_pred raw_term in
245       print_test results test_fname ;
246       if dump then dump_environment env_fname ;
247     ) fnames
248   end else
249    begin
250     (* regtest mode *)
251     print_endline "[ Regtest mode ]";
252     let (ok, nok) = (ref 0, ref []) in
253     List.iter
254      (function fname ->
255        let env_fname = fname ^ ".env" in
256        let test_fname = fname ^ ".test" in
257        let report_fname = fname ^ ".report" in
258        restore_environment env_fname ;
259        let time = Unix.gettimeofday () in
260        print ("Processing " ^ fname ^":\t") ;
261        let is_ok = 
262         try
263           let expected = parse_regtest test_fname in
264           let actual = test_this mqi_handle uri_pred (List.hd expected).term in
265           if dump then dump_environment env_fname ;
266           if as_expected report_fname expected actual then
267            (incr ok ; true)
268           else
269            (nok := fname :: !nok ; false)
270         with e -> (nok := fname :: !nok ; false)
271        in
272         let timediff = Unix.gettimeofday () -. time in
273          print (sprintf "done in %f seconds\t" timediff) ;
274          print_endline
275           (if is_ok then
276             "\e[01;32m[   OK   ]\e[00m"
277           else
278             "\e[01;31m[ FAILED ]\e[00m")
279      ) fnames ;
280     print_endline "*** Summary ***";
281     print_endline (sprintf "Succeeded: %d" !ok);
282     print_endline (sprintf "Failed: %d" (List.length !nok));
283     List.iter (fun fname -> print_endline (sprintf "  %s failed :-(" fname))
284       (List.rev !nok)
285   end
286
287 let _ =
288
289  Helm_registry.load_from "gTopLevel.conf.xml";
290  HelmLogger.register_log_callback
291   (fun ?(append_NL = true) msg ->
292     (if append_NL then prerr_endline else prerr_string)
293       (HelmLogger.string_of_html_msg msg));
294  
295  let mqi_debug_fun = ignore in
296  let mqi_handle = MQIConn.init ~log:mqi_debug_fun () in
297  
298  let fnames = ref [] in
299  let gen = ref false in
300  let tryvars = ref false in
301  let dump = ref false in
302  let nodump = ref false in
303  let varsprefix = ref "" in
304  let usage = "regtest [OPTION] ... test1 ..." in
305  let spec =
306    ["-gen", Arg.Set gen,
307       "generate the tests; implies -dump (unless -nodump is specified)" ;
308     "--gen", Arg.Set gen,
309       "generate the tests; implies -dump (unless -nodump is specified)" ;
310     "-dump", Arg.Set dump, "dump the final environment" ;
311     "--dump", Arg.Set dump, "dump the final environment" ;
312     "-nodump", Arg.Set nodump, "do not dump the final environment" ;
313     "--nodump", Arg.Set nodump, "do not dump the final environment" ;
314     "-vars", Arg.Set tryvars, "try also variables" ;
315     "-novars", Arg.Clear tryvars, "do not try variables (default)" ;
316     "-varsprefix", Arg.Set_string varsprefix,
317       "limit variable choices to URIs beginning with prefix" ;
318     "--varsprefix", Arg.Set_string varsprefix,
319       "limit variable choices to URIs beginning with prefix" ;
320    ]
321  in
322   Arg.parse spec (fun filename -> fnames := filename::!fnames ) usage ;
323   if !fnames = [] then
324    Arg.usage spec (Sys.argv.(0) ^ ": missing argument test. You must provide at least one test file.\n" ^ usage) ;
325   main mqi_handle !gen ((!gen || !dump) && (not !nodump)) !fnames !tryvars !varsprefix;
326   MQIConn.close mqi_handle