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