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