1 (* Copyright (C) 2000-2004, HELM Team.
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.
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.
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.
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,
22 * For details, see the HELM World-Wide-Web page,
23 * http://helm.cs.unibo.it/
26 (******************************************************************************)
30 (* Claudio Sacerdoti Coen <sacerdot@cs.unibo.it> *)
34 (******************************************************************************)
36 let debug_level = ref 1
37 let debug_print ?(level = 1) s = if !debug_level >= level then prerr_endline s
38 let error s = prerr_endline ("E: " ^ s)
39 let warning s = prerr_endline ("W: " ^ s)
45 module MQI = MQueryInterpreter
47 module MQGT = MQGTypes
49 module MQG = MQueryGenerator
52 (* first of all let's initialize the Helm_registry *)
54 let configuration_file = "gTopLevel.conf.xml" in
55 if not (Sys.file_exists configuration_file) then begin
56 eprintf "E: Can't find configuration file '%s'\n" configuration_file;
59 Helm_registry.load_from configuration_file
62 (* GLOBAL CONSTANTS *)
64 let mqi_debug_fun s = debug_print ~level:2 s
65 let mqi_handle = MQIC.init_if_connected ~log:mqi_debug_fun ()
67 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
69 let restore_environment_on_boot = true ;;
70 let notify_hbugs_on_goal_change = false ;;
72 let auto_disambiguation = ref true ;;
74 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
76 let check_term = ref (fun _ _ _ -> assert false);;
78 exception RenderingWindowsNotInitialized;;
80 let set_rendering_window,rendering_window =
81 let rendering_window_ref = ref None in
82 (function rw -> rendering_window_ref := Some rw),
84 match !rendering_window_ref with
85 None -> raise RenderingWindowsNotInitialized
90 exception SettingsWindowsNotInitialized;;
92 let set_settings_window,settings_window =
93 let settings_window_ref = ref None in
94 (function rw -> settings_window_ref := Some rw),
96 match !settings_window_ref with
97 None -> raise SettingsWindowsNotInitialized
102 exception QedSetSensitiveNotInitialized;;
103 let qed_set_sensitive =
104 ref (function _ -> raise QedSetSensitiveNotInitialized)
107 exception SaveSetSensitiveNotInitialized;;
108 let save_set_sensitive =
109 ref (function _ -> raise SaveSetSensitiveNotInitialized)
112 (* COMMAND LINE OPTIONS *)
118 "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
121 Arg.parse argspec ignore ""
125 let term_of_cic_textual_parser_uri uri =
126 let module C = Cic in
127 let module CTP = CicTextualParser0 in
129 CTP.ConUri uri -> C.Const (uri,[])
130 | CTP.VarUri uri -> C.Var (uri,[])
131 | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
132 | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
135 let string_of_cic_textual_parser_uri uri =
136 let module C = Cic in
137 let module CTP = CicTextualParser0 in
140 CTP.ConUri uri -> UriManager.string_of_uri uri
141 | CTP.VarUri uri -> UriManager.string_of_uri uri
142 | CTP.IndTyUri (uri,tyno) ->
143 UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
144 | CTP.IndConUri (uri,tyno,consno) ->
145 UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
148 (* 4 = String.length "cic:" *)
149 String.sub uri' 4 (String.length uri' - 4)
152 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
156 let check_window uris =
159 ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
161 GPack.notebook ~scrollable:true ~packing:window#add () in
166 let scrolled_window =
167 GBin.scrolled_window ~border_width:10
169 (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
174 TermViewer.sequent_viewer
175 ~mml_of_cic_sequent:ChosenTransformer.mml_of_cic_sequent
176 ~packing:scrolled_window#add ~width:400 ~height:280 () in
179 term_of_cic_textual_parser_uri
180 (MQueryMisc.cic_textual_parser_uri_of_string uri)
182 (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
185 mmlwidget#load_sequent [] (111,[],expr)
188 HelmLogger.log (`Error (`T (Printexc.to_string e)))
193 (notebook#connect#switch_page
195 Lazy.force (List.nth render_terms i)))
200 let interactive_user_uri_choice
201 ~(selection_mode:[ `SINGLE | `MULTIPLE ])
202 ?(ok="Ok") ?(enable_button_for_non_vars=false) ~title ~msg uris
204 let only_constant_choices =
207 (fun uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
210 if selection_mode <> `SINGLE && !auto_disambiguation then
211 Lazy.force only_constant_choices
213 let choices = ref [] in
214 let chosen = ref false in
215 let use_only_constants = ref false in
217 GWindow.dialog ~modal:true ~title ~width:600 () in
219 GMisc.label ~text:msg
220 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
221 let scrolled_window =
222 GBin.scrolled_window ~border_width:10
223 ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
225 let expected_height = 18 * List.length uris in
226 let height = if expected_height > 400 then 400 else expected_height in
227 GList.clist ~columns:1 ~packing:scrolled_window#add
228 ~height ~selection_mode:(selection_mode :> Gtk.Tags.selection_mode) () in
229 let _ = List.map (function x -> clist#append [x]) uris in
231 GPack.hbox ~border_width:0
232 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
234 GMisc.label ~text:"None of the above. Try this one:"
235 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
237 GEdit.entry ~editable:true
238 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
240 GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
242 GButton.button ~label:ok
243 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
244 let _ = okb#misc#set_sensitive false in
249 if enable_button_for_non_vars then
250 hbox#pack ~expand:false ~fill:false ~padding:5 w)
251 ~label:"Try constants only" () in
256 if enable_button_for_non_vars then
257 hbox#pack ~expand:false ~fill:false ~padding:5 w)
260 GButton.button ~label:"Check"
261 ~packing:(hbox#pack ~padding:5) () in
262 let _ = checkb#misc#set_sensitive false in
264 GButton.button ~label:"Abort"
265 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
267 let check_callback () =
268 assert (List.length !choices > 0) ;
269 check_window !choices
271 ignore (window#connect#destroy GMain.Main.quit) ;
272 ignore (cancelb#connect#clicked window#destroy) ;
274 (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
276 (nonvarsb#connect#clicked
278 use_only_constants := true ;
282 ignore (autob#connect#clicked (fun () ->
283 auto_disambiguation := true;
284 (rendering_window ())#set_auto_disambiguation true;
285 use_only_constants := true ;
288 ignore (checkb#connect#clicked check_callback) ;
290 (clist#connect#select_row
291 (fun ~row ~column ~event ->
292 checkb#misc#set_sensitive true ;
293 okb#misc#set_sensitive true ;
294 choices := (List.nth uris row)::!choices)) ;
296 (clist#connect#unselect_row
297 (fun ~row ~column ~event ->
299 List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
301 (manual_input#connect#changed
303 if manual_input#text = "" then
306 checkb#misc#set_sensitive false ;
307 okb#misc#set_sensitive false ;
308 clist#misc#set_sensitive true
312 choices := [manual_input#text] ;
313 clist#unselect_all () ;
314 checkb#misc#set_sensitive true ;
315 okb#misc#set_sensitive true ;
316 clist#misc#set_sensitive false
318 window#set_position `CENTER ;
322 if !use_only_constants then
323 Lazy.force only_constant_choices
325 if List.length !choices > 0 then !choices else raise NoChoice
331 let interactive_interpretation_choice interpretations =
332 let chosen = ref None in
335 ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
336 let vbox = GPack.vbox ~packing:window#add () in
340 ("Ambiguous input since there are many well-typed interpretations." ^
341 " Please, choose one of them.")
342 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
344 GPack.notebook ~scrollable:true
345 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
348 (function interpretation ->
350 let expected_height = 18 * List.length interpretation in
351 let height = if expected_height > 400 then 400 else expected_height in
352 GList.clist ~columns:2 ~packing:notebook#append_page ~height
353 ~titles:["id" ; "URI"] ()
357 (function (id,uri) ->
358 let n = clist#append [id;uri] in
359 clist#set_row ~selectable:false n
362 clist#columns_autosize ()
365 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
367 GButton.button ~label:"Ok"
368 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
370 GButton.button ~label:"Abort"
371 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
373 ignore (window#connect#destroy GMain.Main.quit) ;
374 ignore (cancelb#connect#clicked window#destroy) ;
377 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
378 window#set_position `CENTER ;
382 None -> raise NoChoice
390 save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
393 let struri = UriManager.string_of_uri uri in
394 let idx = (String.rindex struri '/') + 1 in
395 String.sub struri idx (String.length struri - idx)
397 let path = pathname ^ "/" ^ name in
399 Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
403 Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
404 ~ask_dtd_to_the_getter:false
407 let innertypesuri = UriManager.innertypesuri_of_uri uri in
408 Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
409 Http_getter.register' innertypesuri
410 (Helm_registry.get "local_library.url" ^
411 Str.replace_first (Str.regexp "^cic:") ""
412 (UriManager.string_of_uri innertypesuri) ^ ".xml"
414 (* constant type / variable / mutual inductive types definition *)
415 Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
416 Http_getter.register' uri
417 (Helm_registry.get "local_library.url" ^
418 Str.replace_first (Str.regexp "^cic:") ""
419 (UriManager.string_of_uri uri) ^ ".xml"
426 match UriManager.bodyuri_of_uri uri with
428 | Some bodyuri -> bodyuri
430 Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
431 Http_getter.register' bodyuri
432 (Helm_registry.get "local_library.url" ^
433 Str.replace_first (Str.regexp "^cic:") ""
434 (UriManager.string_of_uri bodyuri) ^ ".xml"
441 exception OpenConjecturesStillThere;;
442 exception WrongProof;;
444 let pathname_of_annuri uristring =
445 Helm_registry.get "local_library.dir" ^
446 Str.replace_first (Str.regexp "^cic:") "" uristring
449 let make_dirs dirpath =
450 ignore (Unix.system ("mkdir -p " ^ dirpath))
453 let save_obj uri obj =
455 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
456 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
458 Cic2acic.acic_object_of_cic_object ~eta_fix:false obj
460 (* let's save the theorem and register it to the getter *)
461 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
463 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
468 match ProofEngine.get_proof () with
470 | Some (uri,[],bo,ty) ->
471 let uri = match uri with Some uri -> uri | _ -> assert false in
472 (* we want to typecheck in the ENV *)
473 (*let old_working = CicUniv.get_working () in
474 CicUniv.set_working (CicUniv.get_global ());*)
475 CicUniv.directly_to_env_begin () ;
476 prerr_endline "-------------> QED";
478 CicReduction.are_convertible []
479 (CicTypeChecker.type_of_aux' [] [] bo) ty
482 (*CSC: Wrong: [] is just plainly wrong *)
483 let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
484 let (acic,ids_to_inner_types,ids_to_inner_sorts) =
485 (rendering_window ())#output#load_proof uri proof
487 !qed_set_sensitive false ;
488 (* let's save the theorem and register it to the getter *)
489 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
491 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
493 (* add the object to the env *)
494 CicEnvironment.add_type_checked_term uri (
495 Cic.Constant ((UriManager.name_of_uri uri),(Some bo),ty,[]));
496 (* FIXME: the variable list!! *)
498 CicUniv.qed (); (* now the env has the right constraints *)*)
499 CicUniv.directly_to_env_end();
500 CicUniv.reset_working ();
501 prerr_endline "-------------> FINE";
505 | _ -> raise OpenConjecturesStillThere
508 (** save an unfinished proof on the filesystem *)
509 let save_unfinished_proof () =
510 let (xml, bodyxml) = ProofEngine.get_current_status_as_xml () in
511 let proof_file_type = Helm_registry.get "gtoplevel.proof_file_type" in
512 let proof_file = Helm_registry.get "gtoplevel.proof_file" in
513 Xml.pp ~quiet:true xml (Some proof_file_type) ;
515 (`Msg (`T ("Current proof type saved to " ^ proof_file_type))) ;
516 Xml.pp ~quiet:true bodyxml (Some proof_file) ;
518 (`Msg (`T ("Current proof body saved to " ^ proof_file)))
521 (* Used to typecheck the loaded proofs *)
522 let typecheck_loaded_proof metasenv bo ty =
523 let module T = CicTypeChecker in
526 (fun metasenv ((_,context,ty) as conj) ->
527 ignore (T.type_of_aux' metasenv context ty) ;
530 ignore (T.type_of_aux' metasenv [] ty) ;
531 ignore (T.type_of_aux' metasenv [] bo)
534 let decompose_uris_choice_callback uris =
535 (* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
536 let module U = UriManager in
539 match MQueryMisc.cic_textual_parser_uri_of_string uri with
540 CicTextualParser0.IndTyUri (uri,typeno) -> (uri,typeno,[])
542 (interactive_user_uri_choice
543 ~selection_mode:`MULTIPLE ~ok:"Ok" ~enable_button_for_non_vars:false
544 ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose"
546 (function (uri,typeno,_) ->
547 U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1)
552 let mk_fresh_name_callback metasenv context name ~typ =
554 match FreshNamesGenerator.mk_fresh_name metasenv context name ~typ with
555 Cic.Name fresh_name -> fresh_name
556 | Cic.Anonymous -> assert false
559 GToolbox.input_string ~title:"Enter a fresh hypothesis name" ~text:fresh_name
560 ("Enter a fresh name for the hypothesis " ^
562 (List.map (function None -> None | Some (n,_) -> Some n) context))
564 Some fresh_name' -> Cic.Name fresh_name'
565 | None -> raise NoChoice
568 let refresh_proof (output : TermViewer.proof_viewer) =
570 let uri,currentproof =
571 match ProofEngine.get_proof () with
573 | Some (uri,metasenv,bo,ty) ->
574 ProofEngine.set_proof (Some (uri,metasenv,bo,ty)) ;
575 if List.length metasenv = 0 then
577 !qed_set_sensitive true ;
582 (*CSC: Wrong: [] is just plainly wrong *)
583 let uri = match uri with Some uri -> uri | _ -> assert false in
585 Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
587 ignore (output#load_proof uri currentproof)
590 match ProofEngine.get_proof () with
592 | Some (uri,metasenv,bo,ty) ->
593 debug_print ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[])));
594 raise (InvokeTactics.RefreshProofException e)
596 let set_proof_engine_goal g =
597 ProofEngine.goal := g
600 let refresh_goals ?(empty_notebook=true) notebook =
602 match !ProofEngine.goal with
604 if empty_notebook then
606 notebook#remove_all_pages ~skip_switch_page_event:false ;
607 notebook#set_empty_page
610 notebook#proofw#unload
613 match ProofEngine.get_proof () with
615 | Some (_,metasenv,_,_) -> metasenv
618 List.find (function (m,_,_) -> m=metano) metasenv
620 let regenerate_notebook () =
621 let skip_switch_page_event =
623 (m,_,_)::_ when m = metano -> false
626 notebook#remove_all_pages ~skip_switch_page_event ;
627 List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
629 if empty_notebook then
631 regenerate_notebook () ;
632 notebook#set_current_page
633 ~may_skip_switch_page_event:false metano
637 notebook#set_current_page
638 ~may_skip_switch_page_event:true metano ;
639 prerr_endline "CIAO CIAO" ;
640 prerr_endline ("SEQUENTE CORRENTE: " ^ SequentPp.TextualPp.print_sequent currentsequent) ;
641 notebook#proofw#load_sequent metasenv currentsequent ;
642 prerr_endline "pASSO CIAO CIAO"
647 match !ProofEngine.goal with
652 match ProofEngine.get_proof () with
654 | Some (_,metasenv,_,_) -> metasenv
657 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
659 ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent);
660 raise (InvokeTactics.RefreshSequentException e)
662 debug_print ("Offending sequent " ^ string_of_int metano ^ " unknown.");
663 raise (InvokeTactics.RefreshSequentException e)
665 module InvokeTacticsCallbacks =
667 let sequent_viewer () = (rendering_window ())#notebook#proofw
668 let term_editor () = (rendering_window ())#inputt
669 let scratch_window () = (rendering_window ())#scratch_window
671 let refresh_proof () =
672 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
675 let refresh_goals () =
676 let notebook = (rendering_window ())#notebook in
677 refresh_goals notebook
679 let decompose_uris_choice_callback = decompose_uris_choice_callback
680 let mk_fresh_name_callback = mk_fresh_name_callback
681 let mqi_handle = mqi_handle
684 module InvokeTactics' = InvokeTactics.Make (InvokeTacticsCallbacks);;
686 (* Just to initialize the Hbugs module *)
687 module Ignore = Hbugs.Initialize (InvokeTactics');;
688 Hbugs.set_describe_hint_callback (fun hint ->
690 | Hbugs_types.Use_apply_Luke term -> check_window [term]
694 let dummy_uri = "/dummy.con"
696 (** load an unfinished proof from filesystem *)
697 let load_unfinished_proof () =
698 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
699 let notebook = (rendering_window ())#notebook in
702 GToolbox.input_string ~title:"Load Unfinished Proof" ~text:dummy_uri
705 None -> raise NoChoice
707 let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
708 let proof_file_type = Helm_registry.get "gtoplevel.proof_file_type" in
709 let proof_file = Helm_registry.get "gtoplevel.proof_file" in
710 match CicParser.obj_of_xml proof_file_type (Some proof_file) with
711 Cic.CurrentProof (_,metasenv,bo,ty,_) ->
712 typecheck_loaded_proof metasenv bo ty ;
713 ProofEngine.set_proof (Some (Some uri, metasenv, bo, ty));
714 refresh_proof output ;
715 set_proof_engine_goal
718 | (metano,_,_)::_ -> Some metano
720 refresh_goals notebook ;
722 (`Msg (`T ("Current proof type loaded from " ^ proof_file_type)));
724 (`Msg (`T ("Current proof body loaded from " ^ proof_file))) ;
725 !save_set_sensitive true;
728 InvokeTactics.RefreshSequentException e ->
730 (`Error (`T ("Exception raised during the refresh of the " ^
731 "sequent: " ^ Printexc.to_string e)))
732 | InvokeTactics.RefreshProofException e ->
734 (`Error (`T ("Exception raised during the refresh of the " ^
735 "proof: " ^ Printexc.to_string e)))
738 (`Error (`T (Printexc.to_string e)))
741 let clear_aliases () =
742 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
743 inputt#environment :=
744 DisambiguatingParser.EnvironmentP3.of_string
745 DisambiguatingParser.EnvironmentP3.empty
748 let edit_aliases () =
749 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
750 let disambiguation_env = inputt#environment in
751 let chosen_aliases = ref None in
754 ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
756 GPack.vbox ~border_width:0 ~packing:window#add () in
757 let scrolled_window =
758 GBin.scrolled_window ~border_width:10
759 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
760 let input = GText.view ~editable:true ~width:400 ~height:100
761 ~packing:scrolled_window#add () in
763 GPack.hbox ~border_width:0
764 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
766 GButton.button ~label:"Ok"
767 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
769 GButton.button ~label:"Clear"
770 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
772 GButton.button ~label:"Cancel"
773 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
774 ignore (window#connect#destroy GMain.Main.quit) ;
775 ignore (cancelb#connect#clicked window#destroy) ;
776 ignore (clearb#connect#clicked (fun () ->
777 input#buffer#set_text DisambiguatingParser.EnvironmentP3.empty)) ;
778 ignore (okb#connect#clicked (fun () ->
779 chosen_aliases := Some (input#buffer#get_text ());
782 (input#buffer#insert ~iter:(input#buffer#get_iter_at_char 0)
783 (DisambiguatingParser.EnvironmentP3.to_string !disambiguation_env ^ "\n"));
786 match !chosen_aliases with
788 | Some raw_aliases ->
789 let new_disambiguation_env =
791 DisambiguatingParser.EnvironmentP3.of_string raw_aliases
795 ("Error while parsing aliases: " ^ Printexc.to_string e)));
798 disambiguation_env := new_disambiguation_env
802 let module L = LogicalOperations in
803 let module G = Gdome in
804 let notebook = (rendering_window ())#notebook in
805 let output = (rendering_window ())#output in
807 output#make_sequent_of_selected_term ;
808 refresh_proof output ;
809 refresh_goals notebook
811 InvokeTactics.RefreshSequentException e ->
813 (`Error (`T ("Exception raised during the refresh of the " ^
814 "sequent: " ^ Printexc.to_string e)))
815 | InvokeTactics.RefreshProofException e ->
817 (`Error (`T ("Exception raised during the refresh of the " ^
818 "proof: " ^ Printexc.to_string e)))
821 (`Error (`T (Printexc.to_string e)))
825 let module L = LogicalOperations in
826 let module G = Gdome in
827 let notebook = (rendering_window ())#notebook in
828 let output = (rendering_window ())#output in
830 output#focus_sequent_of_selected_term ;
831 refresh_goals notebook
833 InvokeTactics.RefreshSequentException e ->
835 (`Error (`T ("Exception raised during the refresh of the " ^
836 "sequent: " ^ Printexc.to_string e)))
837 | InvokeTactics.RefreshProofException e ->
839 (`Error (`T ("Exception raised during the refresh of the " ^
840 "proof: " ^ Printexc.to_string e)))
843 (`Error (`T (Printexc.to_string e)))
846 exception NoPrevGoal;;
847 exception NoNextGoal;;
850 let module L = LogicalOperations in
851 let module G = Gdome in
852 let notebook = (rendering_window ())#notebook in
853 let output = (rendering_window ())#output in
855 match ProofEngine.get_proof () with
857 | Some (_,metasenv,_,_) -> metasenv
860 refresh_goals ~empty_notebook:false notebook
862 InvokeTactics.RefreshSequentException e ->
864 (`Error (`T ("Exception raised during the refresh of the " ^
865 "sequent: " ^ Printexc.to_string e)))
868 (`Error (`T (Printexc.to_string e)))
872 show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
875 GWindow.window ~width:800 ~border_width:2 () in
876 let scrolled_window =
877 GBin.scrolled_window ~border_width:10 ~packing:window#add () in
879 GMathViewAux.single_selection_math_view
880 ~packing:scrolled_window#add ~width:600 ~height:400 ()
882 let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
883 let href = Gdome.domString "href" in
884 let show_in_show_window_obj uri obj =
887 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
888 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
890 Cic2acic.acic_object_of_cic_object obj
893 ChosenTransformer.mml_of_cic_object
894 ~explode_all:false uri acic ids_to_inner_sorts ids_to_inner_types
896 window#set_title (UriManager.string_of_uri uri) ;
897 window#misc#hide () ; window#show () ;
898 mmlwidget#load_root mml#get_documentElement ;
902 (`Error (`T (Printexc.to_string e)))
904 let show_in_show_window_uri uri =
905 let obj = CicEnvironment.get_obj uri in
906 show_in_show_window_obj uri obj
908 let show_in_show_window_callback mmlwidget ((n : Gdome.element option),_,_,_) =
912 if n'#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
914 (n'#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
916 show_in_show_window_uri (UriManager.uri_of_string uri)
918 ignore (mmlwidget#action_toggle n')
921 mmlwidget#connect#click (show_in_show_window_callback mmlwidget)
923 show_in_show_window_obj, show_in_show_window_uri,
924 show_in_show_window_callback
927 exception NoObjectsLocated;;
929 let user_uri_choice ~title ~msg uris =
932 [] -> raise NoObjectsLocated
936 interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
941 String.sub uri 4 (String.length uri - 4)
944 let locate_callback id =
945 let query = MQG.locate id in
946 let result = MQI.execute mqi_handle query in
950 MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format' uri)
952 HelmLogger.log (`Msg (`T "Locate Query:")) ;
953 MQueryUtil.text_of_query (fun m -> HelmLogger.log (`Msg (`T m))) "" query;
954 HelmLogger.log (`Msg (`T "Result:")) ;
955 MQueryUtil.text_of_result (fun m -> HelmLogger.log (`Msg (`T m))) "" result;
956 user_uri_choice ~title:"Ambiguous input."
958 ("Ambiguous input \"" ^ id ^
959 "\". Please, choose one interpetation:")
964 let input_or_locate_uri ~title =
965 let uri = ref None in
968 ~width:400 ~modal:true ~title ~border_width:2 () in
969 let vbox = GPack.vbox ~packing:window#add () in
971 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
973 GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
975 GEdit.entry ~editable:true
976 ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
978 GButton.button ~label:"Check"
979 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
980 let _ = checkb#misc#set_sensitive false in
982 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
984 GMisc.label ~text:"You can also enter an indentifier to locate:"
985 ~packing:(hbox2#pack ~padding:5) () in
987 GEdit.entry ~editable:true
988 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
990 GButton.button ~label:"Locate"
991 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
992 let _ = locateb#misc#set_sensitive false in
994 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
996 GButton.button ~label:"Ok"
997 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
998 let _ = okb#misc#set_sensitive false in
1000 GButton.button ~label:"Cancel"
1001 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
1003 ignore (window#connect#destroy GMain.Main.quit) ;
1005 (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
1006 let check_callback () =
1007 let uri = "cic:" ^ manual_input#text in
1009 ignore (Http_getter.resolve' (UriManager.uri_of_string uri)) ;
1010 HelmLogger.log (`Msg (`T "OK")) ;
1013 Http_getter_types.Unresolvable_URI _ ->
1015 (`Error (`T ("URI " ^ uri ^
1016 " does not correspond to any object."))) ;
1018 | UriManager.IllFormedUri _ ->
1020 (`Error (`T ("URI " ^ uri ^ " is not well-formed."))) ;
1024 (`Error (`T (Printexc.to_string e))) ;
1028 (okb#connect#clicked
1030 if check_callback () then
1032 uri := Some manual_input#text ;
1036 ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1038 (manual_input#connect#changed
1040 if manual_input#text = "" then
1042 checkb#misc#set_sensitive false ;
1043 okb#misc#set_sensitive false
1047 checkb#misc#set_sensitive true ;
1048 okb#misc#set_sensitive true
1051 (locate_input#connect#changed
1052 (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1054 (locateb#connect#clicked
1056 let id = locate_input#text in
1057 manual_input#set_text (locate_callback id) ;
1058 locate_input#delete_text 0 (String.length id)
1063 None -> raise NoChoice
1064 | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1067 exception AmbiguousInput;;
1069 (* A WIDGET TO ENTER CIC TERMS *)
1071 module DisambiguateCallbacks =
1073 let interactive_user_uri_choice =
1074 fun ~selection_mode ?ok ?enable_button_for_non_vars ~title ~msg ~id ->
1075 interactive_user_uri_choice ~selection_mode ?ok
1076 ?enable_button_for_non_vars ~title ~msg
1077 let interactive_interpretation_choice = interactive_interpretation_choice
1078 let input_or_locate_uri ~title ?id () = input_or_locate_uri ~title
1082 module TermEditor' = ChosenTermEditor.Make (DisambiguateCallbacks);;
1084 (* OTHER FUNCTIONS *)
1087 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1090 GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1092 None -> raise NoChoice
1094 let uri = locate_callback input in
1099 (`Error (`T (Printexc.to_string e)))
1103 exception UriAlreadyInUse;;
1104 exception NotAUriToAConstant;;
1106 let new_inductive () =
1107 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1108 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1109 let notebook = (rendering_window ())#notebook in
1111 let chosen = ref false in
1112 let inductive = ref true in
1113 let paramsno = ref 0 in
1114 let get_uri = ref (function _ -> assert false) in
1115 let get_base_uri = ref (function _ -> assert false) in
1116 let get_names = ref (function _ -> assert false) in
1117 let get_types_and_cons = ref (function _ -> assert false) in
1118 let get_context_and_subst = ref (function _ -> assert false) in
1121 ~width:600 ~modal:true ~position:`CENTER
1122 ~title:"New Block of Mutual (Co)Inductive Definitions"
1123 ~border_width:2 () in
1124 let vbox = GPack.vbox ~packing:window#add () in
1126 GPack.hbox ~border_width:0
1127 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1129 GMisc.label ~text:"Enter the URI for the new block:"
1130 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1132 GEdit.entry ~editable:true
1133 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1135 GPack.hbox ~border_width:0
1136 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1140 "Enter the number of left parameters in every arity and constructor type:"
1141 ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1142 let paramsno_entry =
1143 GEdit.entry ~editable:true ~text:"0"
1144 ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1146 GPack.hbox ~border_width:0
1147 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1149 GMisc.label ~text:"Are the definitions inductive or coinductive?"
1150 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1152 GButton.radio_button ~label:"Inductive"
1153 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1155 GButton.radio_button ~label:"Coinductive"
1156 ~group:inductiveb#group
1157 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1159 GPack.hbox ~border_width:0
1160 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1162 GMisc.label ~text:"Enter the list of the names of the types:"
1163 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1165 GEdit.entry ~editable:true
1166 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1168 GPack.hbox ~border_width:0
1169 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1171 GButton.button ~label:"> Next"
1172 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1173 let _ = okb#misc#set_sensitive true in
1175 GButton.button ~label:"Abort"
1176 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1177 ignore (window#connect#destroy GMain.Main.quit) ;
1178 ignore (cancelb#connect#clicked window#destroy) ;
1182 (okb#connect#clicked
1185 let uristr = "cic:" ^ uri_entry#text in
1186 let namesstr = names_entry#text in
1187 let paramsno' = int_of_string (paramsno_entry#text) in
1188 match Str.split (Str.regexp " +") namesstr with
1190 | (he::tl) as names ->
1191 let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1194 ignore (Http_getter.resolve' uri) ;
1195 raise UriAlreadyInUse
1196 with Http_getter_types.Unresolvable_URI _ ->
1197 get_uri := (function () -> uri) ;
1198 get_names := (function () -> names) ;
1199 inductive := inductiveb#active ;
1200 paramsno := paramsno' ;
1206 (`Error (`T (Printexc.to_string e)))
1214 GBin.frame ~label:name
1215 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1216 let vbox = GPack.vbox ~packing:frame#add () in
1217 let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1219 GMisc.label ~text:("Enter its type:")
1220 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1221 let scrolled_window =
1222 GBin.scrolled_window ~border_width:5
1223 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1225 TermEditor'.term_editor
1227 ~width:400 ~height:20 ~packing:scrolled_window#add
1228 ~share_environment_with:inputt ()
1229 ~isnotempty_callback:
1231 (*non_empty_type := b ;*)
1232 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1235 GPack.hbox ~border_width:0
1236 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1238 GMisc.label ~text:("Enter the list of its constructors:")
1239 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1240 let cons_names_entry =
1241 GEdit.entry ~editable:true
1242 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1243 (newinputt,cons_names_entry)
1246 vbox#remove hboxn#coerce ;
1248 GPack.hbox ~border_width:0
1249 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1251 GButton.button ~label:"> Next"
1252 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1254 GButton.button ~label:"Abort"
1255 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1256 ignore (cancelb#connect#clicked window#destroy) ;
1258 (okb#connect#clicked
1261 let names = !get_names () in
1262 let types_and_cons =
1264 (fun name (newinputt,cons_names_entry) ->
1265 let consnamesstr = cons_names_entry#text in
1266 let cons_names = Str.split (Str.regexp " +") consnamesstr in
1268 newinputt#get_metasenv_and_term ~context:[] ~metasenv:[]
1271 [] -> expr,cons_names
1272 | _ -> raise AmbiguousInput
1273 ) names type_widgets
1275 let uri = !get_uri () in
1277 (* Let's see if so far the definition is well-typed *)
1280 (* To test if the arities of the inductive types are well *)
1281 (* typed, we check the inductive block definition where *)
1282 (* no constructor is given to each type. *)
1285 (fun name (ty,cons) -> (name, !inductive, ty, []))
1286 names types_and_cons
1288 CicTypeChecker.typecheck_mutual_inductive_defs uri
1289 (tys,params,paramsno)
1291 get_context_and_subst :=
1295 (fun (context,subst) name (ty,_) ->
1297 (Some (Cic.Name name, Cic.Decl ty))::context,
1298 (Cic.MutInd (uri,!i,[]))::subst
1301 ) ([],[]) names types_and_cons) ;
1302 let types_and_cons' =
1304 (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1305 names types_and_cons
1307 get_types_and_cons := (function () -> types_and_cons') ;
1313 (`Error (`T (Printexc.to_string e)))
1316 and phase3 name cons =
1317 let get_cons_types = ref (function () -> assert false) in
1320 ~width:600 ~modal:true ~position:`CENTER
1321 ~title:(name ^ " Constructors")
1322 ~border_width:2 () in
1323 let vbox = GPack.vbox ~packing:window2#add () in
1324 let cons_type_widgets =
1326 (function consname ->
1328 GPack.hbox ~border_width:0
1329 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1331 GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1332 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1333 let scrolled_window =
1334 GBin.scrolled_window ~border_width:5
1335 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1337 TermEditor'.term_editor
1339 ~width:400 ~height:20 ~packing:scrolled_window#add
1340 ~share_environment_with:inputt ()
1341 ~isnotempty_callback:
1343 (* (*non_empty_type := b ;*)
1344 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1349 GPack.hbox ~border_width:0
1350 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1352 GButton.button ~label:"> Next"
1353 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1354 let _ = okb#misc#set_sensitive true in
1356 GButton.button ~label:"Abort"
1357 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1358 ignore (window2#connect#destroy GMain.Main.quit) ;
1359 ignore (cancelb#connect#clicked window2#destroy) ;
1361 (okb#connect#clicked
1365 let context,subst= !get_context_and_subst () in
1370 inputt#get_metasenv_and_term ~context ~metasenv:[]
1374 let undebrujined_expr =
1376 (fun expr t -> CicSubstitution.subst t expr) expr subst
1378 name, undebrujined_expr
1379 | _ -> raise AmbiguousInput
1380 ) cons cons_type_widgets
1382 get_cons_types := (function () -> cons_types) ;
1387 (`Error (`T (Printexc.to_string e)))
1391 let okb_pressed = !chosen in
1393 if (not okb_pressed) then
1396 assert false (* The control never reaches this point *)
1399 (!get_cons_types ())
1402 (* No more phases left or Abort pressed *)
1408 let uri = !get_uri () in
1411 let tys = !get_types_and_cons () in
1412 let obj = Cic.InductiveDefinition(tys,params,!paramsno) in
1415 debug_print (CicPp.ppobj obj);
1416 CicTypeChecker.typecheck_mutual_inductive_defs uri
1417 (tys,params,!paramsno) ;
1420 debug_print "Offending mutual (co)inductive type declaration:" ;
1421 debug_print (CicPp.ppobj obj) ;
1423 (* We already know that obj is well-typed. We need to add it to the *)
1424 (* environment in order to compute the inner-types without having to *)
1425 (* debrujin it or having to modify lots of other functions to avoid *)
1426 (* asking the environment for the MUTINDs we are defining now. *)
1427 CicEnvironment.put_inductive_definition uri obj ;
1429 show_in_show_window_obj uri obj
1433 (`Error (`T (Printexc.to_string e)))
1437 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1438 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1439 let notebook = (rendering_window ())#notebook in
1441 let chosen = ref false in
1442 let get_metasenv_and_term = ref (function _ -> assert false) in
1443 let get_uri = ref (function _ -> assert false) in
1444 let non_empty_type = ref false in
1447 ~width:600 ~modal:true ~title:"New Proof or Definition"
1448 ~border_width:2 () in
1449 let vbox = GPack.vbox ~packing:window#add () in
1451 GPack.hbox ~border_width:0
1452 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1454 GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1455 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1457 GEdit.entry ~editable:true
1458 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1459 uri_entry#set_text dummy_uri;
1460 uri_entry#select_region ~start:1 ~stop:(String.length dummy_uri);
1462 GPack.hbox ~border_width:0
1463 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1465 GMisc.label ~text:"Enter the theorem or definition type:"
1466 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1467 let scrolled_window =
1468 GBin.scrolled_window ~border_width:5
1469 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1470 (* the content of the scrolled_window is moved below (see comment) *)
1472 GPack.hbox ~border_width:0
1473 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1475 GButton.button ~label:"Ok"
1476 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1477 let _ = okb#misc#set_sensitive false in
1479 GButton.button ~label:"Cancel"
1480 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1481 (* moved here to have visibility of the ok button *)
1483 TermEditor'.term_editor
1485 ~width:400 ~height:100 ~packing:scrolled_window#add
1486 ~share_environment_with:inputt ()
1487 ~isnotempty_callback:
1489 non_empty_type := b ;
1490 okb#misc#set_sensitive (b && uri_entry#text <> ""))
1493 newinputt#set_term inputt#get_as_string ;
1496 uri_entry#connect#changed
1498 okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1500 ignore (window#connect#destroy GMain.Main.quit) ;
1501 ignore (cancelb#connect#clicked window#destroy) ;
1503 (okb#connect#clicked
1507 let metasenv,parsed = newinputt#get_metasenv_and_term [] [] in
1508 let uristr = "cic:" ^ uri_entry#text in
1509 let uri = UriManager.uri_of_string uristr in
1510 if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1511 raise NotAUriToAConstant
1515 ignore (Http_getter.resolve' uri) ;
1516 raise UriAlreadyInUse
1517 with Http_getter_types.Unresolvable_URI _ ->
1518 get_metasenv_and_term := (function () -> metasenv,parsed) ;
1519 get_uri := (function () -> uri) ;
1525 (`Error (`T (Printexc.to_string e)))
1531 let metasenv,expr = !get_metasenv_and_term () in
1532 let _ = CicTypeChecker.type_of_aux' metasenv [] expr in
1533 ProofEngine.set_proof
1534 (Some (Some (!get_uri ()), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr));
1535 set_proof_engine_goal (Some 1) ;
1536 refresh_goals notebook ;
1537 refresh_proof output ;
1538 !save_set_sensitive true ;
1540 ProofEngine.intros ~mk_fresh_name_callback () ;
1541 refresh_goals notebook ;
1542 refresh_proof output
1544 InvokeTactics.RefreshSequentException e ->
1546 (`Error (`T ("Exception raised during the refresh of the " ^
1547 "sequent: " ^ Printexc.to_string e)))
1548 | InvokeTactics.RefreshProofException e ->
1550 (`Error (`T ("Exception raised during the refresh of the " ^
1551 "proof: " ^ Printexc.to_string e)))
1554 (`Error (`T (Printexc.to_string e)))
1557 let check_term_in_scratch scratch_window metasenv context expr =
1559 let ty = CicTypeChecker.type_of_aux' metasenv context expr in
1560 let expr = Cic.Cast (expr,ty) in
1561 scratch_window#show () ;
1562 scratch_window#set_term expr ;
1563 scratch_window#set_context context ;
1564 scratch_window#set_metasenv metasenv ;
1565 scratch_window#sequent_viewer#load_sequent metasenv (111,context,expr)
1568 print_endline ("? " ^ CicPp.ppterm expr) ;
1572 let check scratch_window () =
1573 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1575 match ProofEngine.get_proof () with
1577 | Some (_,metasenv,_,_) -> metasenv
1580 match !ProofEngine.goal with
1583 let (_,canonical_context,_) =
1584 List.find (function (m,_,_) -> m=metano) metasenv
1589 let metasenv',expr = inputt#get_metasenv_and_term context metasenv in
1590 check_term_in_scratch scratch_window metasenv' context expr
1594 (`Error (`T (Printexc.to_string e)))
1599 show_in_show_window_uri (input_or_locate_uri ~title:"Show")
1603 (`Error (`T (Printexc.to_string e)))
1606 exception NotADefinition;;
1609 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1610 let notebook = (rendering_window ())#notebook in
1612 let uri = input_or_locate_uri ~title:"Open" in
1613 ignore(CicTypeChecker.typecheck uri);
1614 (* TASSI: typecheck mette la uri nell'env... cosa fa la open_ ?*)
1615 let metasenv,bo,ty =
1616 match CicEnvironment.get_cooked_obj uri with
1617 Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
1618 | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
1621 | Cic.InductiveDefinition _ -> raise NotADefinition
1623 ProofEngine.set_proof (Some (Some uri, metasenv, bo, ty)) ;
1624 set_proof_engine_goal None ;
1625 refresh_goals notebook ;
1626 refresh_proof output ;
1627 !save_set_sensitive true
1629 InvokeTactics.RefreshSequentException e ->
1631 (`Error (`T ("Exception raised during the refresh of the " ^
1632 "sequent: " ^ Printexc.to_string e)))
1633 | InvokeTactics.RefreshProofException e ->
1635 (`Error (`T ("Exception raised during the refresh of the " ^
1636 "proof: " ^ Printexc.to_string e)))
1639 (`Error (`T (Printexc.to_string e)))
1642 let show_query_results results =
1645 ~modal:false ~title:"Query results." ~border_width:2 () in
1646 let vbox = GPack.vbox ~packing:window#add () in
1648 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1651 ~text:"Click on a URI to show that object"
1652 ~packing:hbox#add () in
1653 let scrolled_window =
1654 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1655 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1656 let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
1659 (function (uri,_) ->
1663 clist#set_row ~selectable:false n
1666 clist#columns_autosize () ;
1668 (clist#connect#select_row
1669 (fun ~row ~column ~event ->
1670 let (uristr,_) = List.nth results row in
1672 MQueryMisc.cic_textual_parser_uri_of_string
1673 (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
1676 CicTextualParser0.ConUri uri
1677 | CicTextualParser0.VarUri uri
1678 | CicTextualParser0.IndTyUri (uri,_)
1679 | CicTextualParser0.IndConUri (uri,_,_) ->
1680 show_in_show_window_uri uri
1686 let refine_constraints (must_obj,must_rel,must_sort) =
1687 let chosen = ref false in
1688 let use_only = ref false in
1691 ~modal:true ~title:"Constraints refinement."
1692 ~width:800 ~border_width:2 () in
1693 let vbox = GPack.vbox ~packing:window#add () in
1695 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1698 ~text: "\"Only\" constraints can be enforced or not."
1699 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1701 GButton.toggle_button ~label:"Enforce \"only\" constraints"
1702 ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1705 (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
1706 (* Notebook for the constraints choice *)
1708 GPack.notebook ~scrollable:true
1709 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1710 (* Rel constraints *)
1713 ~text: "Constraints on Rels" () in
1715 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1718 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1721 ~text: "You can now specify the constraints on Rels."
1722 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1723 let expected_height = 25 * (List.length must_rel + 2) in
1724 let height = if expected_height > 400 then 400 else expected_height in
1725 let scrolled_window =
1726 GBin.scrolled_window ~border_width:10 ~height ~width:600
1727 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1728 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1729 let mk_depth_button (hbox:GPack.box) d =
1730 let mutable_ref = ref (Some d) in
1732 GButton.toggle_button
1733 ~label:("depth = " ^ string_of_int d)
1735 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1738 (depthb#connect#toggled
1740 let sel_depth = if depthb#active then Some d else None in
1741 mutable_ref := sel_depth
1744 let rel_constraints =
1749 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1752 ~text:(MQGU.text_of_position (p:>MQGT.full_position))
1753 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1755 | `MainHypothesis None
1756 | `MainConclusion None -> p, ref None
1757 | `MainHypothesis (Some depth')
1758 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth'
1760 (* Sort constraints *)
1763 ~text: "Constraints on Sorts" () in
1765 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1768 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1771 ~text: "You can now specify the constraints on Sorts."
1772 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1773 let expected_height = 25 * (List.length must_sort + 2) in
1774 let height = if expected_height > 400 then 400 else expected_height in
1775 let scrolled_window =
1776 GBin.scrolled_window ~border_width:10 ~height ~width:600
1777 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1778 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1779 let sort_constraints =
1781 (function (p, sort) ->
1784 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1787 ~text:(MQGU.text_of_sort sort ^ " " ^ MQGU.text_of_position (p:>MQGT.full_position))
1788 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1790 | `MainHypothesis None
1791 | `MainConclusion None -> p, ref None, sort
1792 | `MainHypothesis (Some depth')
1793 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth', sort
1795 (* Obj constraints *)
1798 ~text: "Constraints on constants" () in
1800 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1803 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1806 ~text: "You can now specify the constraints on constants."
1807 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1808 let expected_height = 25 * (List.length must_obj + 2) in
1809 let height = if expected_height > 400 then 400 else expected_height in
1810 let scrolled_window =
1811 GBin.scrolled_window ~border_width:10 ~height ~width:600
1812 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1813 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1814 let obj_constraints =
1816 (function (p, uri) ->
1819 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1822 ~text:(uri ^ " " ^ (MQGU.text_of_position p))
1823 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1828 | `MainHypothesis None
1829 | `MainConclusion None -> p, ref None, uri
1830 | `MainHypothesis (Some depth')
1831 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth', uri
1833 (* Confirm/abort buttons *)
1835 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1837 GButton.button ~label:"Ok"
1838 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1840 GButton.button ~label:"Abort"
1841 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1843 ignore (window#connect#destroy GMain.Main.quit) ;
1844 ignore (cancelb#connect#clicked window#destroy) ;
1846 (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
1847 window#set_position `CENTER ;
1851 let chosen_must_rel =
1853 (function (position, ref_depth) -> MQGU.set_main_position position !ref_depth)
1856 let chosen_must_sort =
1858 (function (position, ref_depth, sort) ->
1859 MQGU.set_main_position position !ref_depth,sort)
1862 let chosen_must_obj =
1864 (function (position, ref_depth, uri) -> MQGU.set_full_position position !ref_depth, uri)
1867 (chosen_must_obj,chosen_must_rel,chosen_must_sort),
1869 (*CSC: ???????????????????????? I assume that must and only are the same... *)
1870 Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
1878 let completeSearchPattern () =
1879 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1881 let metasenv,expr = inputt#get_metasenv_and_term ~context:[] ~metasenv:[] in
1882 let must = CGSearchPattern.get_constraints expr in
1883 let must',only = refine_constraints must in
1885 MQG.query_of_constraints (Some CGSearchPattern.universe) must' only
1887 let results = MQI.execute mqi_handle query in
1888 show_query_results results
1892 (`Error (`T (Printexc.to_string e)))
1895 let insertQuery () =
1897 let chosen = ref None in
1900 ~modal:true ~title:"Insert Query (Experts Only)" ~border_width:2 () in
1901 let vbox = GPack.vbox ~packing:window#add () in
1903 GMisc.label ~text:"Insert Query. For Experts Only."
1904 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1905 let scrolled_window =
1906 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1907 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1908 let input = GText.view ~editable:true
1909 ~packing:scrolled_window#add () in
1911 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1913 GButton.button ~label:"Ok"
1914 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1916 GButton.button ~label:"Load from file..."
1917 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1919 GButton.button ~label:"Abort"
1920 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1921 ignore (window#connect#destroy GMain.Main.quit) ;
1922 ignore (cancelb#connect#clicked window#destroy) ;
1924 (okb#connect#clicked
1926 chosen := Some (input#buffer#get_text ()) ; window#destroy ())) ;
1928 (loadb#connect#clicked
1931 GToolbox.select_file ~title:"Select Query File" ()
1935 let inch = open_in filename in
1936 let rec read_file () =
1938 let line = input_line inch in
1939 line ^ "\n" ^ read_file ()
1943 let text = read_file () in
1944 input#buffer#delete input#buffer#start_iter input#buffer#end_iter ;
1945 ignore (input#buffer#insert text))) ;
1946 window#set_position `CENTER ;
1953 MQI.execute mqi_handle (MQueryUtil.query_of_text (Lexing.from_string q))
1955 show_query_results results
1959 (`Error (`T (Printexc.to_string e)))
1962 let choose_must list_of_must only =
1963 let chosen = ref None in
1964 let user_constraints = ref [] in
1967 ~modal:true ~title:"Query refinement." ~border_width:2 () in
1968 let vbox = GPack.vbox ~packing:window#add () in
1970 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1974 ("You can now specify the genericity of the query. " ^
1975 "The more generic the slower.")
1976 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1978 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1982 "Suggestion: start with faster queries before moving to more generic ones."
1983 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1985 GPack.notebook ~scrollable:true
1986 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1989 let last = List.length list_of_must in
1995 (if !page = 1 then "More generic" else
1996 if !page = last then "More precise" else " ") () in
1997 let expected_height = 25 * (List.length must + 2) in
1998 let height = if expected_height > 400 then 400 else expected_height in
1999 let scrolled_window =
2000 GBin.scrolled_window ~border_width:10 ~height ~width:600
2001 ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2003 GList.clist ~columns:2 ~packing:scrolled_window#add
2004 ~titles:["URI" ; "Position"] ()
2008 (function (position, uri) ->
2011 [uri; MQGUtil.text_of_position position]
2013 clist#set_row ~selectable:false n
2016 clist#columns_autosize ()
2019 let label = GMisc.label ~text:"User provided" () in
2021 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2023 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2026 ~text:"Select the constraints that must be satisfied and press OK."
2027 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2028 let expected_height = 25 * (List.length only + 2) in
2029 let height = if expected_height > 400 then 400 else expected_height in
2030 let scrolled_window =
2031 GBin.scrolled_window ~border_width:10 ~height ~width:600
2032 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2034 GList.clist ~columns:2 ~packing:scrolled_window#add
2035 ~selection_mode:`MULTIPLE
2036 ~titles:["URI" ; "Position"] ()
2040 (function (position, uri) ->
2043 [uri; MQGUtil.text_of_position position]
2045 clist#set_row ~selectable:true n
2048 clist#columns_autosize () ;
2050 (clist#connect#select_row
2051 (fun ~row ~column ~event ->
2052 user_constraints := (List.nth only row)::!user_constraints)) ;
2054 (clist#connect#unselect_row
2055 (fun ~row ~column ~event ->
2058 (function uri -> uri != (List.nth only row)) !user_constraints)) ;
2061 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2063 GButton.button ~label:"Ok"
2064 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2066 GButton.button ~label:"Abort"
2067 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2069 ignore (window#connect#destroy GMain.Main.quit) ;
2070 ignore (cancelb#connect#clicked window#destroy) ;
2072 (okb#connect#clicked
2073 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2074 window#set_position `CENTER ;
2078 None -> raise NoChoice
2080 if n = List.length list_of_must then
2081 (* user provided constraints *)
2084 List.nth list_of_must n
2087 let searchPattern () =
2088 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
2091 match ProofEngine.get_proof () with
2092 None -> assert false
2093 | Some proof -> proof
2095 match !ProofEngine.goal with
2099 TacticChaser.matchConclusion mqi_handle
2100 ~choose_must () (proof, metano)
2103 user_uri_choice ~title:"Ambiguous input."
2104 ~msg: "Many lemmas can be successfully applied. Please, choose one:"
2107 inputt#set_term uri' ;
2108 InvokeTactics'.apply ()
2112 (`Error (`T (Printexc.to_string e)))
2115 let choose_selection mmlwidget (element : Gdome.element option) =
2116 let module G = Gdome in
2117 let rec aux element =
2118 if element#hasAttributeNS
2119 ~namespaceURI:Misc.helmns
2120 ~localName:(G.domString "xref")
2122 mmlwidget#set_selection (Some element)
2125 match element#get_parentNode with
2126 None -> assert false
2127 (*CSC: OCAML DIVERGES!
2128 | Some p -> aux (new G.element_of_node p)
2130 | Some p -> aux (new Gdome.element_of_node p)
2132 GdomeInit.DOMCastException _ ->
2134 "******* trying to select above the document root ********"
2138 | None -> mmlwidget#set_selection None
2141 (* STUFF TO BUILD THE GTK INTERFACE *)
2143 (* Stuff for the widget settings *)
2146 let export_to_postscript output =
2147 let lastdir = ref (Unix.getcwd ()) in
2150 GToolbox.select_file ~title:"Export to PostScript"
2151 ~dir:lastdir ~filename:"screenshot.ps" ()
2155 (output :> GMathView.math_view)#export_to_postscript
2156 ~filename:filename ();
2161 let activate_t1 output button_set_anti_aliasing
2162 button_set_transparency export_to_postscript_menu_item
2165 let is_set = button_t1#active in
2166 output#set_font_manager_type
2167 ~fm_type:(if is_set then `font_manager_t1 else `font_manager_gtk) ;
2170 button_set_anti_aliasing#misc#set_sensitive true ;
2171 button_set_transparency#misc#set_sensitive true ;
2172 export_to_postscript_menu_item#misc#set_sensitive true ;
2176 button_set_anti_aliasing#misc#set_sensitive false ;
2177 button_set_transparency#misc#set_sensitive false ;
2178 export_to_postscript_menu_item#misc#set_sensitive false ;
2182 let set_anti_aliasing output button_set_anti_aliasing () =
2183 output#set_anti_aliasing button_set_anti_aliasing#active
2186 let set_transparency output button_set_transparency () =
2187 output#set_transparency button_set_transparency#active
2191 let changefont output font_size_spinb () =
2192 output#set_font_size font_size_spinb#value_as_int
2195 let set_log_verbosity output log_verbosity_spinb () =
2196 output#set_log_verbosity log_verbosity_spinb#value_as_int
2199 class settings_window output sw
2200 export_to_postscript_menu_item selection_changed_callback
2202 let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2204 GPack.vbox ~packing:settings_window#add () in
2207 ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2208 ~border_width:5 ~packing:vbox#add () in
2210 GButton.toggle_button ~label:"activate t1 fonts"
2211 ~packing:(table#attach ~left:0 ~top:0) () in
2212 let button_set_anti_aliasing =
2213 GButton.toggle_button ~label:"set_anti_aliasing"
2214 ~packing:(table#attach ~left:0 ~top:1) () in
2215 let button_set_transparency =
2216 GButton.toggle_button ~label:"set_transparency"
2217 ~packing:(table#attach ~left:2 ~top:1) () in
2220 ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2221 ~border_width:5 ~packing:vbox#add () in
2222 let font_size_label =
2223 GMisc.label ~text:"font size:"
2224 ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2225 let font_size_spinb =
2227 GData.adjustment ~value:(float_of_int output#get_font_size)
2228 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2231 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2232 let log_verbosity_label =
2233 GMisc.label ~text:"log verbosity:"
2234 ~packing:(table#attach ~left:0 ~top:1) () in
2235 let log_verbosity_spinb =
2237 GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2240 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2242 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2244 GButton.button ~label:"Close"
2245 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2247 method show = settings_window#show
2249 button_set_anti_aliasing#misc#set_sensitive false ;
2250 button_set_transparency#misc#set_sensitive false ;
2251 (* Signals connection *)
2253 ignore(button_t1#connect#clicked
2254 (activate_t1 output button_set_anti_aliasing
2255 button_set_transparency export_to_postscript_menu_item button_t1)) ;
2257 ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2259 ignore(button_set_anti_aliasing#connect#toggled
2260 (set_anti_aliasing output button_set_anti_aliasing));
2261 ignore(button_set_transparency#connect#toggled
2262 (set_transparency output button_set_transparency)) ;
2264 ignore(log_verbosity_spinb#connect#changed
2265 (set_log_verbosity output log_verbosity_spinb)) ;
2266 ignore(closeb#connect#clicked settings_window#misc#hide)
2269 (* Scratch window *)
2271 class scratch_window =
2274 ~title:"MathML viewer"
2275 ~border_width:2 () in
2277 GPack.vbox ~packing:window#add () in
2279 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2281 GButton.button ~label:"Whd"
2282 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2284 GButton.button ~label:"Reduce"
2285 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2287 GButton.button ~label:"Simpl"
2288 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2289 let scrolled_window =
2290 GBin.scrolled_window ~border_width:10
2291 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2292 let sequent_viewer =
2293 TermViewer.sequent_viewer
2294 ~mml_of_cic_sequent:ChosenTransformer.mml_of_cic_sequent
2295 ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
2297 val mutable term = Cic.Rel 1 (* dummy value *)
2298 val mutable context = ([] : Cic.context) (* dummy value *)
2299 val mutable metasenv = ([] : Cic.metasenv) (* dummy value *)
2300 method sequent_viewer = sequent_viewer
2301 method show () = window#misc#hide () ; window#show ()
2303 method set_term t = term <- t
2304 method context = context
2305 method set_context t = context <- t
2306 method metasenv = metasenv
2307 method set_metasenv t = metasenv <- t
2310 (sequent_viewer#connect#selection_changed (choose_selection sequent_viewer));
2311 ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
2312 ignore(whdb#connect#clicked InvokeTactics'.whd_in_scratch) ;
2313 ignore(reduceb#connect#clicked InvokeTactics'.reduce_in_scratch) ;
2314 ignore(simplb#connect#clicked InvokeTactics'.simpl_in_scratch)
2317 let open_contextual_menu_for_selected_terms mmlwidget infos =
2318 let button = GdkEvent.Button.button infos in
2319 let terms_selected = List.length mmlwidget#get_selections > 0 in
2322 let time = GdkEvent.Button.time infos in
2323 let menu = GMenu.menu () in
2324 let f = new GMenu.factory menu in
2326 f#add_item "Whd" ~key:GdkKeysyms._W ~callback:InvokeTactics'.whd in
2327 let reduce_menu_item =
2328 f#add_item "Reduce" ~key:GdkKeysyms._R ~callback:InvokeTactics'.reduce in
2329 let simpl_menu_item =
2330 f#add_item "Simpl" ~key:GdkKeysyms._S ~callback:InvokeTactics'.simpl in
2331 let _ = f#add_separator () in
2332 let generalize_menu_item =
2333 f#add_item "Generalize"
2334 ~key:GdkKeysyms._G ~callback:InvokeTactics'.generalize in
2335 let _ = f#add_separator () in
2336 let clear_menu_item =
2337 f#add_item "Clear" ~key:GdkKeysyms._C ~callback:InvokeTactics'.clear in
2338 let clearbody_menu_item =
2339 f#add_item "ClearBody"
2340 ~key:GdkKeysyms._B ~callback:InvokeTactics'.clearbody
2342 whd_menu_item#misc#set_sensitive terms_selected ;
2343 reduce_menu_item#misc#set_sensitive terms_selected ;
2344 simpl_menu_item#misc#set_sensitive terms_selected ;
2345 generalize_menu_item#misc#set_sensitive terms_selected ;
2346 clear_menu_item#misc#set_sensitive terms_selected ;
2347 clearbody_menu_item#misc#set_sensitive terms_selected ;
2348 menu#popup ~button ~time
2354 let vbox1 = GPack.vbox () in
2356 val mutable proofw_ref = None
2357 val mutable compute_ref = None
2359 Lazy.force self#compute ;
2360 match proofw_ref with
2361 None -> assert false
2362 | Some proofw -> proofw
2363 method content = vbox1
2365 match compute_ref with
2366 None -> assert false
2367 | Some compute -> compute
2371 let scrolled_window1 =
2372 GBin.scrolled_window ~border_width:10
2373 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2375 TermViewer.sequent_viewer
2376 ~mml_of_cic_sequent:ChosenTransformer.mml_of_cic_sequent
2377 ~width:400 ~height:275 ~packing:(scrolled_window1#add) () in
2378 let _ = proofw_ref <- Some proofw in
2380 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2382 GButton.button ~label:"Ring"
2383 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2385 GButton.button ~label:"Fourier"
2386 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2388 GButton.button ~label:"Reflexivity"
2389 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2391 GButton.button ~label:"Symmetry"
2392 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2394 GButton.button ~label:"Assumption"
2395 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2396 let contradictionb =
2397 GButton.button ~label:"Contradiction"
2398 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2400 GButton.button ~label:"Auto"
2401 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2403 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2405 GButton.button ~label:"Exists"
2406 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2408 GButton.button ~label:"Split"
2409 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2411 GButton.button ~label:"Left"
2412 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2414 GButton.button ~label:"Right"
2415 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2416 let searchpatternb =
2417 GButton.button ~label:"SearchPattern_Apply"
2418 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2420 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2422 GButton.button ~label:"Exact"
2423 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2425 GButton.button ~label:"Intros"
2426 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2428 GButton.button ~label:"Apply"
2429 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2430 let elimintrossimplb =
2431 GButton.button ~label:"ElimIntrosSimpl"
2432 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2434 GButton.button ~label:"ElimType"
2435 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2437 GButton.button ~label:"Fold_whd"
2438 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2440 GButton.button ~label:"Fold_reduce"
2441 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2443 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2445 GButton.button ~label:"Fold_simpl"
2446 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2448 GButton.button ~label:"Cut"
2449 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2451 GButton.button ~label:"Change"
2452 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2454 GButton.button ~label:"Let ... In"
2455 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2457 GButton.button ~label:"RewriteSimpl ->"
2458 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2459 let rewritebacksimplb =
2460 GButton.button ~label:"RewriteSimpl <-"
2461 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2463 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2465 GButton.button ~label:"Absurd"
2466 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2468 GButton.button ~label:"Decompose"
2469 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2471 GButton.button ~label:"Transitivity"
2472 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2474 GButton.button ~label:"Replace"
2475 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2477 GButton.button ~label:"Injection"
2478 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2480 GButton.button ~label:"Discriminate"
2481 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2482 (* Zack: spostare in una toolbar
2484 GButton.button ~label:"Generalize"
2485 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2487 GButton.button ~label:"ClearBody"
2488 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2490 GButton.button ~label:"Clear"
2491 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2493 GButton.button ~label:"Whd"
2494 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2496 GButton.button ~label:"Reduce"
2497 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2499 GButton.button ~label:"Simpl"
2500 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2503 ignore(exactb#connect#clicked InvokeTactics'.exact) ;
2504 ignore(applyb#connect#clicked InvokeTactics'.apply) ;
2505 ignore(elimintrossimplb#connect#clicked InvokeTactics'.elimintrossimpl) ;
2506 ignore(elimtypeb#connect#clicked InvokeTactics'.elimtype) ;
2507 ignore(foldwhdb#connect#clicked InvokeTactics'.fold_whd) ;
2508 ignore(foldreduceb#connect#clicked InvokeTactics'.fold_reduce) ;
2509 ignore(foldsimplb#connect#clicked InvokeTactics'.fold_simpl) ;
2510 ignore(cutb#connect#clicked InvokeTactics'.cut) ;
2511 ignore(changeb#connect#clicked InvokeTactics'.change) ;
2512 ignore(letinb#connect#clicked InvokeTactics'.letin) ;
2513 ignore(ringb#connect#clicked InvokeTactics'.ring) ;
2514 ignore(fourierb#connect#clicked InvokeTactics'.fourier) ;
2515 ignore(rewritesimplb#connect#clicked InvokeTactics'.rewritesimpl) ;
2516 ignore(rewritebacksimplb#connect#clicked InvokeTactics'.rewritebacksimpl) ;
2517 ignore(replaceb#connect#clicked InvokeTactics'.replace) ;
2518 ignore(reflexivityb#connect#clicked InvokeTactics'.reflexivity) ;
2519 ignore(symmetryb#connect#clicked InvokeTactics'.symmetry) ;
2520 ignore(transitivityb#connect#clicked InvokeTactics'.transitivity) ;
2521 ignore(existsb#connect#clicked InvokeTactics'.exists) ;
2522 ignore(splitb#connect#clicked InvokeTactics'.split) ;
2523 ignore(leftb#connect#clicked InvokeTactics'.left) ;
2524 ignore(rightb#connect#clicked InvokeTactics'.right) ;
2525 ignore(assumptionb#connect#clicked InvokeTactics'.assumption) ;
2526 ignore(absurdb#connect#clicked InvokeTactics'.absurd) ;
2527 ignore(contradictionb#connect#clicked InvokeTactics'.contradiction) ;
2528 ignore(introsb#connect#clicked InvokeTactics'.intros) ;
2529 ignore(decomposeb#connect#clicked InvokeTactics'.decompose) ;
2530 ignore(searchpatternb#connect#clicked searchPattern) ;
2531 ignore(injectionb#connect#clicked InvokeTactics'.injection) ;
2532 ignore(discriminateb#connect#clicked InvokeTactics'.discriminate) ;
2533 ignore(autob#connect#clicked InvokeTactics'.auto) ;
2534 (* Zack: spostare in una toolbar
2535 ignore(whdb#connect#clicked whd) ;
2536 ignore(reduceb#connect#clicked reduce) ;
2537 ignore(simplb#connect#clicked simpl) ;
2538 ignore(clearbodyb#connect#clicked clearbody) ;
2539 ignore(clearb#connect#clicked clear) ;
2540 ignore(generalizeb#connect#clicked generalize) ;
2542 ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
2544 ((new GObj.event_ops proofw#as_widget)#connect#button_press
2545 (open_contextual_menu_for_selected_terms proofw)) ;
2551 let vbox1 = GPack.vbox () in
2552 let scrolled_window1 =
2553 GBin.scrolled_window ~border_width:10
2554 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2556 TermViewer.sequent_viewer
2557 ~mml_of_cic_sequent:ChosenTransformer.mml_of_cic_sequent
2558 ~width:400 ~height:275 ~packing:(scrolled_window1#add) () in
2560 method proofw = (assert false : TermViewer.sequent_viewer)
2561 method content = vbox1
2562 method compute = (assert false : unit)
2566 let empty_page = new empty_page;;
2570 val notebook = GPack.notebook ()
2572 val mutable skip_switch_page_event = false
2573 val mutable empty = true
2574 method notebook = notebook
2576 let new_page = new page () in
2578 pages := !pages @ [n,lazy (setgoal n),new_page] ;
2579 notebook#append_page
2580 ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
2581 new_page#content#coerce
2582 method remove_all_pages ~skip_switch_page_event:skip =
2584 notebook#remove_page 0 (* let's remove the empty page *)
2586 List.iter (function _ -> notebook#remove_page 0) !pages ;
2588 skip_switch_page_event <- skip
2589 method set_current_page ~may_skip_switch_page_event n =
2590 let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
2591 let new_page = notebook#page_num page#content#coerce in
2592 if may_skip_switch_page_event && new_page <> notebook#current_page then
2593 skip_switch_page_event <- true ;
2594 notebook#goto_page new_page
2595 method set_empty_page =
2598 notebook#append_page
2599 ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
2600 empty_page#content#coerce
2602 let (_,_,page) = List.nth !pages notebook#current_page in
2606 (notebook#connect#switch_page
2608 let skip = skip_switch_page_event in
2609 skip_switch_page_event <- false ;
2612 let (metano,setgoal,page) = List.nth !pages i in
2613 set_proof_engine_goal (Some metano) ;
2614 Lazy.force (page#compute) ;
2616 if notify_hbugs_on_goal_change then
2623 let dump_environment () =
2625 let oc = open_out (Helm_registry.get "gtoplevel.environment_file") in
2626 HelmLogger.log (`Msg (`T "Dumping environment ..."));
2627 CicEnvironment.dump_to_channel oc;
2628 HelmLogger.log (`Msg (`T "... done!")) ;
2632 (`Error (`T (Printf.sprintf "Dump failure, uncaught exception:%s"
2633 (Printexc.to_string exc))))
2635 let restore_environment () =
2637 let ic = open_in (Helm_registry.get "gtoplevel.environment_file") in
2638 HelmLogger.log (`Msg (`T "Restoring environment ... "));
2639 CicEnvironment.restore_from_channel ic;
2640 HelmLogger.log (`Msg (`T "... done!"));
2644 (`Error (`T (Printf.sprintf "Restore failure, uncaught exception:%s"
2645 (Printexc.to_string exc))))
2650 class rendering_window output (notebook : notebook) =
2651 let scratch_window = new scratch_window in
2654 ~title:"gTopLevel - Helm's Proof Assistant"
2655 ~border_width:0 ~allow_shrink:false () in
2656 let vbox_for_menu = GPack.vbox ~packing:window#add () in
2658 let handle_box = GBin.handle_box ~border_width:2
2659 ~packing:(vbox_for_menu#pack ~padding:0) () in
2660 let menubar = GMenu.menu_bar ~packing:handle_box#add () in
2661 let factory0 = new GMenu.factory menubar in
2662 let accel_group = factory0#accel_group in
2664 let file_menu = factory0#add_submenu "File" in
2665 let factory1 = new GMenu.factory file_menu ~accel_group in
2666 (* let export_to_postscript_menu_item = *)
2670 factory1#add_item "New Block of (Co)Inductive Definitions..."
2671 ~key:GdkKeysyms._B ~callback:new_inductive
2674 factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
2677 let reopen_menu_item =
2678 factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
2682 factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
2683 ignore (factory1#add_separator ()) ;
2685 (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
2686 ~callback:load_unfinished_proof) ;
2687 let save_menu_item =
2688 factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S
2689 ~callback:save_unfinished_proof
2691 ignore (factory1#add_separator ()) ;
2692 ignore (factory1#add_item "Clear Environment" ~callback:CicEnvironment.empty);
2693 ignore (factory1#add_item "Dump Environment" ~callback:dump_environment);
2695 (factory1#add_item "Restore Environment" ~callback:restore_environment);
2697 (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
2698 ignore (!save_set_sensitive false);
2699 ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
2700 ignore (!qed_set_sensitive false);
2701 ignore (factory1#add_separator ()) ;
2703 let export_to_postscript_menu_item =
2704 factory1#add_item "Export to PostScript..."
2705 ~callback:(export_to_postscript output) in
2707 ignore (factory1#add_separator ()) ;
2709 (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) (*;
2710 export_to_postscript_menu_item *)
2713 let edit_menu = factory0#add_submenu "Edit Current Proof" in
2714 let factory2 = new GMenu.factory edit_menu ~accel_group in
2715 let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
2716 let proveit_menu_item =
2717 factory2#add_item "Prove It" ~key:GdkKeysyms._I
2718 ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
2720 let focus_menu_item =
2721 factory2#add_item "Focus" ~key:GdkKeysyms._F
2722 ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
2725 focus_and_proveit_set_sensitive :=
2727 proveit_menu_item#misc#set_sensitive b ;
2728 focus_menu_item#misc#set_sensitive b
2730 let _ = !focus_and_proveit_set_sensitive false in
2731 (* edit term menu *)
2732 let edit_term_menu = factory0#add_submenu "Edit Term" in
2733 let factory5 = new GMenu.factory edit_term_menu ~accel_group in
2734 let check_menu_item =
2735 factory5#add_item "Check Term" ~key:GdkKeysyms._C
2736 ~callback:(check scratch_window) in
2737 let _ = check_menu_item#misc#set_sensitive false in
2739 let search_menu = factory0#add_submenu "Search" in
2740 let factory4 = new GMenu.factory search_menu ~accel_group in
2742 factory4#add_item "Locate..." ~key:GdkKeysyms._T
2744 let searchPattern_menu_item =
2745 factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
2746 ~callback:completeSearchPattern in
2747 let _ = searchPattern_menu_item#misc#set_sensitive false in
2748 let show_menu_item =
2749 factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
2751 let insert_query_item =
2752 factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._Y
2753 ~callback:insertQuery in
2755 let hbugs_menu = factory0#add_submenu "HBugs" in
2756 let factory6 = new GMenu.factory hbugs_menu ~accel_group in
2758 factory6#add_check_item
2759 ~active:false ~key:GdkKeysyms._F5 ~callback:Hbugs.toggle "HBugs enabled"
2762 factory6#add_item ~key:GdkKeysyms._Return ~callback:Hbugs.notify
2763 "(Re)Submit status!"
2765 let _ = factory6#add_separator () in
2767 factory6#add_item ~callback:Hbugs.start_web_services "Start Web Services"
2770 factory6#add_item ~callback:Hbugs.stop_web_services "Stop Web Services"
2773 let settings_menu = factory0#add_submenu "Settings" in
2774 let factory3 = new GMenu.factory settings_menu ~accel_group in
2776 factory3#add_item "Edit Aliases..." ~key:GdkKeysyms._A
2777 ~callback:edit_aliases in
2779 factory3#add_item "Clear Aliases" ~key:GdkKeysyms._K
2780 ~callback:clear_aliases in
2782 factory3#add_check_item "Auto disambiguation"
2783 ~callback:(fun checked -> auto_disambiguation := checked) in
2784 let _ = factory3#add_separator () in
2786 factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
2787 ~callback:(function _ -> (settings_window ())#show ()) in
2788 let _ = factory3#add_separator () in
2790 factory3#add_item "Reload Stylesheets"
2793 ChosenTransformer.reload_stylesheets () ;
2794 if ProofEngine.get_proof () <> None then
2796 refresh_goals notebook ;
2797 refresh_proof output
2799 InvokeTactics.RefreshSequentException e ->
2801 (`Error (`T ("An error occurred while refreshing the " ^
2802 "sequent: " ^ Printexc.to_string e))) ;
2803 (*notebook#remove_all_pages ~skip_switch_page_event:false ;*)
2804 notebook#set_empty_page
2805 | InvokeTactics.RefreshProofException e ->
2807 (`Error (`T ("An error occurred while refreshing the proof: " ^ Printexc.to_string e))) ;
2811 let _ = window#add_accel_group accel_group in
2815 ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
2817 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2818 let scrolled_window0 =
2819 GBin.scrolled_window ~border_width:10
2820 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2821 let _ = scrolled_window0#add output#coerce in
2823 GBin.frame ~label:"Insert Term"
2824 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2825 let scrolled_window1 =
2826 GBin.scrolled_window ~border_width:5
2827 ~packing:frame#add () in
2829 TermEditor'.term_editor
2831 ~width:400 ~height:100 ~packing:scrolled_window1#add ()
2832 ~isnotempty_callback:
2834 check_menu_item#misc#set_sensitive b ;
2835 searchPattern_menu_item#misc#set_sensitive b) in
2837 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2839 vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
2841 GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
2844 new HelmGtkLogger.html_logger
2845 ~width:400 ~height: 100 ~show:true ~packing:frame#add ()
2848 method inputt = inputt
2849 method output = (output : TermViewer.proof_viewer)
2850 method scratch_window = scratch_window
2851 method notebook = notebook
2852 method show = window#show
2853 method set_auto_disambiguation set = autoitem#set_active set
2855 notebook#set_empty_page ;
2856 (*export_to_postscript_menu_item#misc#set_sensitive false ;*)
2857 check_term := (check_term_in_scratch scratch_window) ;
2859 (* signal handlers here *)
2860 ignore(output#connect#selection_changed
2862 choose_selection output elem ;
2863 !focus_and_proveit_set_sensitive true
2865 ignore (output#connect#click (show_in_show_window_callback output)) ;
2866 let settings_window = new settings_window output scrolled_window0
2867 (*export_to_postscript_menu_item*)() (choose_selection output) in
2868 set_settings_window settings_window ;
2869 ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true ))
2874 let initialize_everything () =
2875 prerr_endline "STO PER CREARE LA PROOF WINDOW" ;
2877 TermViewer.proof_viewer
2878 ~mml_of_cic_object:ChosenTransformer.mml_of_cic_object
2879 ~width:350 ~height:280 ()
2881 prerr_endline "CREATA" ;
2882 let notebook = new notebook in
2883 let rendering_window' = new rendering_window output notebook in
2884 prerr_endline "OK" ;
2885 rendering_window'#set_auto_disambiguation !auto_disambiguation;
2886 set_rendering_window rendering_window';
2887 let print_error_as_html prefix msg =
2888 HelmLogger.log (`Error (`T (prefix ^ msg)))
2890 Gdome_xslt.setErrorCallback (Some (print_error_as_html "XSLT Error: "));
2891 Gdome_xslt.setDebugCallback
2892 (Some (print_error_as_html "XSLT Debug Message: "));
2893 rendering_window'#show () ;
2894 if restore_environment_on_boot &&
2895 Sys.file_exists (Helm_registry.get "gtoplevel.environment_file")
2897 restore_environment ();
2902 prerr_endline "CIAO" ;
2903 ignore (GtkMain.Main.init ()) ;
2904 initialize_everything () ;
2905 MQIC.close mqi_handle;
2910 Sys.catch_break true;
2912 with Sys.Break -> () (* exit nicely, invoking at_exit functions *)