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