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