]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/gTopLevel.ml
Interface improvement: a window is opened to show objects returned by the
[helm.git] / helm / gTopLevel / gTopLevel.ml
1 (* Copyright (C) 2000-2002, 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 (******************************************************************************)
27 (*                                                                            *)
28 (*                               PROJECT HELM                                 *)
29 (*                                                                            *)
30 (*                Claudio Sacerdoti Coen <natile@cs.unibo.it>               *)
31 (*                                 06/01/2002                                 *)
32 (*                                                                            *)
33 (*                                                                            *)
34 (******************************************************************************)
35
36
37 (* CSC: quick fix: a function from [uri#xpointer(path)] to [uri#path] *)
38 let wrong_xpointer_format_from_wrong_xpointer_format' uri =
39  try
40   let index_sharp =  String.index uri '#' in
41   let index_rest = index_sharp + 10 in
42    let baseuri = String.sub uri 0 index_sharp in
43    let rest = String.sub uri index_rest (String.length uri - index_rest - 1) in
44     baseuri ^ "#" ^ rest
45  with Not_found -> uri
46 ;;
47
48 (* GLOBAL CONSTANTS *)
49
50 let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
51 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
52
53 let htmlheader =
54  "<html>" ^
55  " <body bgColor=\"white\">"
56 ;;
57
58 let htmlfooter =
59  " </body>" ^
60  "</html>"
61 ;;
62
63 let prooffile = "/public/sacerdot/currentproof";;
64 let prooffiletype = "/public/sacerdot/currentprooftype";;
65
66 (* SACERDOT
67 let prooffile = "/public/sacerdot/currentproof";;
68 let prooffiletype = "/public/sacerdot/currentprooftype";;
69 *)
70
71 (* NATILE
72 let prooffile = "/public/natile/currentproof";;
73 let prooffiletype = "/public/natile/currentprooftype";;
74 *)
75
76 (* TASSI
77 let prooffile = "//miohelm/tmp/currentproof";;
78 let prooffiletype = "/home/tassi/miohelm/tmp/currentprooftype";;
79 *)
80
81 (* GALATA
82 let prooffile = "/home/galata/miohelm/currentproof";;
83 let prooffiletype = "/home/galata/miohelm/currentprooftype";;
84 *)
85
86 (*CSC: the getter should handle the innertypes, not the FS *)
87
88 let innertypesfile = "/public/sacerdot/innertypes";;
89 let constanttypefile = "/public/sacerdot/constanttype";;
90
91 (* SACERDOT
92 let innertypesfile = "/public/sacerdot/innertypes";;
93 let constanttypefile = "/public/sacerdot/constanttype";;
94 *)
95
96 (* NATILE
97 let innertypesfile = "/public/natile/innertypes";;
98 let constanttypefile = "/public/natile/constanttype";;
99 *)
100
101 (* TASSI
102 let innertypesfile = "/home/tassi/miohelm/tmp/innertypes";;
103 let constanttypefile = "/home/tassi/miohelm/tmp/constanttype";;
104 *)
105
106 (* GALATA
107 let innertypesfile = "/home/galata/miohelm/innertypes";;
108 let constanttypefile = "/home/galata/miohelm/constanttype";;
109 *)
110
111 let empty_id_to_uris = ([],function _ -> None);;
112
113
114 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
115
116 let htmlheader_and_content = ref htmlheader;;
117
118 let current_cic_infos = ref None;;
119 let current_goal_infos = ref None;;
120 let current_scratch_infos = ref None;;
121
122 let id_to_uris = ref empty_id_to_uris;;
123
124 let check_term = ref (fun _ _ _ -> assert false);;
125 let mml_of_cic_term_ref = ref (fun _ _ -> assert false);;
126
127 exception RenderingWindowsNotInitialized;;
128
129 let set_rendering_window,rendering_window =
130  let rendering_window_ref = ref None in
131   (function rw -> rendering_window_ref := Some rw),
132   (function () ->
133     match !rendering_window_ref with
134        None -> raise RenderingWindowsNotInitialized
135      | Some rw -> rw
136   )
137 ;;
138
139 exception SettingsWindowsNotInitialized;;
140
141 let set_settings_window,settings_window =
142  let settings_window_ref = ref None in
143   (function rw -> settings_window_ref := Some rw),
144   (function () ->
145     match !settings_window_ref with
146        None -> raise SettingsWindowsNotInitialized
147      | Some rw -> rw
148   )
149 ;;
150
151 exception OutputHtmlNotInitialized;;
152
153 let set_outputhtml,outputhtml =
154  let outputhtml_ref = ref None in
155   (function rw -> outputhtml_ref := Some rw),
156   (function () ->
157     match !outputhtml_ref with
158        None -> raise OutputHtmlNotInitialized
159      | Some outputhtml -> outputhtml
160   )
161 ;;
162
163 exception QedSetSensitiveNotInitialized;;
164 let qed_set_sensitive =
165  ref (function _ -> raise QedSetSensitiveNotInitialized)
166 ;;
167
168 exception SaveSetSensitiveNotInitialized;;
169 let save_set_sensitive =
170  ref (function _ -> raise SaveSetSensitiveNotInitialized)
171 ;;
172
173 (* COMMAND LINE OPTIONS *)
174
175 let usedb = ref true
176
177 let argspec =
178   [
179     "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
180   ]
181 in
182 Arg.parse argspec ignore ""
183
184 (* A WIDGET TO ENTER CIC TERMS *)
185
186 class term_editor ?packing ?width ?height ?isnotempty_callback () =
187  let input = GEdit.text ~editable:true ?width ?height ?packing () in
188  let _ =
189   match isnotempty_callback with
190      None -> ()
191    | Some callback ->
192       ignore(input#connect#changed (function () -> callback (input#length > 0)))
193  in
194 object(self)
195  method coerce = input#coerce
196  method reset =
197   input#delete_text 0 input#length
198  (* CSC: txt is now a string, but should be of type Cic.term *)
199  method set_term txt =
200   self#reset ;
201   ignore ((input#insert_text txt) ~pos:0)
202  (* CSC: this method should disappear *)
203  method get_as_string =
204   input#get_chars 0 input#length
205  method get_term ~context ~metasenv =
206   let lexbuf = Lexing.from_string (input#get_chars 0 input#length) in
207    CicTextualParserContext.main ~context ~metasenv CicTextualLexer.token lexbuf
208 end
209 ;;
210
211 (* MISC FUNCTIONS *)
212
213 exception IllFormedUri of string;;
214
215 let cic_textual_parser_uri_of_string uri' =
216  try
217   (* Constant *)
218   if String.sub uri' (String.length uri' - 4) 4 = ".con" then
219    CicTextualParser0.ConUri (UriManager.uri_of_string uri')
220   else
221    if String.sub uri' (String.length uri' - 4) 4 = ".var" then
222     CicTextualParser0.VarUri (UriManager.uri_of_string uri')
223    else
224     (try
225       (* Inductive Type *)
226       let uri'',typeno = CicTextualLexer.indtyuri_of_uri uri' in
227        CicTextualParser0.IndTyUri (uri'',typeno)
228      with
229       _ ->
230        (* Constructor of an Inductive Type *)
231        let uri'',typeno,consno =
232         CicTextualLexer.indconuri_of_uri uri'
233        in
234         CicTextualParser0.IndConUri (uri'',typeno,consno)
235     )
236  with
237   _ -> raise (IllFormedUri uri')
238 ;;
239
240 let term_of_cic_textual_parser_uri uri =
241  let module C = Cic in
242  let module CTP = CicTextualParser0 in
243   match uri with
244      CTP.ConUri uri -> C.Const (uri,[])
245    | CTP.VarUri uri -> C.Var (uri,[])
246    | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
247    | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
248 ;;
249
250 let string_of_cic_textual_parser_uri uri =
251  let module C = Cic in
252  let module CTP = CicTextualParser0 in
253   let uri' =
254    match uri with
255       CTP.ConUri uri -> UriManager.string_of_uri uri
256     | CTP.VarUri uri -> UriManager.string_of_uri uri
257     | CTP.IndTyUri (uri,tyno) ->
258        UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
259     | CTP.IndConUri (uri,tyno,consno) ->
260        UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
261         string_of_int consno
262   in
263    (* 4 = String.length "cic:" *)
264    String.sub uri' 4 (String.length uri' - 4)
265 ;;
266
267 let output_html outputhtml msg =
268  htmlheader_and_content := !htmlheader_and_content ^ msg ;
269  outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
270  outputhtml#set_topline (-1)
271 ;;
272
273 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
274
275 (* Check window *)
276
277 let check_window outputhtml uris =
278  let window =
279   GWindow.window
280    ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
281  let notebook =
282   GPack.notebook ~scrollable:true ~packing:window#add () in
283  window#show () ;
284  let render_terms =
285   List.map
286    (function uri ->
287      let scrolled_window =
288       GBin.scrolled_window ~border_width:10
289        ~packing:
290          (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
291        ()
292      in
293       lazy 
294        (let mmlwidget =
295          GMathView.math_view
296           ~packing:scrolled_window#add ~width:400 ~height:280 () in
297         let expr =
298          let term =
299           term_of_cic_textual_parser_uri (cic_textual_parser_uri_of_string uri)
300          in
301           (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
302         in
303          try
304           let mml = !mml_of_cic_term_ref 111 expr in
305 prerr_endline ("### " ^ CicPp.ppterm expr) ;
306            mmlwidget#load_tree ~dom:mml
307          with
308           e ->
309            output_html outputhtml
310             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
311        )
312    ) uris
313  in
314   ignore
315    (notebook#connect#switch_page
316      (function i -> Lazy.force (List.nth render_terms i)))
317 ;;
318
319 exception NoChoice;;
320
321 let
322  interactive_user_uri_choice ~selection_mode ?(ok="Ok") ~title ~msg uris
323 =
324  let choices = ref [] in
325  let chosen = ref false in
326  let window =
327   GWindow.dialog ~modal:true ~title ~width:600 () in
328  let lMessage =
329   GMisc.label ~text:msg
330    ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
331  let scrolled_window =
332   GBin.scrolled_window ~border_width:10
333    ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
334  let clist =
335   let expected_height = 18 * List.length uris in
336    let height = if expected_height > 400 then 400 else expected_height in
337     GList.clist ~columns:1 ~packing:scrolled_window#add
338      ~height ~selection_mode () in
339  let _ = List.map (function x -> clist#append [x]) uris in
340  let hbox2 =
341   GPack.hbox ~border_width:0
342    ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
343  let explain_label =
344   GMisc.label ~text:"None of the above. Try this one:"
345    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
346  let manual_input =
347   GEdit.entry ~editable:true
348    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
349  let hbox =
350   GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
351  let okb =
352   GButton.button ~label:ok
353    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
354  let _ = okb#misc#set_sensitive false in
355  let checkb =
356   GButton.button ~label:"Check"
357    ~packing:(hbox#pack ~padding:5) () in
358  let _ = checkb#misc#set_sensitive false in
359  let cancelb =
360   GButton.button ~label:"Abort"
361    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
362  (* actions *)
363  let check_callback () =
364   assert (List.length !choices > 0) ;
365   check_window (outputhtml ()) !choices
366  in
367   ignore (window#connect#destroy GMain.Main.quit) ;
368   ignore (cancelb#connect#clicked window#destroy) ;
369   ignore
370    (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
371   ignore (checkb#connect#clicked check_callback) ;
372   ignore
373    (clist#connect#select_row
374      (fun ~row ~column ~event ->
375        checkb#misc#set_sensitive true ;
376        okb#misc#set_sensitive true ;
377        choices := (List.nth uris row)::!choices)) ;
378   ignore
379    (clist#connect#unselect_row
380      (fun ~row ~column ~event ->
381        choices :=
382         List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
383   ignore
384    (manual_input#connect#changed
385      (fun _ ->
386        if manual_input#text = "" then
387         begin
388          choices := [] ;
389          checkb#misc#set_sensitive false ;
390          okb#misc#set_sensitive false ;
391          clist#misc#set_sensitive true
392         end
393        else
394         begin
395          choices := [manual_input#text] ;
396          clist#unselect_all () ;
397          checkb#misc#set_sensitive true ;
398          okb#misc#set_sensitive true ;
399          clist#misc#set_sensitive false
400         end));
401   window#set_position `CENTER ;
402   window#show () ;
403   GMain.Main.main () ;
404   if !chosen && List.length !choices > 0 then
405    !choices
406   else
407    raise NoChoice
408 ;;
409
410 let interactive_interpretation_choice interpretations =
411  let chosen = ref None in
412  let window =
413   GWindow.window
414    ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
415  let vbox = GPack.vbox ~packing:window#add () in
416  let lMessage =
417   GMisc.label
418    ~text:
419     ("Ambiguous input since there are many well-typed interpretations." ^
420      " Please, choose one of them.")
421    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
422  let notebook =
423   GPack.notebook ~scrollable:true
424    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
425  let _ =
426   List.map
427    (function interpretation ->
428      let clist =
429       let expected_height = 18 * List.length interpretation in
430        let height = if expected_height > 400 then 400 else expected_height in
431         GList.clist ~columns:2 ~packing:notebook#append_page ~height
432          ~titles:["id" ; "URI"] ()
433      in
434       ignore
435        (List.map
436          (function (id,uri) ->
437            let n = clist#append [id;uri] in
438             clist#set_row ~selectable:false n
439          ) interpretation
440        ) ;
441       clist#columns_autosize ()
442    ) interpretations in
443  let hbox =
444   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
445  let okb =
446   GButton.button ~label:"Ok"
447    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
448  let cancelb =
449   GButton.button ~label:"Abort"
450    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
451  (* actions *)
452  ignore (window#connect#destroy GMain.Main.quit) ;
453  ignore (cancelb#connect#clicked window#destroy) ;
454  ignore
455   (okb#connect#clicked
456     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
457  window#set_position `CENTER ;
458  window#show () ;
459  GMain.Main.main () ;
460  match !chosen with
461     None -> raise NoChoice
462   | Some n -> n
463 ;;
464
465
466 (* MISC FUNCTIONS *)
467
468 (* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
469 let get_last_query = 
470  let query = ref "" in
471   MQueryGenerator.set_confirm_query
472    (function q -> query := MQueryUtil.text_of_query q ; true) ;
473   function result -> !query ^ " <h1>Result:</h1> " ^ MQueryUtil.text_of_result result "<br>"
474 ;;
475
476 let domImpl = Gdome.domImplementation ();;
477
478 let parseStyle name =
479  let style =
480   domImpl#createDocumentFromURI
481 (*
482    ~uri:("http://phd.cs.unibo.it:8081/getxslt?uri=" ^ name) ?mode:None
483 *)
484    ~uri:("styles/" ^ name) ()
485  in
486   Gdome_xslt.processStylesheet style
487 ;;
488
489 let d_c = parseStyle "drop_coercions.xsl";;
490 let tc1 = parseStyle "objtheorycontent.xsl";;
491 let hc2 = parseStyle "content_to_html.xsl";;
492 let l   = parseStyle "link.xsl";;
493
494 let c1 = parseStyle "rootcontent.xsl";;
495 let g  = parseStyle "genmmlid.xsl";;
496 let c2 = parseStyle "annotatedpres.xsl";;
497
498
499 let getterURL = Configuration.getter_url;;
500 let processorURL = Configuration.processor_url;;
501
502 let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
503 let mml_args ~explode_all =
504  ("explodeall",(if explode_all then "true()" else "false()"))::
505   ["processorURL", "'" ^ processorURL ^ "'" ;
506    "getterURL", "'" ^ getterURL ^ "'" ;
507    "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
508    "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
509    "UNICODEvsSYMBOL", "'symbol'" ;
510    "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
511    "encoding", "'iso-8859-1'" ;
512    "media-type", "'text/html'" ;
513    "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
514    "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
515    "naturalLanguage", "'yes'" ;
516    "annotations", "'no'" ;
517    "URLs_or_URIs", "'URIs'" ;
518    "topurl", "'http://phd.cs.unibo.it/helm'" ;
519    "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
520 ;;
521
522 let sequent_styles = [d_c ; c1 ; g ; c2 ; l];;
523 let sequent_args =
524  ["processorURL", "'" ^ processorURL ^ "'" ;
525   "getterURL", "'" ^ getterURL ^ "'" ;
526   "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
527   "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
528   "UNICODEvsSYMBOL", "'symbol'" ;
529   "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
530   "encoding", "'iso-8859-1'" ;
531   "media-type", "'text/html'" ;
532   "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
533   "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
534   "naturalLanguage", "'no'" ;
535   "annotations", "'no'" ;
536   "explodeall", "true()" ;
537   "URLs_or_URIs", "'URIs'" ;
538   "topurl", "'http://phd.cs.unibo.it/helm'" ;
539   "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
540 ;;
541
542 let parse_file filename =
543  let inch = open_in filename in
544   let rec read_lines () =
545    try
546     let line = input_line inch in
547      line ^ read_lines ()
548    with
549     End_of_file -> ""
550   in
551    read_lines ()
552 ;;
553
554 let applyStylesheets input styles args =
555  List.fold_left (fun i style -> Gdome_xslt.applyStylesheet i style args)
556   input styles
557 ;;
558
559 let
560  mml_of_cic_object ~explode_all uri annobj ids_to_inner_sorts ids_to_inner_types
561 =
562 (*CSC: ????????????????? *)
563  let xml, bodyxml =
564   Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:true
565    annobj 
566  in
567  let xmlinnertypes =
568   Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
569    ~ask_dtd_to_the_getter:true
570  in
571   let input =
572    match bodyxml with
573       None -> Xml2Gdome.document_of_xml domImpl xml
574     | Some bodyxml' ->
575        Xml.pp xml (Some constanttypefile) ;
576        Xml2Gdome.document_of_xml domImpl bodyxml'
577   in
578 (*CSC: We save the innertypes to disk so that we can retrieve them in the  *)
579 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
580 (*CSC: local.                                                              *)
581    Xml.pp xmlinnertypes (Some innertypesfile) ;
582    let output = applyStylesheets input mml_styles (mml_args ~explode_all) in
583     output
584 ;;
585
586 let
587  save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
588 =
589  let name =
590   let struri = UriManager.string_of_uri uri in
591   let idx = (String.rindex struri '/') + 1 in
592    String.sub struri idx (String.length struri - idx)
593  in
594   let path = pathname ^ "/" ^ name in
595   let xml, bodyxml =
596    Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
597     annobj 
598   in
599   let xmlinnertypes =
600    Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
601     ~ask_dtd_to_the_getter:false
602   in
603    (* innertypes *)
604    let innertypesuri = UriManager.innertypesuri_of_uri uri in
605     Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
606     Getter.register innertypesuri
607      (Configuration.annotations_url ^
608        Str.replace_first (Str.regexp "^cic:") ""
609         (UriManager.string_of_uri innertypesuri) ^ ".xml"
610      ) ;
611     (* constant type / variable / mutual inductive types definition *)
612     Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
613     Getter.register uri
614      (Configuration.annotations_url ^
615        Str.replace_first (Str.regexp "^cic:") ""
616         (UriManager.string_of_uri uri) ^ ".xml"
617      ) ;
618     match bodyxml with
619        None -> ()
620      | Some bodyxml' ->
621         (* constant body *)
622         let bodyuri =
623          match UriManager.bodyuri_of_uri uri with
624             None -> assert false
625           | Some bodyuri -> bodyuri
626         in
627          Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
628          Getter.register bodyuri
629           (Configuration.annotations_url ^
630             Str.replace_first (Str.regexp "^cic:") ""
631              (UriManager.string_of_uri bodyuri) ^ ".xml"
632           )
633 ;;
634
635
636 (* CALLBACKS *)
637
638 exception RefreshSequentException of exn;;
639 exception RefreshProofException of exn;;
640
641 let refresh_proof (output : GMathView.math_view) =
642  try
643   let uri,currentproof =
644    match !ProofEngine.proof with
645       None -> assert false
646     | Some (uri,metasenv,bo,ty) ->
647        !qed_set_sensitive (List.length metasenv = 0) ;
648        (*CSC: Wrong: [] is just plainly wrong *)
649        uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
650   in
651    let
652     (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
653      ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
654    =
655     Cic2acic.acic_object_of_cic_object currentproof
656    in
657     let mml =
658      mml_of_cic_object ~explode_all:true uri acic ids_to_inner_sorts
659       ids_to_inner_types
660     in
661      output#load_tree mml ;
662      current_cic_infos :=
663       Some (ids_to_terms,ids_to_father_ids,ids_to_conjectures,ids_to_hypotheses)
664  with
665   e ->
666  match !ProofEngine.proof with
667     None -> assert false
668   | Some (uri,metasenv,bo,ty) ->
669 prerr_endline ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[]))) ; flush stderr ;
670    raise (RefreshProofException e)
671 ;;
672
673 let refresh_sequent ?(empty_notebook=true) notebook =
674  try
675   match !ProofEngine.goal with
676      None ->
677       if empty_notebook then
678        begin 
679         notebook#remove_all_pages ~skip_switch_page_event:false ;
680         notebook#set_empty_page
681        end
682       else
683        notebook#proofw#unload
684    | Some metano ->
685       let metasenv =
686        match !ProofEngine.proof with
687           None -> assert false
688         | Some (_,metasenv,_,_) -> metasenv
689       in
690       let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
691        let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
692         SequentPp.XmlPp.print_sequent metasenv currentsequent
693        in
694         let regenerate_notebook () = 
695          let skip_switch_page_event =
696           match metasenv with
697              (m,_,_)::_ when m = metano -> false
698            | _ -> true
699          in
700           notebook#remove_all_pages ~skip_switch_page_event ;
701           List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
702         in
703           if empty_notebook then
704            begin
705             regenerate_notebook () ;
706             notebook#set_current_page ~may_skip_switch_page_event:false metano
707            end
708           else
709            begin
710             let sequent_doc = Xml2Gdome.document_of_xml domImpl sequent_gdome in
711             let sequent_mml =
712              applyStylesheets sequent_doc sequent_styles sequent_args
713             in
714              notebook#set_current_page ~may_skip_switch_page_event:true metano;
715              notebook#proofw#load_tree ~dom:sequent_mml
716            end ;
717           current_goal_infos :=
718            Some (ids_to_terms,ids_to_father_ids,ids_to_hypotheses)
719  with
720   e ->
721 let metano =
722   match !ProofEngine.goal with
723      None -> assert false
724    | Some m -> m
725 in
726 let metasenv =
727  match !ProofEngine.proof with
728     None -> assert false
729   | Some (_,metasenv,_,_) -> metasenv
730 in
731 try
732 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
733 prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
734    raise (RefreshSequentException e)
735 with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unkown."); raise (RefreshSequentException e)
736 ;;
737
738 (*
739 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
740  ~name:"/home/galata/miohelm/guruguru1" ~indent:true ()) ;
741 *)
742
743 let mml_of_cic_term metano term =
744  let metasenv =
745   match !ProofEngine.proof with
746      None -> []
747    | Some (_,metasenv,_,_) -> metasenv
748  in
749  let context =
750   match !ProofEngine.goal with
751      None -> []
752    | Some metano ->
753       let (_,canonical_context,_) =
754        List.find (function (m,_,_) -> m=metano) metasenv
755       in
756        canonical_context
757  in
758    let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
759     SequentPp.XmlPp.print_sequent metasenv (metano,context,term)
760    in
761     let sequent_doc =
762      Xml2Gdome.document_of_xml domImpl sequent_gdome
763     in
764      let res =
765       applyStylesheets sequent_doc sequent_styles sequent_args ;
766      in
767       current_scratch_infos :=
768        Some (term,ids_to_terms,ids_to_father_ids,ids_to_hypotheses) ;
769       res
770 ;;
771
772 exception OpenConjecturesStillThere;;
773 exception WrongProof;;
774
775 let pathname_of_annuri uristring =
776  Configuration.annotations_dir ^    
777   Str.replace_first (Str.regexp "^cic:") "" uristring
778 ;;
779
780 let make_dirs dirpath =
781  ignore (Unix.system ("mkdir -p " ^ dirpath))
782 ;;
783
784 let save_obj uri obj =
785  let
786   (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
787    ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
788  =
789   Cic2acic.acic_object_of_cic_object obj
790  in
791   (* let's save the theorem and register it to the getter *) 
792   let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
793    make_dirs pathname ;
794    save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
795     pathname
796 ;;
797
798 let qed () =
799  match !ProofEngine.proof with
800     None -> assert false
801   | Some (uri,[],bo,ty) ->
802      if
803       CicReduction.are_convertible []
804        (CicTypeChecker.type_of_aux' [] [] bo) ty
805      then
806       begin
807        (*CSC: Wrong: [] is just plainly wrong *)
808        let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
809         let
810          (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
811           ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
812         =
813          Cic2acic.acic_object_of_cic_object proof
814         in
815          let mml =
816           mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
817            ids_to_inner_types
818          in
819           ((rendering_window ())#output : GMathView.math_view)#load_tree mml ;
820           !qed_set_sensitive false ;
821           (* let's save the theorem and register it to the getter *) 
822           let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
823           make_dirs pathname ;
824           save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
825            pathname ;
826           current_cic_infos :=
827            Some
828             (ids_to_terms,ids_to_father_ids,ids_to_conjectures,
829              ids_to_hypotheses)
830       end
831      else
832       raise WrongProof
833   | _ -> raise OpenConjecturesStillThere
834 ;;
835
836 let save () =
837  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
838   match !ProofEngine.proof with
839      None -> assert false
840    | Some (uri, metasenv, bo, ty) ->
841       let currentproof =
842        (*CSC: Wrong: [] is just plainly wrong *)
843        Cic.CurrentProof (UriManager.name_of_uri uri,metasenv,bo,ty,[])
844       in
845        let (acurrentproof,_,_,ids_to_inner_sorts,_,_,_) =
846         Cic2acic.acic_object_of_cic_object currentproof
847        in
848         let xml, bodyxml =
849          match
850           Cic2Xml.print_object uri ~ids_to_inner_sorts
851            ~ask_dtd_to_the_getter:true acurrentproof
852          with
853             xml,Some bodyxml -> xml,bodyxml
854           | _,None -> assert false
855         in
856          Xml.pp ~quiet:true xml (Some prooffiletype) ;
857          output_html outputhtml
858           ("<h1 color=\"Green\">Current proof type saved to " ^
859            prooffiletype ^ "</h1>") ;
860          Xml.pp ~quiet:true bodyxml (Some prooffile) ;
861          output_html outputhtml
862           ("<h1 color=\"Green\">Current proof body saved to " ^
863            prooffile ^ "</h1>")
864 ;;
865
866 (* Used to typecheck the loaded proofs *)
867 let typecheck_loaded_proof metasenv bo ty =
868  let module T = CicTypeChecker in
869   ignore (
870    List.fold_left
871     (fun metasenv ((_,context,ty) as conj) ->
872       ignore (T.type_of_aux' metasenv context ty) ;
873       metasenv @ [conj]
874     ) [] metasenv) ;
875   ignore (T.type_of_aux' metasenv [] ty) ;
876   ignore (T.type_of_aux' metasenv [] bo)
877 ;;
878
879 let load () =
880  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
881  let output = ((rendering_window ())#output : GMathView.math_view) in
882  let notebook = (rendering_window ())#notebook in
883   try
884    match 
885     GToolbox.input_string ~title:"Load Unfinished Proof" ~text:"/dummy.con"
886      "Choose an URI:"
887    with
888       None -> raise NoChoice
889     | Some uri0 ->
890        let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
891         match CicParser.obj_of_xml prooffiletype (Some prooffile) with
892            Cic.CurrentProof (_,metasenv,bo,ty,_) ->
893             typecheck_loaded_proof metasenv bo ty ;
894             ProofEngine.proof :=
895              Some (uri, metasenv, bo, ty) ;
896             ProofEngine.goal :=
897              (match metasenv with
898                  [] -> None
899                | (metano,_,_)::_ -> Some metano
900              ) ;
901             refresh_proof output ;
902             refresh_sequent notebook ;
903              output_html outputhtml
904               ("<h1 color=\"Green\">Current proof type loaded from " ^
905                 prooffiletype ^ "</h1>") ;
906              output_html outputhtml
907               ("<h1 color=\"Green\">Current proof body loaded from " ^
908                 prooffile ^ "</h1>") ;
909             !save_set_sensitive true
910          | _ -> assert false
911   with
912      RefreshSequentException e ->
913       output_html outputhtml
914        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
915         "sequent: " ^ Printexc.to_string e ^ "</h1>")
916    | RefreshProofException e ->
917       output_html outputhtml
918        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
919         "proof: " ^ Printexc.to_string e ^ "</h1>")
920    | e ->
921       output_html outputhtml
922        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
923 ;;
924
925 let edit_aliases () =
926  let chosen = ref false in
927  let window =
928   GWindow.window
929    ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
930  let vbox =
931   GPack.vbox ~border_width:0 ~packing:window#add () in
932  let scrolled_window =
933   GBin.scrolled_window ~border_width:10
934    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
935  let input = GEdit.text ~editable:true ~width:400 ~height:100
936    ~packing:scrolled_window#add () in
937  let hbox =
938   GPack.hbox ~border_width:0
939    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
940  let okb =
941   GButton.button ~label:"Ok"
942    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
943  let cancelb =
944   GButton.button ~label:"Cancel"
945    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
946  ignore (window#connect#destroy GMain.Main.quit) ;
947  ignore (cancelb#connect#clicked window#destroy) ;
948  ignore
949   (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
950  let dom,resolve_id = !id_to_uris in
951   ignore
952    (input#insert_text ~pos:0
953     (String.concat "\n"
954       (List.map
955         (function v ->
956           let uri =
957            match resolve_id v with
958               None -> assert false
959             | Some uri -> uri
960           in
961            "alias " ^ v ^ " " ^
962              (string_of_cic_textual_parser_uri uri)
963         ) dom))) ;
964   window#show () ;
965   GMain.Main.main () ;
966   if !chosen then
967    let dom,resolve_id =
968     let inputtext = input#get_chars 0 input#length in
969     let regexpr =
970      let alfa = "[a-zA-Z_-]" in
971      let digit = "[0-9]" in
972      let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
973      let blanks = "\( \|\t\|\n\)+" in
974      let nonblanks = "[^ \t\n]+" in
975      let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
976       Str.regexp
977        ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
978     in
979      let rec aux n =
980       try
981        let n' = Str.search_forward regexpr inputtext n in
982         let id = Str.matched_group 2 inputtext in
983         let uri =
984          cic_textual_parser_uri_of_string
985           ("cic:" ^ (Str.matched_group 5 inputtext))
986         in
987          let dom,resolve_id = aux (n' + 1) in
988           if List.mem id dom then
989            dom,resolve_id
990           else
991            id::dom,
992             (function id' -> if id = id' then Some uri else resolve_id id')
993       with
994        Not_found -> empty_id_to_uris
995      in
996       aux 0
997    in
998     id_to_uris := dom,resolve_id
999 ;;
1000
1001 let proveit () =
1002  let module L = LogicalOperations in
1003  let module G = Gdome in
1004  let notebook = (rendering_window ())#notebook in
1005  let output = (rendering_window ())#output in
1006  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1007   match (rendering_window ())#output#get_selection with
1008     Some node ->
1009      let xpath =
1010       ((node : Gdome.element)#getAttributeNS
1011       (*CSC: OCAML DIVERGE
1012       ((element : G.element)#getAttributeNS
1013       *)
1014         ~namespaceURI:helmns
1015         ~localName:(G.domString "xref"))#to_string
1016      in
1017       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1018       else
1019        begin
1020         try
1021          match !current_cic_infos with
1022             Some (ids_to_terms, ids_to_father_ids, _, _) ->
1023              let id = xpath in
1024               L.to_sequent id ids_to_terms ids_to_father_ids ;
1025               refresh_proof output ;
1026               refresh_sequent notebook
1027           | None -> assert false (* "ERROR: No current term!!!" *)
1028         with
1029            RefreshSequentException e ->
1030             output_html outputhtml
1031              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1032               "sequent: " ^ Printexc.to_string e ^ "</h1>")
1033          | RefreshProofException e ->
1034             output_html outputhtml
1035              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1036               "proof: " ^ Printexc.to_string e ^ "</h1>")
1037          | e ->
1038             output_html outputhtml
1039              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1040        end
1041   | None -> assert false (* "ERROR: No selection!!!" *)
1042 ;;
1043
1044 let focus () =
1045  let module L = LogicalOperations in
1046  let module G = Gdome in
1047  let notebook = (rendering_window ())#notebook in
1048  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1049   match (rendering_window ())#output#get_selection with
1050     Some node ->
1051      let xpath =
1052       ((node : Gdome.element)#getAttributeNS
1053       (*CSC: OCAML DIVERGE
1054       ((element : G.element)#getAttributeNS
1055       *)
1056         ~namespaceURI:helmns
1057         ~localName:(G.domString "xref"))#to_string
1058      in
1059       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1060       else
1061        begin
1062         try
1063          match !current_cic_infos with
1064             Some (ids_to_terms, ids_to_father_ids, _, _) ->
1065              let id = xpath in
1066               L.focus id ids_to_terms ids_to_father_ids ;
1067               refresh_sequent notebook
1068           | None -> assert false (* "ERROR: No current term!!!" *)
1069         with
1070            RefreshSequentException e ->
1071             output_html outputhtml
1072              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1073               "sequent: " ^ Printexc.to_string e ^ "</h1>")
1074          | RefreshProofException e ->
1075             output_html outputhtml
1076              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1077               "proof: " ^ Printexc.to_string e ^ "</h1>")
1078          | e ->
1079             output_html outputhtml
1080              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1081        end
1082   | None -> assert false (* "ERROR: No selection!!!" *)
1083 ;;
1084
1085 exception NoPrevGoal;;
1086 exception NoNextGoal;;
1087
1088 let setgoal metano =
1089  let module L = LogicalOperations in
1090  let module G = Gdome in
1091  let notebook = (rendering_window ())#notebook in
1092  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1093   let metasenv =
1094    match !ProofEngine.proof with
1095       None -> assert false
1096     | Some (_,metasenv,_,_) -> metasenv
1097   in
1098    try
1099     refresh_sequent ~empty_notebook:false notebook
1100    with
1101       RefreshSequentException e ->
1102        output_html outputhtml
1103         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1104          "sequent: " ^ Printexc.to_string e ^ "</h1>")
1105     | e ->
1106        output_html outputhtml
1107         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1108 ;;
1109
1110 let
1111  show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
1112 =
1113  let window =
1114   GWindow.window ~width:800 ~border_width:2 () in
1115  let scrolled_window =
1116   GBin.scrolled_window ~border_width:10 ~packing:window#add () in
1117  let mmlwidget =
1118   GMathView.math_view ~packing:scrolled_window#add ~width:600 ~height:400 () in
1119  let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
1120  let href = Gdome.domString "href" in
1121   let show_in_show_window_obj uri obj =
1122    let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1123     try
1124      let
1125       (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
1126        ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
1127      =
1128       Cic2acic.acic_object_of_cic_object obj
1129      in
1130       let mml =
1131        mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
1132         ids_to_inner_types
1133       in
1134        window#set_title (UriManager.string_of_uri uri) ;
1135        window#misc#hide () ; window#show () ;
1136        mmlwidget#load_tree mml ;
1137     with
1138      e ->
1139       output_html outputhtml
1140        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1141   in
1142   let show_in_show_window_uri uri =
1143    CicTypeChecker.typecheck uri ;
1144    let obj = CicEnvironment.get_cooked_obj uri in
1145     show_in_show_window_obj uri obj
1146   in
1147    let show_in_show_window_callback mmlwidget (n : Gdome.element) =
1148     if n#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
1149      let uri =
1150       (n#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
1151      in 
1152       show_in_show_window_uri (UriManager.uri_of_string uri)
1153     else
1154      if mmlwidget#get_action <> None then
1155       mmlwidget#action_toggle
1156    in
1157     let _ =
1158      mmlwidget#connect#clicked (show_in_show_window_callback mmlwidget)
1159     in
1160      show_in_show_window_obj, show_in_show_window_uri,
1161       show_in_show_window_callback
1162 ;;
1163
1164 exception NoObjectsLocated;;
1165
1166 let user_uri_choice ~title ~msg uris =
1167  let uri =
1168   match uris with
1169      [] -> raise NoObjectsLocated
1170    | [uri] -> uri
1171    | uris ->
1172       match
1173        interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
1174       with
1175          [uri] -> uri
1176        | _ -> assert false
1177  in
1178   String.sub uri 4 (String.length uri - 4)
1179 ;;
1180
1181 let locate_callback id =
1182  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1183  let result = MQueryGenerator.locate id in
1184  let uris =
1185   List.map
1186    (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
1187    result in
1188  let html =
1189   (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>")
1190  in
1191   output_html outputhtml html ;
1192   user_uri_choice ~title:"Ambiguous input."
1193    ~msg:
1194      ("Ambiguous input \"" ^ id ^
1195       "\". Please, choose one interpetation:")
1196    uris
1197 ;;
1198
1199 let locate () =
1200  let inputt = ((rendering_window ())#inputt : term_editor) in
1201  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1202    try
1203     match
1204      GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1205     with
1206        None -> raise NoChoice
1207      | Some input ->
1208         let uri = locate_callback input in
1209          inputt#set_term uri
1210    with
1211     e ->
1212      output_html outputhtml
1213       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1214 ;;
1215
1216 let input_or_locate_uri ~title =
1217  let uri = ref None in
1218  let window =
1219   GWindow.window
1220    ~width:400 ~modal:true ~title ~border_width:2 () in
1221  let vbox = GPack.vbox ~packing:window#add () in
1222  let hbox1 =
1223   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1224  let _ =
1225   GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
1226  let manual_input =
1227   GEdit.entry ~editable:true
1228    ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
1229  let checkb =
1230   GButton.button ~label:"Check"
1231    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1232  let _ = checkb#misc#set_sensitive false in
1233  let hbox2 =
1234   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1235  let _ =
1236   GMisc.label ~text:"You can also enter an indentifier to locate:"
1237    ~packing:(hbox2#pack ~padding:5) () in
1238  let locate_input =
1239   GEdit.entry ~editable:true
1240    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1241  let locateb =
1242   GButton.button ~label:"Locate"
1243    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1244  let _ = locateb#misc#set_sensitive false in
1245  let hbox3 =
1246   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1247  let okb =
1248   GButton.button ~label:"Ok"
1249    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
1250  let _ = okb#misc#set_sensitive false in
1251  let cancelb =
1252   GButton.button ~label:"Cancel"
1253    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
1254  in
1255   ignore (window#connect#destroy GMain.Main.quit) ;
1256   ignore
1257    (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
1258   let check_callback () =
1259    let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1260    let uri = "cic:" ^ manual_input#text in
1261     try
1262       ignore (Getter.resolve (UriManager.uri_of_string uri)) ;
1263       output_html outputhtml "<h1 color=\"Green\">OK</h1>" ;
1264       true
1265     with
1266        Getter.Unresolved ->
1267         output_html outputhtml
1268          ("<h1 color=\"Red\">URI " ^ uri ^
1269           " does not correspond to any object.</h1>") ;
1270         false
1271      | UriManager.IllFormedUri _ ->
1272         output_html outputhtml
1273          ("<h1 color=\"Red\">URI " ^ uri ^ " is not well-formed.</h1>") ;
1274         false
1275      | e ->
1276         output_html outputhtml
1277          ("<h1 color=\"Red\">" ^ Printexc.to_string e ^ "</h1>") ;
1278         false
1279   in
1280   ignore
1281    (okb#connect#clicked
1282      (function () ->
1283        if check_callback () then
1284         begin
1285          uri := Some manual_input#text ;
1286          window#destroy ()
1287         end
1288    )) ;
1289   ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1290   ignore
1291    (manual_input#connect#changed
1292      (fun _ ->
1293        if manual_input#text = "" then
1294         begin
1295          checkb#misc#set_sensitive false ;
1296          okb#misc#set_sensitive false
1297         end
1298        else
1299         begin
1300          checkb#misc#set_sensitive true ;
1301          okb#misc#set_sensitive true
1302         end));
1303   ignore
1304    (locate_input#connect#changed
1305      (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1306   ignore
1307    (locateb#connect#clicked
1308      (function () ->
1309        let id = locate_input#text in
1310         manual_input#set_text (locate_callback id) ;
1311         locate_input#delete_text 0 (String.length id)
1312    )) ;
1313   window#show () ;
1314   GMain.Main.main () ;
1315   match !uri with
1316      None -> raise NoChoice
1317    | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1318 ;;
1319
1320 let locate_one_id id =
1321  let result = MQueryGenerator.locate id in
1322  let uris =
1323   List.map
1324    (function uri,_ ->
1325      wrong_xpointer_format_from_wrong_xpointer_format' uri
1326    ) result in
1327  let html= " <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>" in
1328   output_html (rendering_window ())#outputhtml html ;
1329   let uris' =
1330    match uris with
1331       [] ->
1332        [UriManager.string_of_uri
1333          (input_or_locate_uri ~title:("URI matching \"" ^ id ^ "\" unknown."))]
1334     | [uri] -> [uri]
1335     | _ ->
1336       interactive_user_uri_choice
1337        ~selection_mode:`EXTENDED
1338        ~ok:"Try every selection."
1339        ~title:"Ambiguous input."
1340        ~msg:
1341          ("Ambiguous input \"" ^ id ^
1342           "\". Please, choose one or more interpretations:")
1343        uris
1344   in
1345    List.map cic_textual_parser_uri_of_string uris'
1346 ;;
1347
1348 exception ThereDoesNotExistAnyWellTypedInterpretationOfTheInput;;
1349 exception AmbiguousInput;;
1350
1351 let disambiguate_input context metasenv dom mk_metasenv_and_expr =
1352  let known_ids,resolve_id = !id_to_uris in
1353  let dom' =
1354   let rec filter =
1355    function
1356       [] -> []
1357     | he::tl ->
1358        if List.mem he known_ids then filter tl else he::(filter tl)
1359   in
1360    filter dom
1361  in
1362   (* for each id in dom' we get the list of uris associated to it *)
1363   let list_of_uris = List.map locate_one_id dom' in
1364   (* and now we compute the list of all possible assignments from id to uris *)
1365   let resolve_ids =
1366    let rec aux ids list_of_uris =
1367     match ids,list_of_uris with
1368        [],[] -> [resolve_id]
1369      | id::idtl,uris::uristl ->
1370         let resolves = aux idtl uristl in
1371          List.concat
1372           (List.map
1373             (function uri ->
1374               List.map
1375                (function f ->
1376                  function id' -> if id = id' then Some uri else f id'
1377                ) resolves
1378             ) uris
1379           )
1380      | _,_ -> assert false
1381    in
1382     aux dom' list_of_uris
1383   in
1384    let tests_no = List.length resolve_ids in
1385     if tests_no > 1 then
1386      output_html (outputhtml ())
1387       ("<h1>Disambiguation phase started: " ^
1388         string_of_int (List.length resolve_ids) ^ " cases will be tried.") ;
1389    (* now we select only the ones that generates well-typed terms *)
1390    let resolve_ids' =
1391     let rec filter =
1392      function
1393         [] -> []
1394       | resolve::tl ->
1395          let metasenv',expr = mk_metasenv_and_expr resolve in
1396           try
1397 (*CSC: Bug here: we do not try to typecheck also the metasenv' *)
1398            ignore
1399             (CicTypeChecker.type_of_aux' metasenv context expr) ;
1400            resolve::(filter tl)
1401           with
1402            _ -> filter tl
1403     in
1404      filter resolve_ids
1405    in
1406     let resolve_id' =
1407      match resolve_ids' with
1408         [] -> raise ThereDoesNotExistAnyWellTypedInterpretationOfTheInput
1409       | [resolve_id] -> resolve_id
1410       | _ ->
1411         let choices =
1412          List.map
1413           (function resolve ->
1414             List.map
1415              (function id ->
1416                id,
1417                 match resolve id with
1418                    None -> assert false
1419                  | Some uri ->
1420                     match uri with
1421                        CicTextualParser0.ConUri uri
1422                      | CicTextualParser0.VarUri uri ->
1423                         UriManager.string_of_uri uri
1424                      | CicTextualParser0.IndTyUri (uri,tyno) ->
1425                         UriManager.string_of_uri uri ^ "#xpointer(1/" ^
1426                          string_of_int (tyno+1) ^ ")"
1427                      | CicTextualParser0.IndConUri (uri,tyno,consno) ->
1428                         UriManager.string_of_uri uri ^ "#xpointer(1/" ^
1429                          string_of_int (tyno+1) ^ "/" ^ string_of_int consno ^                           ")"
1430              ) dom
1431           ) resolve_ids'
1432         in
1433          let index = interactive_interpretation_choice choices in
1434           List.nth resolve_ids' index
1435     in
1436      id_to_uris := known_ids @ dom', resolve_id' ;
1437      mk_metasenv_and_expr resolve_id'
1438 ;;
1439
1440 exception UriAlreadyInUse;;
1441 exception NotAUriToAConstant;;
1442
1443 let new_inductive () =
1444  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1445  let output = ((rendering_window ())#output : GMathView.math_view) in
1446  let notebook = (rendering_window ())#notebook in
1447
1448  let chosen = ref false in
1449  let inductive = ref true in
1450  let paramsno = ref 0 in
1451  let get_uri = ref (function _ -> assert false) in
1452  let get_base_uri = ref (function _ -> assert false) in
1453  let get_names = ref (function _ -> assert false) in
1454  let get_types_and_cons = ref (function _ -> assert false) in
1455  let get_name_context_context_and_subst = ref (function _ -> assert false) in 
1456  let window =
1457   GWindow.window
1458    ~width:600 ~modal:true ~position:`CENTER
1459    ~title:"New Block of Mutual (Co)Inductive Definitions"
1460    ~border_width:2 () in
1461  let vbox = GPack.vbox ~packing:window#add () in
1462  let hbox =
1463   GPack.hbox ~border_width:0
1464    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1465  let _ =
1466   GMisc.label ~text:"Enter the URI for the new block:"
1467    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1468  let uri_entry =
1469   GEdit.entry ~editable:true
1470    ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1471  let hbox0 =
1472   GPack.hbox ~border_width:0
1473    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1474  let _ =
1475   GMisc.label
1476    ~text:
1477      "Enter the number of left parameters in every arity and constructor type:"
1478    ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1479  let paramsno_entry =
1480   GEdit.entry ~editable:true ~text:"0"
1481    ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1482  let hbox1 =
1483   GPack.hbox ~border_width:0
1484    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1485  let _ =
1486   GMisc.label ~text:"Are the definitions inductive or coinductive?"
1487    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1488  let inductiveb =
1489   GButton.radio_button ~label:"Inductive"
1490    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1491  let coinductiveb =
1492   GButton.radio_button ~label:"Coinductive"
1493    ~group:inductiveb#group
1494    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1495  let hbox2 =
1496   GPack.hbox ~border_width:0
1497    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1498  let _ =
1499   GMisc.label ~text:"Enter the list of the names of the types:"
1500    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1501  let names_entry =
1502   GEdit.entry ~editable:true
1503    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1504  let hboxn =
1505   GPack.hbox ~border_width:0
1506    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1507  let okb =
1508   GButton.button ~label:"> Next"
1509    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1510  let _ = okb#misc#set_sensitive true in
1511  let cancelb =
1512   GButton.button ~label:"Abort"
1513    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1514  ignore (window#connect#destroy GMain.Main.quit) ;
1515  ignore (cancelb#connect#clicked window#destroy) ;
1516  (* First phase *)
1517  let rec phase1 () =
1518   ignore
1519    (okb#connect#clicked
1520      (function () ->
1521        try
1522         let uristr = "cic:" ^ uri_entry#text in
1523         let namesstr = names_entry#text in
1524         let paramsno' = int_of_string (paramsno_entry#text) in
1525          match Str.split (Str.regexp " +") namesstr with
1526             [] -> assert false
1527           | (he::tl) as names ->
1528              let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1529               begin
1530                try
1531                 ignore (Getter.resolve uri) ;
1532                 raise UriAlreadyInUse
1533                with
1534                 Getter.Unresolved ->
1535                  get_uri := (function () -> uri) ; 
1536                  get_names := (function () -> names) ;
1537                  inductive := inductiveb#active ;
1538                  paramsno := paramsno' ;
1539                  phase2 ()
1540               end
1541        with
1542         e ->
1543          output_html outputhtml
1544           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1545      ))
1546  (* Second phase *)
1547  and phase2 () =
1548   let type_widgets =
1549    List.map
1550     (function name ->
1551       let frame =
1552        GBin.frame ~label:name
1553         ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1554       let vbox = GPack.vbox ~packing:frame#add () in
1555       let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1556       let _ =
1557        GMisc.label ~text:("Enter its type:")
1558         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1559       let scrolled_window =
1560        GBin.scrolled_window ~border_width:5
1561         ~packing:(vbox#pack ~expand:true ~padding:0) () in
1562       let newinputt =
1563        new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
1564         ~isnotempty_callback:
1565          (function b ->
1566            (*non_empty_type := b ;*)
1567            okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1568       in
1569       let hbox =
1570        GPack.hbox ~border_width:0
1571         ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1572       let _ =
1573        GMisc.label ~text:("Enter the list of its constructors:")
1574         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1575       let cons_names_entry =
1576        GEdit.entry ~editable:true
1577         ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1578       (newinputt,cons_names_entry)
1579     ) (!get_names ())
1580   in
1581    vbox#remove hboxn#coerce ;
1582    let hboxn =
1583     GPack.hbox ~border_width:0
1584      ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1585    let okb =
1586     GButton.button ~label:"> Next"
1587      ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1588    let cancelb =
1589     GButton.button ~label:"Abort"
1590      ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1591    ignore (cancelb#connect#clicked window#destroy) ;
1592    ignore
1593     (okb#connect#clicked
1594       (function () ->
1595         try
1596          let names = !get_names () in
1597          let types_and_cons =
1598           List.map2
1599            (fun name (newinputt,cons_names_entry) ->
1600              let dom,mk_metasenv_and_expr =
1601               newinputt#get_term ~context:[] ~metasenv:[] in
1602              let consnamesstr = cons_names_entry#text in
1603              let cons_names = Str.split (Str.regexp " +") consnamesstr in
1604              let metasenv,expr =
1605               disambiguate_input [] [] dom mk_metasenv_and_expr
1606              in
1607               match metasenv with
1608                  [] -> expr,cons_names
1609                | _ -> raise AmbiguousInput
1610            ) names type_widgets
1611          in
1612           (* Let's see if so far the definition is well-typed *)
1613           let uri = !get_uri () in
1614           let params = [] in
1615           let paramsno = 0 in
1616           let tys =
1617            let i = ref 0 in
1618             List.map2
1619              (fun name (ty,cons) ->
1620                let cons' =
1621                 List.map
1622                  (function consname -> consname, Cic.MutInd (uri,!i,[])) cons in
1623                let res = (name, !inductive, ty, cons') in
1624                 incr i ;
1625                 res
1626              ) names types_and_cons
1627           in
1628 (*CSC: test momentaneamente disattivato. Debbo generare dei costruttori validi
1629   anche quando paramsno > 0 ;-((((
1630            CicTypeChecker.typecheck_mutual_inductive_defs uri
1631             (tys,params,paramsno) ;
1632 *)
1633            get_name_context_context_and_subst :=
1634             (function () ->
1635               let i = ref 0 in
1636                List.fold_left2
1637                 (fun (namecontext,context,subst) name (ty,_) ->
1638                   let res =
1639                    (Some (Cic.Name name))::namecontext,
1640                     (Some (Cic.Name name, Cic.Decl ty))::context,
1641                     (Cic.MutInd (uri,!i,[]))::subst
1642                   in
1643                    incr i ; res
1644                 ) ([],[],[]) names types_and_cons) ;
1645            let types_and_cons' =
1646             List.map2
1647              (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1648              names types_and_cons
1649            in
1650             get_types_and_cons := (function () -> types_and_cons') ;
1651             chosen := true ;
1652             window#destroy ()
1653         with
1654          e ->
1655           output_html outputhtml
1656            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1657       ))
1658  (* Third phase *)
1659  and phase3 name cons =
1660   let get_cons_types = ref (function () -> assert false) in
1661   let window2 =
1662    GWindow.window
1663     ~width:600 ~modal:true ~position:`CENTER
1664     ~title:(name ^ " Constructors")
1665     ~border_width:2 () in
1666   let vbox = GPack.vbox ~packing:window2#add () in
1667   let cons_type_widgets =
1668    List.map
1669     (function consname ->
1670       let hbox =
1671        GPack.hbox ~border_width:0
1672         ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1673       let _ =
1674        GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1675         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1676       let scrolled_window =
1677        GBin.scrolled_window ~border_width:5
1678         ~packing:(vbox#pack ~expand:true ~padding:0) () in
1679       let newinputt =
1680        new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
1681         ~isnotempty_callback:
1682          (function b ->
1683            (* (*non_empty_type := b ;*)
1684            okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1685       in
1686        newinputt
1687     ) cons in
1688   let hboxn =
1689    GPack.hbox ~border_width:0
1690     ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1691   let okb =
1692    GButton.button ~label:"> Next"
1693     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1694   let _ = okb#misc#set_sensitive true in
1695   let cancelb =
1696    GButton.button ~label:"Abort"
1697     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1698   ignore (window2#connect#destroy GMain.Main.quit) ;
1699   ignore (cancelb#connect#clicked window2#destroy) ;
1700   ignore
1701    (okb#connect#clicked
1702      (function () ->
1703        try
1704         chosen := true ;
1705         let namecontext,context,subst= !get_name_context_context_and_subst () in
1706         let cons_types =
1707          List.map2
1708           (fun name inputt ->
1709             let dom,mk_metasenv_and_expr =
1710              inputt#get_term ~context:namecontext ~metasenv:[]
1711             in
1712              let metasenv,expr =
1713               disambiguate_input context [] dom mk_metasenv_and_expr
1714              in
1715               match metasenv with
1716                  [] ->
1717                   let undebrujined_expr =
1718                    List.fold_left
1719                     (fun expr t -> CicSubstitution.subst t expr) expr subst
1720                   in
1721                    name, undebrujined_expr
1722                | _ -> raise AmbiguousInput
1723           ) cons cons_type_widgets
1724         in
1725          get_cons_types := (function () -> cons_types) ;
1726          window2#destroy ()
1727        with
1728         e ->
1729          output_html outputhtml
1730           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1731      )) ;
1732   window2#show () ;
1733   GMain.Main.main () ;
1734   let okb_pressed = !chosen in
1735    chosen := false ;
1736    if (not okb_pressed) then
1737     begin
1738      window#destroy () ;
1739      assert false (* The control never reaches this point *)
1740     end
1741    else
1742     (!get_cons_types ())
1743  in
1744   phase1 () ;
1745   (* No more phases left or Abort pressed *) 
1746   window#show () ;
1747   GMain.Main.main () ;
1748   window#destroy () ;
1749   if !chosen then
1750    try
1751     let uri = !get_uri () in
1752 (*CSC: Da finire *)
1753     let params = [] in
1754     let tys = !get_types_and_cons () in
1755      let obj = Cic.InductiveDefinition tys params !paramsno in
1756       begin
1757        try
1758         prerr_endline (CicPp.ppobj obj) ;
1759         CicTypeChecker.typecheck_mutual_inductive_defs uri
1760          (tys,params,!paramsno) ;
1761         with
1762          e ->
1763           prerr_endline "Offending mutual (co)inductive type declaration:" ;
1764           prerr_endline (CicPp.ppobj obj) ;
1765       end ;
1766       (* We already know that obj is well-typed. We need to add it to the  *)
1767       (* environment in order to compute the inner-types without having to *)
1768       (* debrujin it or having to modify lots of other functions to avoid  *)
1769       (* asking the environment for the MUTINDs we are defining now.       *)
1770       CicEnvironment.put_inductive_definition uri obj ;
1771       save_obj uri obj ;
1772       show_in_show_window_obj uri obj
1773    with
1774     e ->
1775      output_html outputhtml
1776       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1777 ;;
1778
1779 let new_proof () =
1780  let inputt = ((rendering_window ())#inputt : term_editor) in
1781  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1782  let output = ((rendering_window ())#output : GMathView.math_view) in
1783  let notebook = (rendering_window ())#notebook in
1784
1785  let chosen = ref false in
1786  let get_parsed = ref (function _ -> assert false) in
1787  let get_uri = ref (function _ -> assert false) in
1788  let non_empty_type = ref false in
1789  let window =
1790   GWindow.window
1791    ~width:600 ~modal:true ~title:"New Proof or Definition"
1792    ~border_width:2 () in
1793  let vbox = GPack.vbox ~packing:window#add () in
1794  let hbox =
1795   GPack.hbox ~border_width:0
1796    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1797  let _ =
1798   GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1799    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1800  let uri_entry =
1801   GEdit.entry ~editable:true
1802    ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1803  let hbox1 =
1804   GPack.hbox ~border_width:0
1805    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1806  let _ =
1807   GMisc.label ~text:"Enter the theorem or definition type:"
1808    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1809  let scrolled_window =
1810   GBin.scrolled_window ~border_width:5
1811    ~packing:(vbox#pack ~expand:true ~padding:0) () in
1812  (* the content of the scrolled_window is moved below (see comment) *)
1813  let hbox =
1814   GPack.hbox ~border_width:0
1815    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1816  let okb =
1817   GButton.button ~label:"Ok"
1818    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1819  let _ = okb#misc#set_sensitive false in
1820  let cancelb =
1821   GButton.button ~label:"Cancel"
1822    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1823  (* moved here to have visibility of the ok button *)
1824  let newinputt =
1825   new term_editor ~width:400 ~height:100 ~packing:scrolled_window#add ()
1826    ~isnotempty_callback:
1827     (function b ->
1828       non_empty_type := b ;
1829       okb#misc#set_sensitive (b && uri_entry#text <> ""))
1830  in
1831  let _ =
1832   newinputt#set_term inputt#get_as_string ;
1833   inputt#reset in
1834  let _ =
1835   uri_entry#connect#changed
1836    (function () ->
1837      okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1838  in
1839  ignore (window#connect#destroy GMain.Main.quit) ;
1840  ignore (cancelb#connect#clicked window#destroy) ;
1841  ignore
1842   (okb#connect#clicked
1843     (function () ->
1844       chosen := true ;
1845       try
1846        let parsed = newinputt#get_term [] [] in
1847        let uristr = "cic:" ^ uri_entry#text in
1848        let uri = UriManager.uri_of_string uristr in
1849         if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1850          raise NotAUriToAConstant
1851         else
1852          begin
1853           try
1854            ignore (Getter.resolve uri) ;
1855            raise UriAlreadyInUse
1856           with
1857            Getter.Unresolved ->
1858             get_parsed := (function () -> parsed) ;
1859             get_uri := (function () -> uri) ; 
1860             window#destroy ()
1861          end
1862       with
1863        e ->
1864         output_html outputhtml
1865          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1866   )) ;
1867  window#show () ;
1868  GMain.Main.main () ;
1869  if !chosen then
1870   try
1871    let dom,mk_metasenv_and_expr = !get_parsed () in
1872     let metasenv,expr =
1873      disambiguate_input [] [] dom mk_metasenv_and_expr
1874     in
1875      let _  = CicTypeChecker.type_of_aux' metasenv [] expr in
1876       ProofEngine.proof :=
1877        Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
1878       ProofEngine.goal := Some 1 ;
1879       refresh_sequent notebook ;
1880       refresh_proof output ;
1881       !save_set_sensitive true ;
1882       inputt#reset
1883   with
1884      RefreshSequentException e ->
1885       output_html outputhtml
1886        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1887         "sequent: " ^ Printexc.to_string e ^ "</h1>")
1888    | RefreshProofException e ->
1889       output_html outputhtml
1890        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1891         "proof: " ^ Printexc.to_string e ^ "</h1>")
1892    | e ->
1893       output_html outputhtml
1894        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1895 ;;
1896
1897 let check_term_in_scratch scratch_window metasenv context expr = 
1898  try
1899   let ty  = CicTypeChecker.type_of_aux' metasenv context expr in
1900    let mml = mml_of_cic_term 111 (Cic.Cast (expr,ty)) in
1901 prerr_endline ("### " ^ CicPp.ppterm expr ^ " ==> " ^ CicPp.ppterm ty) ;
1902     scratch_window#show () ;
1903     scratch_window#mmlwidget#load_tree ~dom:mml
1904  with
1905   e ->
1906    print_endline ("? " ^ CicPp.ppterm expr) ;
1907    raise e
1908 ;;
1909
1910 let check scratch_window () =
1911  let inputt = ((rendering_window ())#inputt : term_editor) in
1912  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1913   let metasenv =
1914    match !ProofEngine.proof with
1915       None -> []
1916     | Some (_,metasenv,_,_) -> metasenv
1917   in
1918   let context,names_context =
1919    let context =
1920     match !ProofEngine.goal with
1921        None -> []
1922      | Some metano ->
1923         let (_,canonical_context,_) =
1924          List.find (function (m,_,_) -> m=metano) metasenv
1925         in
1926          canonical_context
1927    in
1928     context,
1929     List.map
1930      (function
1931          Some (n,_) -> Some n
1932        | None -> None
1933      ) context
1934   in
1935    try
1936     let dom,mk_metasenv_and_expr = inputt#get_term names_context metasenv in
1937      let (metasenv',expr) =
1938       disambiguate_input context metasenv dom mk_metasenv_and_expr
1939      in
1940       check_term_in_scratch scratch_window metasenv' context expr
1941    with
1942     e ->
1943      output_html outputhtml
1944       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1945 ;;
1946
1947
1948 (***********************)
1949 (*       TACTICS       *)
1950 (***********************)
1951
1952 let call_tactic tactic () =
1953  let notebook = (rendering_window ())#notebook in
1954  let output = ((rendering_window ())#output : GMathView.math_view) in
1955  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1956  let savedproof = !ProofEngine.proof in
1957  let savedgoal  = !ProofEngine.goal in
1958   begin
1959    try
1960     tactic () ;
1961     refresh_sequent notebook ;
1962     refresh_proof output
1963    with
1964       RefreshSequentException e ->
1965        output_html outputhtml
1966         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1967          "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
1968        ProofEngine.proof := savedproof ;
1969        ProofEngine.goal := savedgoal ;
1970        refresh_sequent notebook
1971     | RefreshProofException e ->
1972        output_html outputhtml
1973         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1974          "proof: " ^ Printexc.to_string e ^ "</h1>") ;
1975        ProofEngine.proof := savedproof ;
1976        ProofEngine.goal := savedgoal ;
1977        refresh_sequent notebook ;
1978        refresh_proof output
1979     | e ->
1980        output_html outputhtml
1981         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1982        ProofEngine.proof := savedproof ;
1983        ProofEngine.goal := savedgoal ;
1984   end
1985 ;;
1986
1987 let call_tactic_with_input tactic () =
1988  let notebook = (rendering_window ())#notebook in
1989  let output = ((rendering_window ())#output : GMathView.math_view) in
1990  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1991  let inputt = ((rendering_window ())#inputt : term_editor) in
1992  let savedproof = !ProofEngine.proof in
1993  let savedgoal  = !ProofEngine.goal in
1994   let uri,metasenv,bo,ty =
1995    match !ProofEngine.proof with
1996       None -> assert false
1997     | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
1998   in
1999    let canonical_context =
2000     match !ProofEngine.goal with
2001        None -> assert false
2002      | Some metano ->
2003         let (_,canonical_context,_) =
2004          List.find (function (m,_,_) -> m=metano) metasenv
2005         in
2006          canonical_context
2007    in
2008    let context =
2009     List.map
2010      (function
2011          Some (n,_) -> Some n
2012        | None -> None
2013      ) canonical_context
2014    in
2015     try
2016      let dom,mk_metasenv_and_expr = inputt#get_term context metasenv in
2017       let (metasenv',expr) =
2018        disambiguate_input canonical_context metasenv dom mk_metasenv_and_expr
2019       in
2020        ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
2021        tactic expr ;
2022        refresh_sequent notebook ;
2023        refresh_proof output ;
2024        inputt#reset
2025     with
2026        RefreshSequentException e ->
2027         output_html outputhtml
2028          ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2029           "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2030         ProofEngine.proof := savedproof ;
2031         ProofEngine.goal := savedgoal ;
2032         refresh_sequent notebook
2033      | RefreshProofException e ->
2034         output_html outputhtml
2035          ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2036           "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2037         ProofEngine.proof := savedproof ;
2038         ProofEngine.goal := savedgoal ;
2039         refresh_sequent notebook ;
2040         refresh_proof output
2041      | e ->
2042         output_html outputhtml
2043          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2044         ProofEngine.proof := savedproof ;
2045         ProofEngine.goal := savedgoal ;
2046 ;;
2047
2048 let call_tactic_with_goal_input tactic () =
2049  let module L = LogicalOperations in
2050  let module G = Gdome in
2051   let notebook = (rendering_window ())#notebook in
2052   let output = ((rendering_window ())#output : GMathView.math_view) in
2053   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2054   let savedproof = !ProofEngine.proof in
2055   let savedgoal  = !ProofEngine.goal in
2056    match notebook#proofw#get_selection with
2057      Some node ->
2058       let xpath =
2059        ((node : Gdome.element)#getAttributeNS
2060          ~namespaceURI:helmns
2061          ~localName:(G.domString "xref"))#to_string
2062       in
2063        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2064        else
2065         begin
2066          try
2067           match !current_goal_infos with
2068              Some (ids_to_terms, ids_to_father_ids,_) ->
2069               let id = xpath in
2070                tactic (Hashtbl.find ids_to_terms id) ;
2071                refresh_sequent notebook ;
2072                refresh_proof output
2073            | None -> assert false (* "ERROR: No current term!!!" *)
2074          with
2075             RefreshSequentException e ->
2076              output_html outputhtml
2077               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2078                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2079              ProofEngine.proof := savedproof ;
2080              ProofEngine.goal := savedgoal ;
2081              refresh_sequent notebook
2082           | RefreshProofException e ->
2083              output_html outputhtml
2084               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2085                "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2086              ProofEngine.proof := savedproof ;
2087              ProofEngine.goal := savedgoal ;
2088              refresh_sequent notebook ;
2089              refresh_proof output
2090           | e ->
2091              output_html outputhtml
2092               ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2093              ProofEngine.proof := savedproof ;
2094              ProofEngine.goal := savedgoal ;
2095         end
2096    | None ->
2097       output_html outputhtml
2098        ("<h1 color=\"red\">No term selected</h1>")
2099 ;;
2100
2101 let call_tactic_with_input_and_goal_input tactic () =
2102  let module L = LogicalOperations in
2103  let module G = Gdome in
2104   let notebook = (rendering_window ())#notebook in
2105   let output = ((rendering_window ())#output : GMathView.math_view) in
2106   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2107   let inputt = ((rendering_window ())#inputt : term_editor) in
2108   let savedproof = !ProofEngine.proof in
2109   let savedgoal  = !ProofEngine.goal in
2110    match notebook#proofw#get_selection with
2111      Some node ->
2112       let xpath =
2113        ((node : Gdome.element)#getAttributeNS
2114          ~namespaceURI:helmns
2115          ~localName:(G.domString "xref"))#to_string
2116       in
2117        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2118        else
2119         begin
2120          try
2121           match !current_goal_infos with
2122              Some (ids_to_terms, ids_to_father_ids,_) ->
2123               let id = xpath in
2124                let uri,metasenv,bo,ty =
2125                 match !ProofEngine.proof with
2126                    None -> assert false
2127                  | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
2128                in
2129                 let canonical_context =
2130                  match !ProofEngine.goal with
2131                     None -> assert false
2132                   | Some metano ->
2133                      let (_,canonical_context,_) =
2134                       List.find (function (m,_,_) -> m=metano) metasenv
2135                      in
2136                       canonical_context in
2137                 let context =
2138                  List.map
2139                   (function
2140                       Some (n,_) -> Some n
2141                     | None -> None
2142                   ) canonical_context
2143                 in
2144                  let dom,mk_metasenv_and_expr = inputt#get_term context metasenv
2145                  in
2146                   let (metasenv',expr) =
2147                    disambiguate_input canonical_context metasenv dom
2148                     mk_metasenv_and_expr
2149                   in
2150                    ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
2151                    tactic ~goal_input:(Hashtbl.find ids_to_terms id)
2152                     ~input:expr ;
2153                    refresh_sequent notebook ;
2154                    refresh_proof output ;
2155                    inputt#reset
2156            | None -> assert false (* "ERROR: No current term!!!" *)
2157          with
2158             RefreshSequentException e ->
2159              output_html outputhtml
2160               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2161                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2162              ProofEngine.proof := savedproof ;
2163              ProofEngine.goal := savedgoal ;
2164              refresh_sequent notebook
2165           | RefreshProofException e ->
2166              output_html outputhtml
2167               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2168                "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2169              ProofEngine.proof := savedproof ;
2170              ProofEngine.goal := savedgoal ;
2171              refresh_sequent notebook ;
2172              refresh_proof output
2173           | e ->
2174              output_html outputhtml
2175               ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2176              ProofEngine.proof := savedproof ;
2177              ProofEngine.goal := savedgoal ;
2178         end
2179    | None ->
2180       output_html outputhtml
2181        ("<h1 color=\"red\">No term selected</h1>")
2182 ;;
2183
2184 let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
2185  let module L = LogicalOperations in
2186  let module G = Gdome in
2187   let mmlwidget = (scratch_window#mmlwidget : GMathView.math_view) in
2188   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2189   let savedproof = !ProofEngine.proof in
2190   let savedgoal  = !ProofEngine.goal in
2191    match mmlwidget#get_selection with
2192      Some node ->
2193       let xpath =
2194        ((node : Gdome.element)#getAttributeNS
2195          ~namespaceURI:helmns
2196          ~localName:(G.domString "xref"))#to_string
2197       in
2198        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2199        else
2200         begin
2201          try
2202           match !current_scratch_infos with
2203              (* term is the whole goal in the scratch_area *)
2204              Some (term,ids_to_terms, ids_to_father_ids,_) ->
2205               let id = xpath in
2206                let expr = tactic term (Hashtbl.find ids_to_terms id) in
2207                 let mml = mml_of_cic_term 111 expr in
2208                  scratch_window#show () ;
2209                  scratch_window#mmlwidget#load_tree ~dom:mml
2210            | None -> assert false (* "ERROR: No current term!!!" *)
2211          with
2212           e ->
2213            output_html outputhtml
2214             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2215         end
2216    | None ->
2217       output_html outputhtml
2218        ("<h1 color=\"red\">No term selected</h1>")
2219 ;;
2220
2221 let call_tactic_with_hypothesis_input tactic () =
2222  let module L = LogicalOperations in
2223  let module G = Gdome in
2224   let notebook = (rendering_window ())#notebook in
2225   let output = ((rendering_window ())#output : GMathView.math_view) in
2226   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2227   let savedproof = !ProofEngine.proof in
2228   let savedgoal  = !ProofEngine.goal in
2229    match notebook#proofw#get_selection with
2230      Some node ->
2231       let xpath =
2232        ((node : Gdome.element)#getAttributeNS
2233          ~namespaceURI:helmns
2234          ~localName:(G.domString "xref"))#to_string
2235       in
2236        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2237        else
2238         begin
2239          try
2240           match !current_goal_infos with
2241              Some (_,_,ids_to_hypotheses) ->
2242               let id = xpath in
2243                tactic (Hashtbl.find ids_to_hypotheses id) ;
2244                refresh_sequent notebook ;
2245                refresh_proof output
2246            | None -> assert false (* "ERROR: No current term!!!" *)
2247          with
2248             RefreshSequentException e ->
2249              output_html outputhtml
2250               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2251                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2252              ProofEngine.proof := savedproof ;
2253              ProofEngine.goal := savedgoal ;
2254              refresh_sequent notebook
2255           | RefreshProofException e ->
2256              output_html outputhtml
2257               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2258                "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2259              ProofEngine.proof := savedproof ;
2260              ProofEngine.goal := savedgoal ;
2261              refresh_sequent notebook ;
2262              refresh_proof output
2263           | e ->
2264              output_html outputhtml
2265               ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2266              ProofEngine.proof := savedproof ;
2267              ProofEngine.goal := savedgoal ;
2268         end
2269    | None ->
2270       output_html outputhtml
2271        ("<h1 color=\"red\">No term selected</h1>")
2272 ;;
2273
2274
2275 let intros = call_tactic ProofEngine.intros;;
2276 let exact = call_tactic_with_input ProofEngine.exact;;
2277 let apply = call_tactic_with_input ProofEngine.apply;;
2278 let elimsimplintros = call_tactic_with_input ProofEngine.elim_simpl_intros;;
2279 let elimtype = call_tactic_with_input ProofEngine.elim_type;;
2280 let whd = call_tactic_with_goal_input ProofEngine.whd;;
2281 let reduce = call_tactic_with_goal_input ProofEngine.reduce;;
2282 let simpl = call_tactic_with_goal_input ProofEngine.simpl;;
2283 let fold_whd = call_tactic_with_input ProofEngine.fold_whd;;
2284 let fold_reduce = call_tactic_with_input ProofEngine.fold_reduce;;
2285 let fold_simpl = call_tactic_with_input ProofEngine.fold_simpl;;
2286 let cut = call_tactic_with_input ProofEngine.cut;;
2287 let change = call_tactic_with_input_and_goal_input ProofEngine.change;;
2288 let letin = call_tactic_with_input ProofEngine.letin;;
2289 let ring = call_tactic ProofEngine.ring;;
2290 let clearbody = call_tactic_with_hypothesis_input ProofEngine.clearbody;;
2291 let clear = call_tactic_with_hypothesis_input ProofEngine.clear;;
2292 let fourier = call_tactic ProofEngine.fourier;;
2293 let rewritesimpl = call_tactic_with_input ProofEngine.rewrite_simpl;;
2294 let reflexivity = call_tactic ProofEngine.reflexivity;;
2295 let symmetry = call_tactic ProofEngine.symmetry;;
2296 let transitivity = call_tactic_with_input ProofEngine.transitivity;;
2297 let exists = call_tactic ProofEngine.exists;;
2298 let split = call_tactic ProofEngine.split;;
2299 let left = call_tactic ProofEngine.left;;
2300 let right = call_tactic ProofEngine.right;;
2301 let assumption = call_tactic ProofEngine.assumption;;
2302 let generalize = call_tactic_with_goal_input ProofEngine.generalize;;
2303 let absurd = call_tactic_with_input ProofEngine.absurd;;
2304 let contradiction = call_tactic ProofEngine.contradiction;;
2305 (* Galla: come dare alla tattica la lista di termini da decomporre?
2306 let decompose = call_tactic_with_input_and_goal_input ProofEngine.decompose;;
2307 *)
2308
2309 let whd_in_scratch scratch_window =
2310  call_tactic_with_goal_input_in_scratch ProofEngine.whd_in_scratch
2311   scratch_window
2312 ;;
2313 let reduce_in_scratch scratch_window =
2314  call_tactic_with_goal_input_in_scratch ProofEngine.reduce_in_scratch
2315   scratch_window
2316 ;;
2317 let simpl_in_scratch scratch_window =
2318  call_tactic_with_goal_input_in_scratch ProofEngine.simpl_in_scratch
2319   scratch_window
2320 ;;
2321
2322
2323
2324 (**********************)
2325 (*   END OF TACTICS   *)
2326 (**********************)
2327
2328
2329 let show () =
2330  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2331   try
2332    show_in_show_window_uri (input_or_locate_uri ~title:"Show")
2333   with
2334    e ->
2335     output_html outputhtml
2336      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2337 ;;
2338
2339 exception NotADefinition;;
2340
2341 let open_ () =
2342  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2343  let output = ((rendering_window ())#output : GMathView.math_view) in
2344  let notebook = (rendering_window ())#notebook in
2345    try
2346     let uri = input_or_locate_uri ~title:"Open" in
2347      CicTypeChecker.typecheck uri ;
2348      let metasenv,bo,ty =
2349       match CicEnvironment.get_cooked_obj uri with
2350          Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
2351        | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
2352        | Cic.Constant _
2353        | Cic.Variable _
2354        | Cic.InductiveDefinition _ -> raise NotADefinition
2355      in
2356       ProofEngine.proof :=
2357        Some (uri, metasenv, bo, ty) ;
2358       ProofEngine.goal := None ;
2359       refresh_sequent notebook ;
2360       refresh_proof output
2361    with
2362       RefreshSequentException e ->
2363        output_html outputhtml
2364         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2365          "sequent: " ^ Printexc.to_string e ^ "</h1>")
2366     | RefreshProofException e ->
2367        output_html outputhtml
2368         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2369          "proof: " ^ Printexc.to_string e ^ "</h1>")
2370     | e ->
2371        output_html outputhtml
2372         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2373 ;;
2374
2375 let show_query_results results =
2376  let window =
2377   GWindow.window
2378    ~modal:false ~title:"Query refinement." ~border_width:2 () in
2379  let vbox = GPack.vbox ~packing:window#add () in
2380  let hbox =
2381   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2382  let lMessage =
2383   GMisc.label
2384    ~text:"Click on a URI to show that object"
2385    ~packing:hbox#add () in
2386  let scrolled_window =
2387   GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
2388    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2389  let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
2390   ignore
2391    (List.map
2392      (function (uri,_) ->
2393        let n =
2394         clist#append [uri]
2395        in
2396         clist#set_row ~selectable:false n
2397      ) results
2398    ) ;
2399   clist#columns_autosize () ;
2400   ignore
2401    (clist#connect#select_row
2402      (fun ~row ~column ~event ->
2403        let (uri,_) = List.nth results row in
2404         show_in_show_window_uri (UriManager.uri_of_string uri))
2405    ) ;
2406   window#show ()
2407 ;;
2408
2409 let completeSearchPattern () =
2410  let inputt = ((rendering_window ())#inputt : term_editor) in
2411  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2412   try
2413    let dom,mk_metasenv_and_expr = inputt#get_term ~context:[] ~metasenv:[] in
2414    let metasenv,expr = disambiguate_input [] [] dom mk_metasenv_and_expr in
2415    let must,can = MQueryLevels2.get_constraints expr in
2416    let results = MQueryGenerator.searchPattern must can in 
2417     show_query_results results
2418   with
2419    e ->
2420     output_html outputhtml
2421      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2422 ;;
2423
2424 let choose_must list_of_must can =
2425  let chosen = ref None in
2426  let user_constraints = ref [] in
2427  let window =
2428   GWindow.window
2429    ~modal:true ~title:"Query refinement." ~border_width:2 () in
2430  let vbox = GPack.vbox ~packing:window#add () in
2431  let hbox =
2432   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2433  let lMessage =
2434   GMisc.label
2435    ~text:
2436     ("You can now specify the genericity of the query. " ^
2437      "The more generic the slower.")
2438    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2439  let hbox =
2440   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2441  let lMessage =
2442   GMisc.label
2443    ~text:
2444     "Suggestion: start with faster queries before moving to more generic ones."
2445    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2446  let notebook =
2447   GPack.notebook ~scrollable:true
2448    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2449  let _ =
2450   let page = ref 0 in
2451   let last = List.length list_of_must in
2452   List.map
2453    (function must ->
2454      incr page ;
2455      let label =
2456       GMisc.label ~text:
2457        (if !page = 1 then "More generic" else
2458          if !page = last then "More precise" else "          ") () in
2459      let expected_height = 25 * (List.length must + 2) in
2460      let height = if expected_height > 400 then 400 else expected_height in
2461      let scrolled_window =
2462       GBin.scrolled_window ~border_width:10 ~height ~width:600
2463        ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2464      let clist =
2465         GList.clist ~columns:2 ~packing:scrolled_window#add
2466          ~titles:["URI" ; "Position"] ()
2467      in
2468       ignore
2469        (List.map
2470          (function (uri,position) ->
2471            let n =
2472             clist#append 
2473              [uri; if position then "MainConclusion" else "Conclusion"]
2474            in
2475             clist#set_row ~selectable:false n
2476          ) must
2477        ) ;
2478       clist#columns_autosize ()
2479    ) list_of_must in
2480  let _ =
2481   let label = GMisc.label ~text:"User provided" () in
2482   let vbox =
2483    GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2484   let hbox =
2485    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2486   let lMessage =
2487    GMisc.label
2488    ~text:"Select the constraints that must be satisfied and press OK."
2489    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2490   let expected_height = 25 * (List.length can + 2) in
2491   let height = if expected_height > 400 then 400 else expected_height in
2492   let scrolled_window =
2493    GBin.scrolled_window ~border_width:10 ~height ~width:600
2494     ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2495   let clist =
2496    GList.clist ~columns:2 ~packing:scrolled_window#add
2497     ~selection_mode:`EXTENDED
2498     ~titles:["URI" ; "Position"] ()
2499   in
2500    ignore
2501     (List.map
2502       (function (uri,position) ->
2503         let n =
2504          clist#append 
2505           [uri; if position then "MainConclusion" else "Conclusion"]
2506         in
2507          clist#set_row ~selectable:true n
2508       ) can
2509     ) ;
2510    clist#columns_autosize () ;
2511    ignore
2512     (clist#connect#select_row
2513       (fun ~row ~column ~event ->
2514         user_constraints := (List.nth can row)::!user_constraints)) ;
2515    ignore
2516     (clist#connect#unselect_row
2517       (fun ~row ~column ~event ->
2518         user_constraints :=
2519          List.filter
2520           (function uri -> uri != (List.nth can row)) !user_constraints)) ;
2521  in
2522  let hbox =
2523   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2524  let okb =
2525   GButton.button ~label:"Ok"
2526    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2527  let cancelb =
2528   GButton.button ~label:"Abort"
2529    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2530  (* actions *)
2531  ignore (window#connect#destroy GMain.Main.quit) ;
2532  ignore (cancelb#connect#clicked window#destroy) ;
2533  ignore
2534   (okb#connect#clicked
2535     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2536  window#set_position `CENTER ;
2537  window#show () ;
2538  GMain.Main.main () ;
2539  match !chosen with
2540     None -> raise NoChoice
2541   | Some n ->
2542      if n = List.length list_of_must then
2543       (* user provided constraints *)
2544       !user_constraints
2545      else
2546       List.nth list_of_must n
2547 ;;
2548
2549 let searchPattern () =
2550  let inputt = ((rendering_window ())#inputt : term_editor) in
2551  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2552   try
2553     let metasenv =
2554      match !ProofEngine.proof with
2555         None -> assert false
2556       | Some (_,metasenv,_,_) -> metasenv
2557     in
2558      match !ProofEngine.goal with
2559         None -> ()
2560       | Some metano ->
2561          let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
2562           let list_of_must,can = MQueryLevels.out_restr metasenv ey ty in
2563           let must = choose_must list_of_must can in
2564           let torigth_restriction (u,b) =
2565              let p = if b then "http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion" 
2566                      else "http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion" in
2567                (u,p,None)
2568           in
2569           let rigth_must = List.map torigth_restriction must in
2570           let rigth_can = Some (List.map torigth_restriction can) in
2571           let result = MQueryGenerator.searchPattern (rigth_must,[],[]) (rigth_can,None,None) in 
2572           let uris =
2573            List.map
2574             (function uri,_ ->
2575               wrong_xpointer_format_from_wrong_xpointer_format' uri
2576             ) result in
2577           let html =
2578            " <h1>Backward Query: </h1>" ^
2579            " <pre>" ^ get_last_query result ^ "</pre>"
2580           in
2581            output_html outputhtml html ;
2582            let uris',exc =
2583             let rec filter_out =
2584              function
2585                 [] -> [],""
2586               | uri::tl ->
2587                  let tl',exc = filter_out tl in
2588                   try
2589                    if
2590                     ProofEngine.can_apply
2591                      (term_of_cic_textual_parser_uri
2592                       (cic_textual_parser_uri_of_string uri))
2593                    then
2594                     uri::tl',exc
2595                    else
2596                     tl',exc
2597                   with
2598                    e ->
2599                     let exc' =
2600                      "<h1 color=\"red\"> ^ Exception raised trying to apply " ^
2601                       uri ^ ": " ^ Printexc.to_string e ^ " </h1>" ^ exc
2602                     in
2603                      tl',exc'
2604             in
2605              filter_out uris
2606            in
2607             let html' =
2608              " <h1>Objects that can actually be applied: </h1> " ^
2609              String.concat "<br>" uris' ^ exc ^
2610              " <h1>Number of false matches: " ^
2611               string_of_int (List.length uris - List.length uris') ^ "</h1>" ^
2612              " <h1>Number of good matches: " ^
2613               string_of_int (List.length uris') ^ "</h1>"
2614             in
2615              output_html outputhtml html' ;
2616              let uri' =
2617               user_uri_choice ~title:"Ambiguous input."
2618               ~msg:
2619                 "Many lemmas can be successfully applied. Please, choose one:"
2620                uris'
2621              in
2622               inputt#set_term uri' ;
2623               apply ()
2624   with
2625    e -> 
2626     output_html outputhtml 
2627      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2628 ;;
2629       
2630 let choose_selection
2631      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
2632 =
2633  let module G = Gdome in
2634   let rec aux element =
2635    if element#hasAttributeNS
2636        ~namespaceURI:helmns
2637        ~localName:(G.domString "xref")
2638    then
2639      mmlwidget#set_selection (Some element)
2640    else
2641       match element#get_parentNode with
2642          None -> assert false
2643        (*CSC: OCAML DIVERGES!
2644        | Some p -> aux (new G.element_of_node p)
2645        *)
2646        | Some p -> aux (new Gdome.element_of_node p)
2647   in
2648    match element with
2649      Some x -> aux x
2650    | None   -> mmlwidget#set_selection None
2651 ;;
2652
2653 (* STUFF TO BUILD THE GTK INTERFACE *)
2654
2655 (* Stuff for the widget settings *)
2656
2657 let export_to_postscript (output : GMathView.math_view) =
2658  let lastdir = ref (Unix.getcwd ()) in
2659   function () ->
2660    match
2661     GToolbox.select_file ~title:"Export to PostScript"
2662      ~dir:lastdir ~filename:"screenshot.ps" ()
2663    with
2664       None -> ()
2665     | Some filename ->
2666        output#export_to_postscript ~filename:filename ();
2667 ;;
2668
2669 let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
2670  button_set_kerning button_set_transparency export_to_postscript_menu_item
2671  button_t1 ()
2672 =
2673  let is_set = button_t1#active in
2674   output#set_font_manager_type
2675    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
2676   if is_set then
2677    begin
2678     button_set_anti_aliasing#misc#set_sensitive true ;
2679     button_set_kerning#misc#set_sensitive true ;
2680     button_set_transparency#misc#set_sensitive true ;
2681     export_to_postscript_menu_item#misc#set_sensitive true ;
2682    end
2683   else
2684    begin
2685     button_set_anti_aliasing#misc#set_sensitive false ;
2686     button_set_kerning#misc#set_sensitive false ;
2687     button_set_transparency#misc#set_sensitive false ;
2688     export_to_postscript_menu_item#misc#set_sensitive false ;
2689    end
2690 ;;
2691
2692 let set_anti_aliasing output button_set_anti_aliasing () =
2693  output#set_anti_aliasing button_set_anti_aliasing#active
2694 ;;
2695
2696 let set_kerning output button_set_kerning () =
2697  output#set_kerning button_set_kerning#active
2698 ;;
2699
2700 let set_transparency output button_set_transparency () =
2701  output#set_transparency button_set_transparency#active
2702 ;;
2703
2704 let changefont output font_size_spinb () =
2705  output#set_font_size font_size_spinb#value_as_int
2706 ;;
2707
2708 let set_log_verbosity output log_verbosity_spinb () =
2709  output#set_log_verbosity log_verbosity_spinb#value_as_int
2710 ;;
2711
2712 class settings_window (output : GMathView.math_view) sw
2713  export_to_postscript_menu_item selection_changed_callback
2714 =
2715  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2716  let vbox =
2717   GPack.vbox ~packing:settings_window#add () in
2718  let table =
2719   GPack.table
2720    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2721    ~border_width:5 ~packing:vbox#add () in
2722  let button_t1 =
2723   GButton.toggle_button ~label:"activate t1 fonts"
2724    ~packing:(table#attach ~left:0 ~top:0) () in
2725  let button_set_anti_aliasing =
2726   GButton.toggle_button ~label:"set_anti_aliasing"
2727    ~packing:(table#attach ~left:0 ~top:1) () in
2728  let button_set_kerning =
2729   GButton.toggle_button ~label:"set_kerning"
2730    ~packing:(table#attach ~left:1 ~top:1) () in
2731  let button_set_transparency =
2732   GButton.toggle_button ~label:"set_transparency"
2733    ~packing:(table#attach ~left:2 ~top:1) () in
2734  let table =
2735   GPack.table
2736    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2737    ~border_width:5 ~packing:vbox#add () in
2738  let font_size_label =
2739   GMisc.label ~text:"font size:"
2740    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2741  let font_size_spinb =
2742   let sadj =
2743    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2744   in
2745    GEdit.spin_button 
2746     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2747  let log_verbosity_label =
2748   GMisc.label ~text:"log verbosity:"
2749    ~packing:(table#attach ~left:0 ~top:1) () in
2750  let log_verbosity_spinb =
2751   let sadj =
2752    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2753   in
2754    GEdit.spin_button 
2755     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2756  let hbox =
2757   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2758  let closeb =
2759   GButton.button ~label:"Close"
2760    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2761 object(self)
2762  method show = settings_window#show
2763  initializer
2764   button_set_anti_aliasing#misc#set_sensitive false ;
2765   button_set_kerning#misc#set_sensitive false ;
2766   button_set_transparency#misc#set_sensitive false ;
2767   (* Signals connection *)
2768   ignore(button_t1#connect#clicked
2769    (activate_t1 output button_set_anti_aliasing button_set_kerning
2770     button_set_transparency export_to_postscript_menu_item button_t1)) ;
2771   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2772   ignore(button_set_anti_aliasing#connect#toggled
2773    (set_anti_aliasing output button_set_anti_aliasing));
2774   ignore(button_set_kerning#connect#toggled
2775    (set_kerning output button_set_kerning)) ;
2776   ignore(button_set_transparency#connect#toggled
2777    (set_transparency output button_set_transparency)) ;
2778   ignore(log_verbosity_spinb#connect#changed
2779    (set_log_verbosity output log_verbosity_spinb)) ;
2780   ignore(closeb#connect#clicked settings_window#misc#hide)
2781 end;;
2782
2783 (* Scratch window *)
2784
2785 class scratch_window =
2786  let window =
2787   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
2788  let vbox =
2789   GPack.vbox ~packing:window#add () in
2790  let hbox =
2791   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2792  let whdb =
2793   GButton.button ~label:"Whd"
2794    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2795  let reduceb =
2796   GButton.button ~label:"Reduce"
2797    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2798  let simplb =
2799   GButton.button ~label:"Simpl"
2800    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2801  let scrolled_window =
2802   GBin.scrolled_window ~border_width:10
2803    ~packing:(vbox#pack ~expand:true ~padding:5) () in
2804  let mmlwidget =
2805   GMathView.math_view
2806    ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
2807 object(self)
2808  method mmlwidget = mmlwidget
2809  method show () = window#misc#hide () ; window#show ()
2810  initializer
2811   ignore(mmlwidget#connect#selection_changed (choose_selection mmlwidget)) ;
2812   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
2813   ignore(whdb#connect#clicked (whd_in_scratch self)) ;
2814   ignore(reduceb#connect#clicked (reduce_in_scratch self)) ;
2815   ignore(simplb#connect#clicked (simpl_in_scratch self))
2816 end;;
2817
2818 class page () =
2819  let vbox1 = GPack.vbox () in
2820 object(self)
2821  val mutable proofw_ref = None
2822  val mutable compute_ref = None
2823  method proofw =
2824   Lazy.force self#compute ;
2825   match proofw_ref with
2826      None -> assert false
2827    | Some proofw -> proofw
2828  method content = vbox1
2829  method compute =
2830   match compute_ref with
2831      None -> assert false
2832    | Some compute -> compute
2833  initializer
2834   compute_ref <-
2835    Some (lazy (
2836    let scrolled_window1 =
2837     GBin.scrolled_window ~border_width:10
2838      ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2839    let proofw =
2840     GMathView.math_view ~width:400 ~height:275
2841      ~packing:(scrolled_window1#add) () in
2842    let _ = proofw_ref <- Some proofw in
2843    let hbox3 =
2844     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2845    let exactb =
2846     GButton.button ~label:"Exact"
2847      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2848    let introsb =
2849     GButton.button ~label:"Intros"
2850      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2851    let applyb =
2852     GButton.button ~label:"Apply"
2853      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2854    let elimsimplintrosb =
2855     GButton.button ~label:"ElimSimplIntros"
2856      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2857    let elimtypeb =
2858     GButton.button ~label:"ElimType"
2859      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2860    let whdb =
2861     GButton.button ~label:"Whd"
2862      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2863    let reduceb =
2864     GButton.button ~label:"Reduce"
2865      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2866    let simplb =
2867     GButton.button ~label:"Simpl"
2868      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2869    let foldwhdb =
2870     GButton.button ~label:"Fold_whd"
2871      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2872    let hbox4 =
2873     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2874    let foldreduceb =
2875     GButton.button ~label:"Fold_reduce"
2876      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2877    let foldsimplb =
2878     GButton.button ~label:"Fold_simpl"
2879      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2880    let cutb =
2881     GButton.button ~label:"Cut"
2882      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2883    let changeb =
2884     GButton.button ~label:"Change"
2885      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2886    let letinb =
2887     GButton.button ~label:"Let ... In"
2888      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2889    let ringb =
2890     GButton.button ~label:"Ring"
2891      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2892    let clearbodyb =
2893     GButton.button ~label:"ClearBody"
2894      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2895    let clearb =
2896     GButton.button ~label:"Clear"
2897      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2898    let hbox5 =
2899     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2900    let fourierb =
2901     GButton.button ~label:"Fourier"
2902      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2903    let rewritesimplb =
2904     GButton.button ~label:"RewriteSimpl ->"
2905      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2906    let reflexivityb =
2907     GButton.button ~label:"Reflexivity"
2908      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2909    let symmetryb =
2910     GButton.button ~label:"Symmetry"
2911      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2912    let transitivityb =
2913     GButton.button ~label:"Transitivity"
2914      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2915    let existsb =
2916     GButton.button ~label:"Exists"
2917      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2918    let splitb =
2919     GButton.button ~label:"Split"
2920      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2921    let hbox6 =
2922     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2923    let leftb =
2924     GButton.button ~label:"Left"
2925      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2926    let rightb =
2927     GButton.button ~label:"Right"
2928      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2929    let assumptionb =
2930     GButton.button ~label:"Assumption"
2931      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2932    let generalizeb =
2933     GButton.button ~label:"Generalize"
2934      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2935    let absurdb =
2936     GButton.button ~label:"Absurd"
2937      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2938    let contradictionb =
2939     GButton.button ~label:"Contradiction"
2940      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2941    let searchpatternb =
2942     GButton.button ~label:"SearchPattern_Apply"
2943      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2944
2945    ignore(exactb#connect#clicked exact) ;
2946    ignore(applyb#connect#clicked apply) ;
2947    ignore(elimsimplintrosb#connect#clicked elimsimplintros) ;
2948    ignore(elimtypeb#connect#clicked elimtype) ;
2949    ignore(whdb#connect#clicked whd) ;
2950    ignore(reduceb#connect#clicked reduce) ;
2951    ignore(simplb#connect#clicked simpl) ;
2952    ignore(foldwhdb#connect#clicked fold_whd) ;
2953    ignore(foldreduceb#connect#clicked fold_reduce) ;
2954    ignore(foldsimplb#connect#clicked fold_simpl) ;
2955    ignore(cutb#connect#clicked cut) ;
2956    ignore(changeb#connect#clicked change) ;
2957    ignore(letinb#connect#clicked letin) ;
2958    ignore(ringb#connect#clicked ring) ;
2959    ignore(clearbodyb#connect#clicked clearbody) ;
2960    ignore(clearb#connect#clicked clear) ;
2961    ignore(fourierb#connect#clicked fourier) ;
2962    ignore(rewritesimplb#connect#clicked rewritesimpl) ;
2963    ignore(reflexivityb#connect#clicked reflexivity) ;
2964    ignore(symmetryb#connect#clicked symmetry) ;
2965    ignore(transitivityb#connect#clicked transitivity) ;
2966    ignore(existsb#connect#clicked exists) ;
2967    ignore(splitb#connect#clicked split) ;
2968    ignore(leftb#connect#clicked left) ;
2969    ignore(rightb#connect#clicked right) ;
2970    ignore(assumptionb#connect#clicked assumption) ;
2971    ignore(generalizeb#connect#clicked generalize) ;
2972    ignore(absurdb#connect#clicked absurd) ;
2973    ignore(contradictionb#connect#clicked contradiction) ;
2974    ignore(introsb#connect#clicked intros) ;
2975    ignore(searchpatternb#connect#clicked searchPattern) ;
2976    ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
2977   ))
2978 end
2979 ;;
2980
2981 class empty_page =
2982  let vbox1 = GPack.vbox () in
2983  let scrolled_window1 =
2984   GBin.scrolled_window ~border_width:10
2985    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2986  let proofw =
2987   GMathView.math_view ~width:400 ~height:275
2988    ~packing:(scrolled_window1#add) () in
2989 object(self)
2990  method proofw = (assert false : GMathView.math_view)
2991  method content = vbox1
2992  method compute = (assert false : unit)
2993 end
2994 ;;
2995
2996 let empty_page = new empty_page;;
2997
2998 class notebook =
2999 object(self)
3000  val notebook = GPack.notebook ()
3001  val pages = ref []
3002  val mutable skip_switch_page_event = false 
3003  val mutable empty = true
3004  method notebook = notebook
3005  method add_page n =
3006   let new_page = new page () in
3007    empty <- false ;
3008    pages := !pages @ [n,lazy (setgoal n),new_page] ;
3009    notebook#append_page
3010     ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
3011     new_page#content#coerce
3012  method remove_all_pages ~skip_switch_page_event:skip =
3013   if empty then
3014    notebook#remove_page 0 (* let's remove the empty page *)
3015   else
3016    List.iter (function _ -> notebook#remove_page 0) !pages ;
3017   pages := [] ;
3018   skip_switch_page_event <- skip
3019  method set_current_page ~may_skip_switch_page_event n =
3020   let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
3021    let new_page = notebook#page_num page#content#coerce in
3022     if may_skip_switch_page_event && new_page <> notebook#current_page then
3023      skip_switch_page_event <- true ;
3024     notebook#goto_page new_page
3025  method set_empty_page =
3026   empty <- true ;
3027   pages := [] ;
3028   notebook#append_page
3029    ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
3030    empty_page#content#coerce
3031  method proofw =
3032   let (_,_,page) = List.nth !pages notebook#current_page in
3033    page#proofw
3034  initializer
3035   ignore
3036    (notebook#connect#switch_page
3037     (function i ->
3038       let skip = skip_switch_page_event in
3039        skip_switch_page_event <- false ;
3040        if not skip then
3041         try
3042          let (metano,setgoal,page) = List.nth !pages i in
3043           ProofEngine.goal := Some metano ;
3044           Lazy.force (page#compute) ;
3045           Lazy.force setgoal
3046         with _ -> ()
3047     ))
3048 end
3049 ;;
3050
3051 (* Main window *)
3052
3053 class rendering_window output (notebook : notebook) =
3054  let scratch_window = new scratch_window in
3055  let window =
3056   GWindow.window ~title:"MathML viewer" ~border_width:0
3057    ~allow_shrink:false () in
3058  let vbox_for_menu = GPack.vbox ~packing:window#add () in
3059  (* menus *)
3060  let handle_box = GBin.handle_box ~border_width:2
3061   ~packing:(vbox_for_menu#pack ~padding:0) () in
3062  let menubar = GMenu.menu_bar ~packing:handle_box#add () in
3063  let factory0 = new GMenu.factory menubar in
3064  let accel_group = factory0#accel_group in
3065  (* file menu *)
3066  let file_menu = factory0#add_submenu "File" in
3067  let factory1 = new GMenu.factory file_menu ~accel_group in
3068  let export_to_postscript_menu_item =
3069   begin
3070    let _ =
3071     factory1#add_item "New Block of (Co)Inductive Definitions..."
3072      ~key:GdkKeysyms._B ~callback:new_inductive
3073    in
3074    let _ =
3075     factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
3076      ~callback:new_proof
3077    in
3078    let reopen_menu_item =
3079     factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
3080      ~callback:open_
3081    in
3082    let qed_menu_item =
3083     factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
3084    ignore (factory1#add_separator ()) ;
3085    ignore
3086     (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
3087       ~callback:load) ;
3088    let save_menu_item =
3089     factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S ~callback:save
3090    in
3091    ignore
3092     (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
3093    ignore (!save_set_sensitive false);
3094    ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
3095    ignore (!qed_set_sensitive false);
3096    ignore (factory1#add_separator ()) ;
3097    let export_to_postscript_menu_item =
3098     factory1#add_item "Export to PostScript..."
3099      ~callback:(export_to_postscript output) in
3100    ignore (factory1#add_separator ()) ;
3101    ignore
3102     (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) ;
3103    export_to_postscript_menu_item
3104   end in
3105  (* edit menu *)
3106  let edit_menu = factory0#add_submenu "Edit Current Proof" in
3107  let factory2 = new GMenu.factory edit_menu ~accel_group in
3108  let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
3109  let proveit_menu_item =
3110   factory2#add_item "Prove It" ~key:GdkKeysyms._I
3111    ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
3112  in
3113  let focus_menu_item =
3114   factory2#add_item "Focus" ~key:GdkKeysyms._F
3115    ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
3116  in
3117  let _ =
3118   focus_and_proveit_set_sensitive :=
3119    function b ->
3120     proveit_menu_item#misc#set_sensitive b ;
3121     focus_menu_item#misc#set_sensitive b
3122  in
3123  let _ = !focus_and_proveit_set_sensitive false in
3124  (* edit term menu *)
3125  let edit_term_menu = factory0#add_submenu "Edit Term" in
3126  let factory5 = new GMenu.factory edit_term_menu ~accel_group in
3127  let check_menu_item =
3128   factory5#add_item "Check Term" ~key:GdkKeysyms._C
3129    ~callback:(check scratch_window) in
3130  let _ = check_menu_item#misc#set_sensitive false in
3131  (* search menu *)
3132  let settings_menu = factory0#add_submenu "Search" in
3133  let factory4 = new GMenu.factory settings_menu ~accel_group in
3134  let _ =
3135   factory4#add_item "Locate..." ~key:GdkKeysyms._T
3136    ~callback:locate in
3137  let searchPattern_menu_item =
3138   factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
3139    ~callback:completeSearchPattern in
3140  let _ = searchPattern_menu_item#misc#set_sensitive false in
3141  let show_menu_item =
3142   factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
3143  in
3144  (* settings menu *)
3145  let settings_menu = factory0#add_submenu "Settings" in
3146  let factory3 = new GMenu.factory settings_menu ~accel_group in
3147  let _ =
3148   factory3#add_item "Edit Aliases" ~key:GdkKeysyms._A
3149    ~callback:edit_aliases in
3150  let _ = factory3#add_separator () in
3151  let _ =
3152   factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
3153    ~callback:(function _ -> (settings_window ())#show ()) in
3154  (* accel group *)
3155  let _ = window#add_accel_group accel_group in
3156  (* end of menus *)
3157  let hbox0 =
3158   GPack.hbox
3159    ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
3160  let vbox =
3161   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
3162  let scrolled_window0 =
3163   GBin.scrolled_window ~border_width:10
3164    ~packing:(vbox#pack ~expand:true ~padding:5) () in
3165  let _ = scrolled_window0#add output#coerce in
3166  let frame =
3167   GBin.frame ~label:"Insert Term"
3168    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
3169  let scrolled_window1 =
3170   GBin.scrolled_window ~border_width:5
3171    ~packing:frame#add () in
3172  let inputt =
3173   new term_editor ~width:400 ~height:100 ~packing:scrolled_window1#add ()
3174    ~isnotempty_callback:
3175     (function b ->
3176       check_menu_item#misc#set_sensitive b ;
3177       searchPattern_menu_item#misc#set_sensitive b) in
3178  let vboxl =
3179   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
3180  let _ =
3181   vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
3182  let frame =
3183   GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
3184  in
3185  let outputhtml =
3186   GHtml.xmhtml
3187    ~source:"<html><body bgColor=\"white\"></body></html>"
3188    ~width:400 ~height: 100
3189    ~border_width:20
3190    ~packing:frame#add
3191    ~show:true () in
3192 object
3193  method outputhtml = outputhtml
3194  method inputt = inputt
3195  method output = (output : GMathView.math_view)
3196  method notebook = notebook
3197  method show = window#show
3198  initializer
3199   notebook#set_empty_page ;
3200   export_to_postscript_menu_item#misc#set_sensitive false ;
3201   check_term := (check_term_in_scratch scratch_window) ;
3202
3203   (* signal handlers here *)
3204   ignore(output#connect#selection_changed
3205    (function elem ->
3206      choose_selection output elem ;
3207      !focus_and_proveit_set_sensitive true
3208    )) ;
3209   ignore (output#connect#clicked (show_in_show_window_callback output)) ;
3210   let settings_window = new settings_window output scrolled_window0
3211    export_to_postscript_menu_item (choose_selection output) in
3212   set_settings_window settings_window ;
3213   set_outputhtml outputhtml ;
3214   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
3215   Logger.log_callback :=
3216    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
3217 end;;
3218
3219 (* MAIN *)
3220
3221 let initialize_everything () =
3222  let module U = Unix in
3223   let output = GMathView.math_view ~width:350 ~height:280 () in
3224   let notebook = new notebook in
3225    let rendering_window' = new rendering_window output notebook in
3226     set_rendering_window rendering_window' ;
3227     mml_of_cic_term_ref := mml_of_cic_term ;
3228     rendering_window'#show () ;
3229     GMain.Main.main ()
3230 ;;
3231
3232 let _ =
3233  if !usedb then
3234   begin
3235    Mqint.set_database Mqint.postgres_db ;
3236    (* Mqint.init "dbname=helm_mowgli" ; *)
3237    (* Mqint.init "host=mowgli.cs.unibo.it dbname=helm_mowgli user=helm" ; *)
3238    Mqint.init "host=mowgli.cs.unibo.it dbname=helm_mowgli_new_schema user=helm";
3239   end ;
3240  ignore (GtkMain.Main.init ()) ;
3241  initialize_everything () ;
3242  if !usedb then Mqint.close ();
3243 ;;