]> matita.cs.unibo.it Git - helm.git/blob - helm/mathql_test/mqgtop.ml
16a5ea0a9862734c5965ca32096da18238ad1c4a
[helm.git] / helm / mathql_test / mqgtop.ml
1 (* Copyright (C) 2000, 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://cs.unibo.it/helm/.
24  *)
25
26 (*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
27  *)
28
29 let _ = MQueryStandard.init
30 let _ = MQueryHELM.init 
31
32 let query_num = ref 1
33
34 let interp_file = ref "interp.cic" 
35
36 let log_file = ref ""
37
38 let show_queries = ref false
39
40 let int_options = ref ""
41
42 let nl = " <p>\n"
43
44 module IO = MQueryIO
45 module U  = MQueryUtil
46 module I  = MQueryInterpreter
47 module C  = MQIConn
48 module G  = MQueryGenerator
49 module L  = MQGTopLexer
50 module P  = MQGTopParser
51 module TL = CicTextualLexer
52 module TP = CicTextualParser
53 module C3 = CGLocateInductive
54 module C2 = CGSearchPattern
55 module C1 = CGMatchConclusion
56 module GU = MQGUtil
57 module M  = MQueryMisc
58
59 let get_handle () = 
60    C.init (C.flags_of_string ! int_options)
61           (fun s -> print_string s; flush stdout) 
62              
63 let issue handle q =
64    let mode = [Open_wronly; Open_append; Open_creat; Open_text] in
65    let perm = 64 * 6 + 8 * 6 + 4 in
66    let time () =
67       let lt = Unix.localtime (Unix.time ()) in
68       "NEW LOG: " ^
69       string_of_int (lt.Unix.tm_mon + 1) ^ "-" ^
70       string_of_int (lt.Unix.tm_mday + 1) ^ "-" ^
71       string_of_int (lt.Unix.tm_year + 1900) ^ " " ^
72       string_of_int (lt.Unix.tm_hour) ^ ":" ^
73       string_of_int (lt.Unix.tm_min) ^ ":" ^
74       string_of_int (lt.Unix.tm_sec) 
75    in
76    let log q r = 
77       let och = open_out_gen mode perm ! log_file in
78       let out = output_string och in 
79       if ! query_num = 1 then out (time () ^ nl);
80       out ("Query: " ^ string_of_int ! query_num ^ nl);
81       IO.text_of_query out nl q;
82       out ("Result: " ^ nl);
83       IO.text_of_result out nl r;
84       close_out och
85    in
86    if ! show_queries then IO.text_of_query (output_string stdout) nl q;
87    let r = I.execute handle q in    
88    IO.text_of_result (output_string stdout) nl r;
89    if ! log_file <> "" then log q r; 
90    incr query_num;
91    flush stdout
92
93 let get_interp () =
94    let lexer = function
95       | TP.ID s                -> P.ID s
96       | TP.CONURI u            -> P.CONURI u
97       | TP.VARURI u            -> P.VARURI u
98       | TP.INDTYURI (u, p)     -> P.INDTYURI (u, p)
99       | TP.INDCONURI (u, p, s) -> P.INDCONURI (u, p, s)
100       | TP.LETIN               -> P.ALIAS
101       | TP.EOF                 -> P.EOF
102       | _                     -> assert false
103    in
104    let ich = open_in ! interp_file in
105    let lexbuf = Lexing.from_channel ich in
106    let f = P.interp (fun x -> lexer (TL.token x)) lexbuf in
107    close_in ich; f
108    
109 let get_terms interp = 
110    let interp = get_interp () in
111    let lexbuf = Lexing.from_channel stdin in
112    let rec aux () =
113       try
114          let dom, mk_term =
115             CicTextualParserContext.main [] [] CicTextualLexer.token lexbuf
116          in
117          (snd (mk_term interp)) :: aux ()
118       with
119       CicTextualParser0.Eof -> []
120    in
121    aux ()
122
123 let pp_term_of b uri = 
124    let s = try 
125       let body, ty = M.get_object (M.uriref_of_string uri) in
126       if b then CicPp.ppterm body else CicPp.ppterm ty 
127    with
128       | M.CurrentProof        -> "proof in progress"
129       | M.InductiveDefinition -> "inductive definition"
130       | M.IllFormedFragment   -> "ill formed fragment identifier"
131    in print_endline s; flush stdout
132
133 let rec display = function
134    | []           -> ()
135    | term :: tail -> 
136       display tail;
137       print_string ("? " ^ CicPp.ppterm term ^ nl);
138       flush stdout
139
140 let execute ich =
141    let lexbuf = Lexing.from_channel ich in
142    let handle = get_handle () in
143    let rec execute_aux () =
144       try 
145          let q = IO.query_of_text lexbuf in
146          issue handle q; execute_aux ()
147       with End_of_file -> ()
148    in
149    execute_aux ();
150    C.close handle
151
152 let compose () =
153    let handle = get_handle () in  
154    let cl = P.specs L.spec_token (Lexing.from_channel stdin) in
155    issue handle (G.compose cl);
156    C.close handle
157
158 let locate name =
159    let handle = get_handle () in  
160    issue handle (G.locate name); 
161    C.close handle
162
163 let unreferred target source =
164    let handle = get_handle () in  
165    issue handle (G.unreferred target source); 
166    C.close handle
167
168 let mpattern n m l =
169    let queries = ref [] in
170    let univ = Some C2.universe in 
171    let handle = get_handle () in
172    let rec pattern level = function
173       | []           -> ()
174       | term :: tail -> 
175          pattern level tail;
176          print_string ("? " ^ CicPp.ppterm term ^ nl);
177          let t = U.start_time () in
178          let om,rm,sm = C2.get_constraints term in
179          let oml,rml,sml = List.length om, List.length rm, List.length sm in 
180          let oo, ool = if level land 1 = 0 then None, 0 else Some om, oml in
181          let ro, rol = if level land 2 = 0 then None, 0 else Some rm, rml in
182          let so, sol = if level land 4 = 0 then None, 0 else Some sm, sml in
183          let q = G.query_of_constraints univ (om,rm,sm) (oo,ro,so) in 
184          if not (List.mem q ! queries) then
185          begin
186             issue handle q;
187             Printf.eprintf "[%i] " (pred ! query_num); flush stderr;
188             Printf.printf "%i GEN = %i: %s"
189                (pred ! query_num) (oml + rml + sml + ool + rol + sol) 
190                (U.stop_time t ^ nl);
191             flush stdout; queries := q :: ! queries
192          end
193    in 
194    for level = max m n downto min m n do
195       Printf.eprintf "\nmqgtop: pattern: trying level %i\n" level; 
196       flush stderr; pattern level l
197    done;
198    Printf.eprintf "\nmqgtop: pattern: %i queries issued\n" 
199       (List.length ! queries);
200    flush stderr;
201    C.close handle
202
203 let mbackward n m l =
204    let queries = ref [] in
205    let univ = Some C1.universe in
206    let handle = get_handle () in
207    let rec backward level = function
208       | []           -> ()
209       | term :: tail -> 
210          backward level tail;
211          print_string ("? " ^ CicPp.ppterm term ^ nl);
212          let t = U.start_time () in
213          let list_of_must, only = C1.get_constraints [] [] term in
214          let max_level = pred (List.length list_of_must) in 
215          let must = List.nth list_of_must (min level max_level) in 
216          let q = G.query_of_constraints univ (must, [], []) (Some only , None, None) in 
217          if not (List.mem q ! queries) then
218          begin
219             issue handle q;
220             Printf.eprintf "[%i] " (pred ! query_num); flush stderr;
221             Printf.printf "%i GEN = %i: %s"
222                (pred ! query_num) (List.length must) 
223                (U.stop_time t ^ nl);
224             flush stdout; queries := q :: ! queries
225          end
226    in 
227    for level = max m n downto min m n do
228       Printf.eprintf "\nmqgtop: backward: trying level %i\n" level; 
229       flush stderr; backward level l
230    done;
231    Printf.eprintf "\nmqgtop: backward: %i queries issued\n" 
232       (List.length ! queries);
233    flush stderr;
234    C.close handle
235
236 let inductive l = 
237    let queries = ref [] in
238    let univ = None in 
239    let handle = get_handle () in
240    let rec aux = function
241       | []           -> ()
242       | term :: tail -> 
243          aux tail;
244          print_string ("? " ^ CicPp.ppterm term ^ nl);
245          let t = U.start_time () in
246          let m = C3.get_constraints term in
247          let q = G.query_of_constraints univ m (None, None, None) in 
248          if not (List.mem q ! queries) then
249          begin
250             issue handle q;
251             Printf.eprintf "[%i] " (pred ! query_num); flush stderr;
252             Printf.printf "%i GEN: %s"
253                (pred ! query_num) (U.stop_time t ^ nl);
254             flush stdout; queries := q :: ! queries
255          end
256    in 
257    aux l;
258    Printf.eprintf "\nmqgtop: inductive: %i queries issued\n" 
259       (List.length ! queries);
260    flush stderr;
261    C.close handle
262
263 let check () =
264    let handle = get_handle () in
265    Printf.eprintf 
266       "mqgtop: current options: %s, connection: %s\n"  
267       ! int_options (if C.connected handle then "on" else "off");
268    C.close handle
269
270 let prerr_help () =
271    prerr_endline "\nUSAGE: mqgtop.opt OPTIONS < INPUTFILE\n"; 
272    prerr_endline "The tool provides a textual interface to the HELM Query Generator, used for";
273    prerr_endline "testing purposes. mqgtop reads its input from stdin and produces ith output";
274    prerr_endline "in HTML on stdout. The options can be one ore more of the following.\n";
275    prerr_endline "OPTIONS:\n";
276    prerr_endline "-h  -help               shows this help message";
277    prerr_endline "-q  -show-queries       outputs generated queries";
278    prerr_endline "-l  -log-file FILE      sets the log file";
279    prerr_endline "-o  -options STRING     sets the interpreter options";
280    prerr_endline "-c  -check              checks the database connection";
281    prerr_endline "-t  -typeof URI         outputs the CIC type of the given HELM object";
282    prerr_endline "-b  -bodyof URI         outputs the CIC body of the given HELM object";
283    prerr_endline "-x  -execute            issues a query given in the input file";
284    prerr_endline "-i  -interp FILE        sets the CIC short names interpretation file";
285    prerr_endline "-d  -disply             outputs the CIC terms given in the input file";
286    prerr_endline "-L  -locate ALIAS       issues the \"Locate\" query for the given alias";
287    prerr_endline "-U  T_PATTERN S_PATTERN issues the \"Unreferred\" query for the given patterns";
288    prerr_endline "-C  -compose            issues the \"Compose\" query reading its specifications";
289    prerr_endline "                        from the input file"; 
290    prerr_endline "-B  -backward LEVEL     issues the \"Backward\" query for the given level on all";
291    prerr_endline "                        CIC terms in the input file";
292    prerr_endline "-MB -multi-backward MAX issues the \"Backward\" query for each level from max to 0";
293    prerr_endline "                        on all CIC terms in the input file";
294    prerr_endline "-P  -pattern LEVEL      issues the \"Pattern\" query for the given level on all";
295    prerr_endline "                        CIC terms in the input file";
296    prerr_endline "-MP -multi-pattern      issues the \"Pattern\" query for each level from 7 to 0";
297    prerr_endline "                        on all CIC terms in the input file";
298    prerr_endline "-I                      issues the \"Inductive\" query on all CIC terms in the";
299    prerr_endline "                        input file\n";
300    prerr_endline "NOTES: * current interpreter options are:";
301    prerr_endline "         P (postgres), G (Galax), S (show statistics), Q (quiet)";
302    prerr_endline "       * CIC terms are read with the HELM CIC Textual Parser";
303    prerr_endline "       * -typeof / -bodyof do not work with proofs in progress\n"
304
305 let rec parse = function
306    | [] -> ()
307    | ("-h"|"-help") :: rem -> prerr_help (); parse rem
308    | ("-i"|"-interp") :: arg :: rem -> interp_file := arg; parse rem
309    | ("-d"|"-display") :: rem -> display (get_terms ()); parse rem
310    | ("-t"|"-typeof") :: arg :: rem -> pp_term_of false arg; parse rem
311    | ("-b"|"-bodyof") :: arg :: rem -> pp_term_of true arg; parse rem
312    | ("-x"|"-execute") :: rem -> execute stdin; parse rem
313    | ("-q"|"-show-queries") :: rem -> show_queries := true; parse rem
314    | ("-o"|"-options") :: arg :: rem -> int_options := arg; parse rem
315    | ("-c"|"-check") :: rem -> check (); parse rem
316    | ("-l"|"-log-file") :: arg :: rem -> log_file := arg; parse rem
317    | ("-L"|"-Locate") :: arg :: rem -> locate arg; parse rem
318    | ("-C"|"-compose") :: rem -> compose (); parse rem   
319    | ("-B"|"-backward") :: arg :: rem ->
320       let m = (int_of_string arg) in mbackward m m (get_terms ()); parse rem
321    | ("-MB"|"-multi-backward") :: arg :: rem ->
322       let m = (int_of_string arg) in mbackward m 0 (get_terms ()); parse rem
323    | ("-P"|"-pattern") :: arg :: rem ->
324       let m = (int_of_string arg) in mpattern m m (get_terms ()); parse rem
325    | ("-MP"|"-multi-pattern") :: rem -> mpattern 7 0 (get_terms ()); parse rem
326    | ("-U"|"-unreferred") :: arg1 :: arg2 :: rem ->
327       unreferred arg1 arg2; parse rem
328    | ("-I"|"-inductive") :: rem -> inductive (get_terms ()); parse rem
329    | _ :: rem -> parse rem
330
331 let _ =
332    let t = U.start_time () in
333 (*   Logger.log_callback :=
334       (Logger.log_to_html 
335        ~print_and_flush:(fun s -> print_string s; flush stdout)) ; 
336 *)   parse (List.tl (Array.to_list Sys.argv)); 
337    prerr_endline ("mqgtop: done in " ^ (U.stop_time t));
338    exit 0