1 (* Copyright (C) 2000-2003, 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://cs.unibo.it/helm/.
26 (******************************************************************************)
30 (* Claudio Sacerdoti Coen <sacerdot@cs.unibo.it> *)
34 (******************************************************************************)
40 module MQI = MQueryInterpreter
42 module MQGT = MQGTypes
44 module MQG = MQueryGenerator
46 (* GLOBAL CONSTANTS *)
48 let mqi_flags = [MQIC.Postgres ; MQIC.Stat ; MQIC.Warn ; MQIC.Log] (* default MathQL interpreter options *)
50 let mqi_flags = [] (* default MathQL interpreter options *)
52 let mqi_handle = MQIC.init mqi_flags prerr_string
54 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
58 Sys.getenv "GTOPLEVEL_PROOFFILE"
60 Not_found -> "/public/currentproof"
65 Sys.getenv "GTOPLEVEL_PROOFFILETYPE"
67 Not_found -> "/public/currentprooftype"
72 Sys.getenv "GTOPLEVEL_ENVIRONMENTFILE"
74 Not_found -> "/public/environment"
77 let restore_environment_on_boot = true ;;
78 let notify_hbugs_on_goal_change = false ;;
80 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
82 let check_term = ref (fun _ _ _ -> assert false);;
84 exception RenderingWindowsNotInitialized;;
86 let set_rendering_window,rendering_window =
87 let rendering_window_ref = ref None in
88 (function rw -> rendering_window_ref := Some rw),
90 match !rendering_window_ref with
91 None -> raise RenderingWindowsNotInitialized
96 exception SettingsWindowsNotInitialized;;
98 let set_settings_window,settings_window =
99 let settings_window_ref = ref None in
100 (function rw -> settings_window_ref := Some rw),
102 match !settings_window_ref with
103 None -> raise SettingsWindowsNotInitialized
108 exception OutputHtmlNotInitialized;;
110 let set_outputhtml,outputhtml =
111 let outputhtml_ref = ref None in
112 (function (rw: Ui_logger.html_logger) -> outputhtml_ref := Some rw),
114 match !outputhtml_ref with
115 | None -> raise OutputHtmlNotInitialized
116 | Some outputhtml -> (outputhtml: Ui_logger.html_logger)
120 exception QedSetSensitiveNotInitialized;;
121 let qed_set_sensitive =
122 ref (function _ -> raise QedSetSensitiveNotInitialized)
125 exception SaveSetSensitiveNotInitialized;;
126 let save_set_sensitive =
127 ref (function _ -> raise SaveSetSensitiveNotInitialized)
130 (* COMMAND LINE OPTIONS *)
136 "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
139 Arg.parse argspec ignore ""
143 let term_of_cic_textual_parser_uri uri =
144 let module C = Cic in
145 let module CTP = CicTextualParser0 in
147 CTP.ConUri uri -> C.Const (uri,[])
148 | CTP.VarUri uri -> C.Var (uri,[])
149 | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
150 | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
153 let string_of_cic_textual_parser_uri uri =
154 let module C = Cic in
155 let module CTP = CicTextualParser0 in
158 CTP.ConUri uri -> UriManager.string_of_uri uri
159 | CTP.VarUri uri -> UriManager.string_of_uri uri
160 | CTP.IndTyUri (uri,tyno) ->
161 UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
162 | CTP.IndConUri (uri,tyno,consno) ->
163 UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
166 (* 4 = String.length "cic:" *)
167 String.sub uri' 4 (String.length uri' - 4)
170 let output_html ?(append_NL = true) (outputhtml: Ui_logger.html_logger) =
171 outputhtml#log ~append_NL
173 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
177 let check_window (outputhtml: Ui_logger.html_logger) uris =
180 ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
182 GPack.notebook ~scrollable:true ~packing:window#add () in
187 let scrolled_window =
188 GBin.scrolled_window ~border_width:10
190 (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
195 TermViewer.sequent_viewer
196 ~packing:scrolled_window#add ~width:400 ~height:280 () in
199 term_of_cic_textual_parser_uri
200 (MQueryMisc.cic_textual_parser_uri_of_string uri)
202 (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
205 mmlwidget#load_sequent [] (111,[],expr)
208 output_html outputhtml (`Error (`T (Printexc.to_string e)))
213 (notebook#connect#switch_page
215 Lazy.force (List.nth render_terms i)))
221 interactive_user_uri_choice ~(selection_mode:[`MULTIPLE|`SINGLE]) ?(ok="Ok")
222 ?(enable_button_for_non_vars=false) ~title ~msg uris
224 let choices = ref [] in
225 let chosen = ref false in
226 let use_only_constants = ref false in
228 GWindow.dialog ~modal:true ~title ~width:600 () in
230 GMisc.label ~text:msg
231 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
232 let scrolled_window =
233 GBin.scrolled_window ~border_width:10
234 ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
236 let expected_height = 18 * List.length uris in
237 let height = if expected_height > 400 then 400 else expected_height in
238 GList.clist ~columns:1 ~packing:scrolled_window#add
239 ~height ~selection_mode:(selection_mode :> Gtk.Tags.selection_mode) () in
240 let _ = List.map (function x -> clist#append [x]) uris in
242 GPack.hbox ~border_width:0
243 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
245 GMisc.label ~text:"None of the above. Try this one:"
246 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
248 GEdit.entry ~editable:true
249 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
251 GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
253 GButton.button ~label:ok
254 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
255 let _ = okb#misc#set_sensitive false in
260 if enable_button_for_non_vars then
261 hbox#pack ~expand:false ~fill:false ~padding:5 w)
262 ~label:"Try constants only" () in
264 GButton.button ~label:"Check"
265 ~packing:(hbox#pack ~padding:5) () in
266 let _ = checkb#misc#set_sensitive false in
268 GButton.button ~label:"Abort"
269 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
271 let check_callback () =
272 assert (List.length !choices > 0) ;
273 check_window (outputhtml ()) !choices
275 ignore (window#connect#destroy GMain.Main.quit) ;
276 ignore (cancelb#connect#clicked window#destroy) ;
278 (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
280 (nonvarsb#connect#clicked
282 use_only_constants := true ;
286 ignore (checkb#connect#clicked check_callback) ;
288 (clist#connect#select_row
289 (fun ~row ~column ~event ->
290 checkb#misc#set_sensitive true ;
291 okb#misc#set_sensitive true ;
292 choices := (List.nth uris row)::!choices)) ;
294 (clist#connect#unselect_row
295 (fun ~row ~column ~event ->
297 List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
299 (manual_input#connect#changed
301 if manual_input#text = "" then
304 checkb#misc#set_sensitive false ;
305 okb#misc#set_sensitive false ;
306 clist#misc#set_sensitive true
310 choices := [manual_input#text] ;
311 clist#unselect_all () ;
312 checkb#misc#set_sensitive true ;
313 okb#misc#set_sensitive true ;
314 clist#misc#set_sensitive false
316 window#set_position `CENTER ;
320 if !use_only_constants then
322 (function uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
325 if List.length !choices > 0 then !choices else raise NoChoice
330 let interactive_interpretation_choice interpretations =
331 let chosen = ref None in
334 ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
335 let vbox = GPack.vbox ~packing:window#add () in
339 ("Ambiguous input since there are many well-typed interpretations." ^
340 " Please, choose one of them.")
341 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
343 GPack.notebook ~scrollable:true
344 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
347 (function interpretation ->
349 let expected_height = 18 * List.length interpretation in
350 let height = if expected_height > 400 then 400 else expected_height in
351 GList.clist ~columns:2 ~packing:notebook#append_page ~height
352 ~titles:["id" ; "URI"] ()
356 (function (id,uri) ->
357 let n = clist#append [id;uri] in
358 clist#set_row ~selectable:false n
361 clist#columns_autosize ()
364 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
366 GButton.button ~label:"Ok"
367 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
369 GButton.button ~label:"Abort"
370 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
372 ignore (window#connect#destroy GMain.Main.quit) ;
373 ignore (cancelb#connect#clicked window#destroy) ;
376 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
377 window#set_position `CENTER ;
381 None -> raise NoChoice
389 save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
392 let struri = UriManager.string_of_uri uri in
393 let idx = (String.rindex struri '/') + 1 in
394 String.sub struri idx (String.length struri - idx)
396 let path = pathname ^ "/" ^ name in
398 Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
402 Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
403 ~ask_dtd_to_the_getter:false
406 let innertypesuri = UriManager.innertypesuri_of_uri uri in
407 Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
408 Getter.register innertypesuri
409 (Configuration.annotations_url ^
410 Str.replace_first (Str.regexp "^cic:") ""
411 (UriManager.string_of_uri innertypesuri) ^ ".xml"
413 (* constant type / variable / mutual inductive types definition *)
414 Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
416 (Configuration.annotations_url ^
417 Str.replace_first (Str.regexp "^cic:") ""
418 (UriManager.string_of_uri uri) ^ ".xml"
425 match UriManager.bodyuri_of_uri uri with
427 | Some bodyuri -> bodyuri
429 Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
430 Getter.register bodyuri
431 (Configuration.annotations_url ^
432 Str.replace_first (Str.regexp "^cic:") ""
433 (UriManager.string_of_uri bodyuri) ^ ".xml"
440 exception OpenConjecturesStillThere;;
441 exception WrongProof;;
443 let pathname_of_annuri uristring =
444 Configuration.annotations_dir ^
445 Str.replace_first (Str.regexp "^cic:") "" uristring
448 let make_dirs dirpath =
449 ignore (Unix.system ("mkdir -p " ^ dirpath))
452 let save_obj uri obj =
454 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
455 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
457 Cic2acic.acic_object_of_cic_object obj
459 (* let's save the theorem and register it to the getter *)
460 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
462 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
467 match ProofEngine.get_proof () with
469 | Some (uri,[],bo,ty) ->
471 CicReduction.are_convertible []
472 (CicTypeChecker.type_of_aux' [] [] bo) ty
475 (*CSC: Wrong: [] is just plainly wrong *)
476 let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
477 let (acic,ids_to_inner_types,ids_to_inner_sorts) =
478 (rendering_window ())#output#load_proof uri proof
480 !qed_set_sensitive false ;
481 (* let's save the theorem and register it to the getter *)
482 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
484 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
489 | _ -> raise OpenConjecturesStillThere
492 (** save an unfinished proof on the filesystem *)
493 let save_unfinished_proof () =
494 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
495 let (xml, bodyxml) = ProofEngine.get_current_status_as_xml () in
496 Xml.pp ~quiet:true xml (Some prooffiletype) ;
497 output_html outputhtml
498 (`Msg (`T ("Current proof type saved to " ^ prooffiletype))) ;
499 Xml.pp ~quiet:true bodyxml (Some prooffile) ;
500 output_html outputhtml
501 (`Msg (`T ("Current proof body saved to " ^ prooffile)))
504 (* Used to typecheck the loaded proofs *)
505 let typecheck_loaded_proof metasenv bo ty =
506 let module T = CicTypeChecker in
509 (fun metasenv ((_,context,ty) as conj) ->
510 ignore (T.type_of_aux' metasenv context ty) ;
513 ignore (T.type_of_aux' metasenv [] ty) ;
514 ignore (T.type_of_aux' metasenv [] bo)
517 let decompose_uris_choice_callback uris =
518 (* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
519 let module U = UriManager in
522 match MQueryMisc.cic_textual_parser_uri_of_string uri with
523 CicTextualParser0.IndTyUri (uri,typeno) -> (uri,typeno,[])
525 (interactive_user_uri_choice
526 ~selection_mode:`MULTIPLE ~ok:"Ok" ~enable_button_for_non_vars:false
527 ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose"
529 (function (uri,typeno,_) ->
530 U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1)
535 let mk_fresh_name_callback context name ~typ =
537 match ProofEngineHelpers.mk_fresh_name context name ~typ with
538 Cic.Name fresh_name -> fresh_name
539 | Cic.Anonymous -> assert false
542 GToolbox.input_string ~title:"Enter a fresh hypothesis name" ~text:fresh_name
543 ("Enter a fresh name for the hypothesis " ^
545 (List.map (function None -> None | Some (n,_) -> Some n) context))
547 Some fresh_name' -> Cic.Name fresh_name'
548 | None -> raise NoChoice
551 let refresh_proof (output : TermViewer.proof_viewer) =
553 let uri,currentproof =
554 match ProofEngine.get_proof () with
556 | Some (uri,metasenv,bo,ty) ->
557 ProofEngine.set_proof (Some (uri,metasenv,bo,ty)) ;
558 if List.length metasenv = 0 then
560 !qed_set_sensitive true ;
565 (*CSC: Wrong: [] is just plainly wrong *)
567 (Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
569 ignore (output#load_proof uri currentproof)
572 match ProofEngine.get_proof () with
574 | Some (uri,metasenv,bo,ty) ->
575 prerr_endline ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[]))) ; flush stderr ;
576 raise (InvokeTactics.RefreshProofException e)
578 let set_proof_engine_goal g =
579 ProofEngine.goal := g
582 let refresh_goals ?(empty_notebook=true) notebook =
584 match !ProofEngine.goal with
586 if empty_notebook then
588 notebook#remove_all_pages ~skip_switch_page_event:false ;
589 notebook#set_empty_page
592 notebook#proofw#unload
595 match ProofEngine.get_proof () with
597 | Some (_,metasenv,_,_) -> metasenv
600 List.find (function (m,_,_) -> m=metano) metasenv
602 let regenerate_notebook () =
603 let skip_switch_page_event =
605 (m,_,_)::_ when m = metano -> false
608 notebook#remove_all_pages ~skip_switch_page_event ;
609 List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
611 if empty_notebook then
613 regenerate_notebook () ;
614 notebook#set_current_page
615 ~may_skip_switch_page_event:false metano
619 notebook#set_current_page
620 ~may_skip_switch_page_event:true metano ;
621 notebook#proofw#load_sequent metasenv currentsequent
626 match !ProofEngine.goal with
631 match ProofEngine.get_proof () with
633 | Some (_,metasenv,_,_) -> metasenv
636 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
637 prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
638 raise (InvokeTactics.RefreshSequentException e)
639 with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unknown."); raise (InvokeTactics.RefreshSequentException e)
641 module InvokeTacticsCallbacks =
643 let sequent_viewer () = (rendering_window ())#notebook#proofw
644 let term_editor () = (rendering_window ())#inputt
645 let scratch_window () = (rendering_window ())#scratch_window
647 let refresh_proof () =
648 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
651 let refresh_goals () =
652 let notebook = (rendering_window ())#notebook in
653 refresh_goals notebook
655 let decompose_uris_choice_callback = decompose_uris_choice_callback
656 let mk_fresh_name_callback = mk_fresh_name_callback
657 let output_html msg = output_html (outputhtml ()) msg
660 module InvokeTactics' = InvokeTactics.Make (InvokeTacticsCallbacks);;
662 (* Just to initialize the Hbugs module *)
663 module Ignore = Hbugs.Initialize (InvokeTactics');;
664 Hbugs.set_describe_hint_callback (fun hint ->
666 | Hbugs_types.Use_apply_Luke term ->
667 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
668 check_window outputhtml [term]
672 let dummy_uri = "/dummy.con"
674 (** load an unfinished proof from filesystem *)
675 let load_unfinished_proof () =
676 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
677 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
678 let notebook = (rendering_window ())#notebook in
681 GToolbox.input_string ~title:"Load Unfinished Proof" ~text:dummy_uri
684 None -> raise NoChoice
686 let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
687 match CicParser.obj_of_xml prooffiletype (Some prooffile) with
688 Cic.CurrentProof (_,metasenv,bo,ty,_) ->
689 typecheck_loaded_proof metasenv bo ty ;
690 ProofEngine.set_proof (Some (uri, metasenv, bo, ty)) ;
691 refresh_proof output ;
692 set_proof_engine_goal
695 | (metano,_,_)::_ -> Some metano
697 refresh_goals notebook ;
698 output_html outputhtml
699 (`Msg (`T ("Current proof type loaded from " ^
701 output_html outputhtml
702 (`Msg (`T ("Current proof body loaded from " ^
704 !save_set_sensitive true;
707 InvokeTactics.RefreshSequentException e ->
708 output_html outputhtml
709 (`Error (`T ("Exception raised during the refresh of the " ^
710 "sequent: " ^ Printexc.to_string e)))
711 | InvokeTactics.RefreshProofException e ->
712 output_html outputhtml
713 (`Error (`T ("Exception raised during the refresh of the " ^
714 "proof: " ^ Printexc.to_string e)))
716 output_html outputhtml
717 (`Error (`T (Printexc.to_string e)))
720 let edit_aliases () =
721 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
722 let id_to_uris = inputt#id_to_uris in
723 let chosen = ref false in
726 ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
728 GPack.vbox ~border_width:0 ~packing:window#add () in
729 let scrolled_window =
730 GBin.scrolled_window ~border_width:10
731 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
732 let input = GText.view ~editable:true ~width:400 ~height:100
733 ~packing:scrolled_window#add () in
735 GPack.hbox ~border_width:0
736 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
738 GButton.button ~label:"Ok"
739 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
741 GButton.button ~label:"Cancel"
742 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
743 ignore (window#connect#destroy GMain.Main.quit) ;
744 ignore (cancelb#connect#clicked window#destroy) ;
746 (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
747 let dom,resolve_id = !id_to_uris in
749 (input#buffer#insert ~iter:(input#buffer#get_iter_at_char 0)
754 match resolve_id v with
756 | Some (CicTextualParser0.Uri uri) -> uri
757 | Some (CicTextualParser0.Term _)
758 | Some CicTextualParser0.Implicit -> assert false
762 CicTextualParser0.Id id -> id
763 | CicTextualParser0.Symbol (descr,_) ->
764 (* CSC: To be implemented *)
766 )^ " " ^ (string_of_cic_textual_parser_uri uri)
772 let inputtext = input#buffer#get_text () in
774 let alfa = "[a-zA-Z_-]" in
775 let digit = "[0-9]" in
776 let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
777 let blanks = "\( \|\t\|\n\)+" in
778 let nonblanks = "[^ \t\n]+" in
779 let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
781 ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
785 let n' = Str.search_forward regexpr inputtext n in
786 let id = CicTextualParser0.Id (Str.matched_group 2 inputtext) in
788 MQueryMisc.cic_textual_parser_uri_of_string
789 ("cic:" ^ (Str.matched_group 5 inputtext))
791 let dom,resolve_id = aux (n' + 1) in
792 if List.mem id dom then
798 Some (CicTextualParser0.Uri uri)
801 Not_found -> TermEditor.empty_id_to_uris
805 id_to_uris := (dom,resolve_id)
809 let module L = LogicalOperations in
810 let module G = Gdome in
811 let notebook = (rendering_window ())#notebook in
812 let output = (rendering_window ())#output in
813 let outputhtml = ((rendering_window ())#outputhtml (*: GHtml.xmhtml*)) in
815 output#make_sequent_of_selected_term ;
816 refresh_proof output ;
817 refresh_goals notebook
819 InvokeTactics.RefreshSequentException e ->
820 output_html outputhtml
821 (`Error (`T ("Exception raised during the refresh of the " ^
822 "sequent: " ^ Printexc.to_string e)))
823 | InvokeTactics.RefreshProofException e ->
824 output_html outputhtml
825 (`Error (`T ("Exception raised during the refresh of the " ^
826 "proof: " ^ Printexc.to_string e)))
828 output_html outputhtml
829 (`Error (`T (Printexc.to_string e)))
833 let module L = LogicalOperations in
834 let module G = Gdome in
835 let notebook = (rendering_window ())#notebook in
836 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
837 let output = (rendering_window ())#output in
839 output#focus_sequent_of_selected_term ;
840 refresh_goals notebook
842 InvokeTactics.RefreshSequentException e ->
843 output_html outputhtml
844 (`Error (`T ("Exception raised during the refresh of the " ^
845 "sequent: " ^ Printexc.to_string e)))
846 | InvokeTactics.RefreshProofException e ->
847 output_html outputhtml
848 (`Error (`T ("Exception raised during the refresh of the " ^
849 "proof: " ^ Printexc.to_string e)))
851 output_html outputhtml
852 (`Error (`T (Printexc.to_string e)))
855 exception NoPrevGoal;;
856 exception NoNextGoal;;
859 let module L = LogicalOperations in
860 let module G = Gdome in
861 let notebook = (rendering_window ())#notebook in
862 let output = (rendering_window ())#output in
863 let outputhtml = (rendering_window ())#outputhtml in
865 match ProofEngine.get_proof () with
867 | Some (_,metasenv,_,_) -> metasenv
870 refresh_goals ~empty_notebook:false notebook
872 InvokeTactics.RefreshSequentException e ->
873 output_html outputhtml
874 (`Error (`T ("Exception raised during the refresh of the " ^
875 "sequent: " ^ Printexc.to_string e)))
877 output_html outputhtml
878 (`Error (`T (Printexc.to_string e)))
882 show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
885 GWindow.window ~width:800 ~border_width:2 () in
886 let scrolled_window =
887 GBin.scrolled_window ~border_width:10 ~packing:window#add () in
889 GMathViewAux.single_selection_math_view
890 ~packing:scrolled_window#add ~width:600 ~height:400 ()
892 let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
893 let href = Gdome.domString "href" in
894 let show_in_show_window_obj uri obj =
895 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
898 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
899 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
901 Cic2acic.acic_object_of_cic_object obj
904 ApplyStylesheets.mml_of_cic_object
905 ~explode_all:false uri acic ids_to_inner_sorts ids_to_inner_types
907 window#set_title (UriManager.string_of_uri uri) ;
908 window#misc#hide () ; window#show () ;
909 mmlwidget#load_doc mml ;
912 output_html outputhtml
913 (`Error (`T (Printexc.to_string e)))
915 let show_in_show_window_uri uri =
916 let obj = CicEnvironment.get_obj uri in
917 show_in_show_window_obj uri obj
919 let show_in_show_window_callback mmlwidget (n : Gdome.element option) _ =
923 if n'#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
925 (n'#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
927 show_in_show_window_uri (UriManager.uri_of_string uri)
929 ignore (mmlwidget#action_toggle n')
932 mmlwidget#connect#click (show_in_show_window_callback mmlwidget)
934 show_in_show_window_obj, show_in_show_window_uri,
935 show_in_show_window_callback
938 exception NoObjectsLocated;;
940 let user_uri_choice ~title ~msg uris =
943 [] -> raise NoObjectsLocated
947 interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
952 String.sub uri 4 (String.length uri - 4)
955 let locate_callback id =
956 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
957 let out = output_html outputhtml in
958 let query = MQG.locate id in
959 let result = MQI.execute mqi_handle query in
963 MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format' uri)
965 out (`Msg (`T "Locate Query:")) ;
966 MQueryUtil.text_of_query (fun m -> out (`Msg (`T m))) "" query;
967 out (`Msg (`T "Result:")) ;
968 MQueryUtil.text_of_result (fun m -> out (`Msg (`T m))) "" result;
969 user_uri_choice ~title:"Ambiguous input."
971 ("Ambiguous input \"" ^ id ^
972 "\". Please, choose one interpetation:")
977 let input_or_locate_uri ~title =
978 let uri = ref None in
981 ~width:400 ~modal:true ~title ~border_width:2 () in
982 let vbox = GPack.vbox ~packing:window#add () in
984 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
986 GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
988 GEdit.entry ~editable:true
989 ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
991 GButton.button ~label:"Check"
992 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
993 let _ = checkb#misc#set_sensitive false in
995 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
997 GMisc.label ~text:"You can also enter an indentifier to locate:"
998 ~packing:(hbox2#pack ~padding:5) () in
1000 GEdit.entry ~editable:true
1001 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1003 GButton.button ~label:"Locate"
1004 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1005 let _ = locateb#misc#set_sensitive false in
1007 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1009 GButton.button ~label:"Ok"
1010 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
1011 let _ = okb#misc#set_sensitive false in
1013 GButton.button ~label:"Cancel"
1014 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
1016 ignore (window#connect#destroy GMain.Main.quit) ;
1018 (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
1019 let check_callback () =
1020 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1021 let uri = "cic:" ^ manual_input#text in
1023 ignore (Getter.resolve (UriManager.uri_of_string uri)) ;
1024 output_html outputhtml (`Msg (`T "OK")) ;
1027 Getter.Unresolved ->
1028 output_html outputhtml
1029 (`Error (`T ("URI " ^ uri ^
1030 " does not correspond to any object."))) ;
1032 | UriManager.IllFormedUri _ ->
1033 output_html outputhtml
1034 (`Error (`T ("URI " ^ uri ^ " is not well-formed."))) ;
1037 output_html outputhtml
1038 (`Error (`T (Printexc.to_string e))) ;
1042 (okb#connect#clicked
1044 if check_callback () then
1046 uri := Some manual_input#text ;
1050 ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1052 (manual_input#connect#changed
1054 if manual_input#text = "" then
1056 checkb#misc#set_sensitive false ;
1057 okb#misc#set_sensitive false
1061 checkb#misc#set_sensitive true ;
1062 okb#misc#set_sensitive true
1065 (locate_input#connect#changed
1066 (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1068 (locateb#connect#clicked
1070 let id = locate_input#text in
1071 manual_input#set_text (locate_callback id) ;
1072 locate_input#delete_text 0 (String.length id)
1077 None -> raise NoChoice
1078 | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1081 exception AmbiguousInput;;
1083 (* A WIDGET TO ENTER CIC TERMS *)
1085 module ChosenTermEditor = TexTermEditor;;
1086 module ChosenTextualParser0 = TexCicTextualParser0;;
1088 module ChosenTermEditor = TermEditor;;
1089 module ChosenTextualParser0 = CicTextualParser0;;
1094 let get_metasenv () = !ChosenTextualParser0.metasenv
1095 let set_metasenv metasenv = ChosenTextualParser0.metasenv := metasenv
1097 let output_html ?append_NL = output_html ?append_NL (outputhtml ())
1098 let interactive_user_uri_choice =
1099 fun ~selection_mode ?ok ?enable_button_for_non_vars ~title ~msg ~id ->
1100 interactive_user_uri_choice ~selection_mode ?ok
1101 ?enable_button_for_non_vars ~title ~msg
1102 let interactive_interpretation_choice = interactive_interpretation_choice
1103 let input_or_locate_uri = input_or_locate_uri
1107 module TexTermEditor' = ChosenTermEditor.Make(Callbacks);;
1109 (* OTHER FUNCTIONS *)
1112 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1113 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1116 GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1118 None -> raise NoChoice
1120 let uri = locate_callback input in
1124 output_html outputhtml
1125 (`Error (`T (Printexc.to_string e)))
1129 exception UriAlreadyInUse;;
1130 exception NotAUriToAConstant;;
1132 let new_inductive () =
1133 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1134 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1135 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1136 let notebook = (rendering_window ())#notebook in
1138 let chosen = ref false in
1139 let inductive = ref true in
1140 let paramsno = ref 0 in
1141 let get_uri = ref (function _ -> assert false) in
1142 let get_base_uri = ref (function _ -> assert false) in
1143 let get_names = ref (function _ -> assert false) in
1144 let get_types_and_cons = ref (function _ -> assert false) in
1145 let get_context_and_subst = ref (function _ -> assert false) in
1148 ~width:600 ~modal:true ~position:`CENTER
1149 ~title:"New Block of Mutual (Co)Inductive Definitions"
1150 ~border_width:2 () in
1151 let vbox = GPack.vbox ~packing:window#add () in
1153 GPack.hbox ~border_width:0
1154 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1156 GMisc.label ~text:"Enter the URI for the new block:"
1157 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1159 GEdit.entry ~editable:true
1160 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1162 GPack.hbox ~border_width:0
1163 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1167 "Enter the number of left parameters in every arity and constructor type:"
1168 ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1169 let paramsno_entry =
1170 GEdit.entry ~editable:true ~text:"0"
1171 ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1173 GPack.hbox ~border_width:0
1174 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1176 GMisc.label ~text:"Are the definitions inductive or coinductive?"
1177 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1179 GButton.radio_button ~label:"Inductive"
1180 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1182 GButton.radio_button ~label:"Coinductive"
1183 ~group:inductiveb#group
1184 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1186 GPack.hbox ~border_width:0
1187 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1189 GMisc.label ~text:"Enter the list of the names of the types:"
1190 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1192 GEdit.entry ~editable:true
1193 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1195 GPack.hbox ~border_width:0
1196 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1198 GButton.button ~label:"> Next"
1199 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1200 let _ = okb#misc#set_sensitive true in
1202 GButton.button ~label:"Abort"
1203 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1204 ignore (window#connect#destroy GMain.Main.quit) ;
1205 ignore (cancelb#connect#clicked window#destroy) ;
1209 (okb#connect#clicked
1212 let uristr = "cic:" ^ uri_entry#text in
1213 let namesstr = names_entry#text in
1214 let paramsno' = int_of_string (paramsno_entry#text) in
1215 match Str.split (Str.regexp " +") namesstr with
1217 | (he::tl) as names ->
1218 let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1221 ignore (Getter.resolve uri) ;
1222 raise UriAlreadyInUse
1224 Getter.Unresolved ->
1225 get_uri := (function () -> uri) ;
1226 get_names := (function () -> names) ;
1227 inductive := inductiveb#active ;
1228 paramsno := paramsno' ;
1233 output_html outputhtml
1234 (`Error (`T (Printexc.to_string e)))
1242 GBin.frame ~label:name
1243 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1244 let vbox = GPack.vbox ~packing:frame#add () in
1245 let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1247 GMisc.label ~text:("Enter its type:")
1248 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1249 let scrolled_window =
1250 GBin.scrolled_window ~border_width:5
1251 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1253 TexTermEditor'.term_editor
1255 ~width:400 ~height:20 ~packing:scrolled_window#add
1256 ~share_id_to_uris_with:inputt ()
1257 ~isnotempty_callback:
1259 (*non_empty_type := b ;*)
1260 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1263 GPack.hbox ~border_width:0
1264 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1266 GMisc.label ~text:("Enter the list of its constructors:")
1267 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1268 let cons_names_entry =
1269 GEdit.entry ~editable:true
1270 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1271 (newinputt,cons_names_entry)
1274 vbox#remove hboxn#coerce ;
1276 GPack.hbox ~border_width:0
1277 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1279 GButton.button ~label:"> Next"
1280 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1282 GButton.button ~label:"Abort"
1283 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1284 ignore (cancelb#connect#clicked window#destroy) ;
1286 (okb#connect#clicked
1289 let names = !get_names () in
1290 let types_and_cons =
1292 (fun name (newinputt,cons_names_entry) ->
1293 let consnamesstr = cons_names_entry#text in
1294 let cons_names = Str.split (Str.regexp " +") consnamesstr in
1296 newinputt#get_metasenv_and_term ~context:[] ~metasenv:[]
1299 [] -> expr,cons_names
1300 | _ -> raise AmbiguousInput
1301 ) names type_widgets
1303 let uri = !get_uri () in
1305 (* Let's see if so far the definition is well-typed *)
1308 (* To test if the arities of the inductive types are well *)
1309 (* typed, we check the inductive block definition where *)
1310 (* no constructor is given to each type. *)
1313 (fun name (ty,cons) -> (name, !inductive, ty, []))
1314 names types_and_cons
1316 CicTypeChecker.typecheck_mutual_inductive_defs uri
1317 (tys,params,paramsno)
1319 get_context_and_subst :=
1323 (fun (context,subst) name (ty,_) ->
1325 (Some (Cic.Name name, Cic.Decl ty))::context,
1326 (Cic.MutInd (uri,!i,[]))::subst
1329 ) ([],[]) names types_and_cons) ;
1330 let types_and_cons' =
1332 (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1333 names types_and_cons
1335 get_types_and_cons := (function () -> types_and_cons') ;
1340 output_html outputhtml
1341 (`Error (`T (Printexc.to_string e)))
1344 and phase3 name cons =
1345 let get_cons_types = ref (function () -> assert false) in
1348 ~width:600 ~modal:true ~position:`CENTER
1349 ~title:(name ^ " Constructors")
1350 ~border_width:2 () in
1351 let vbox = GPack.vbox ~packing:window2#add () in
1352 let cons_type_widgets =
1354 (function consname ->
1356 GPack.hbox ~border_width:0
1357 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1359 GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1360 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1361 let scrolled_window =
1362 GBin.scrolled_window ~border_width:5
1363 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1365 TexTermEditor'.term_editor
1367 ~width:400 ~height:20 ~packing:scrolled_window#add
1368 ~share_id_to_uris_with:inputt ()
1369 ~isnotempty_callback:
1371 (* (*non_empty_type := b ;*)
1372 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1377 GPack.hbox ~border_width:0
1378 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1380 GButton.button ~label:"> Next"
1381 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1382 let _ = okb#misc#set_sensitive true in
1384 GButton.button ~label:"Abort"
1385 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1386 ignore (window2#connect#destroy GMain.Main.quit) ;
1387 ignore (cancelb#connect#clicked window2#destroy) ;
1389 (okb#connect#clicked
1393 let context,subst= !get_context_and_subst () in
1398 inputt#get_metasenv_and_term ~context ~metasenv:[]
1402 let undebrujined_expr =
1404 (fun expr t -> CicSubstitution.subst t expr) expr subst
1406 name, undebrujined_expr
1407 | _ -> raise AmbiguousInput
1408 ) cons cons_type_widgets
1410 get_cons_types := (function () -> cons_types) ;
1414 output_html outputhtml
1415 (`Error (`T (Printexc.to_string e)))
1419 let okb_pressed = !chosen in
1421 if (not okb_pressed) then
1424 assert false (* The control never reaches this point *)
1427 (!get_cons_types ())
1430 (* No more phases left or Abort pressed *)
1436 let uri = !get_uri () in
1439 let tys = !get_types_and_cons () in
1440 let obj = Cic.InductiveDefinition(tys,params,!paramsno) in
1443 prerr_endline (CicPp.ppobj obj) ;
1444 CicTypeChecker.typecheck_mutual_inductive_defs uri
1445 (tys,params,!paramsno) ;
1448 prerr_endline "Offending mutual (co)inductive type declaration:" ;
1449 prerr_endline (CicPp.ppobj obj) ;
1451 (* We already know that obj is well-typed. We need to add it to the *)
1452 (* environment in order to compute the inner-types without having to *)
1453 (* debrujin it or having to modify lots of other functions to avoid *)
1454 (* asking the environment for the MUTINDs we are defining now. *)
1455 CicEnvironment.put_inductive_definition uri obj ;
1457 show_in_show_window_obj uri obj
1460 output_html outputhtml
1461 (`Error (`T (Printexc.to_string e)))
1465 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1466 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1467 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1468 let notebook = (rendering_window ())#notebook in
1470 let chosen = ref false in
1471 let get_metasenv_and_term = ref (function _ -> assert false) in
1472 let get_uri = ref (function _ -> assert false) in
1473 let non_empty_type = ref false in
1476 ~width:600 ~modal:true ~title:"New Proof or Definition"
1477 ~border_width:2 () in
1478 let vbox = GPack.vbox ~packing:window#add () in
1480 GPack.hbox ~border_width:0
1481 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1483 GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1484 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1486 GEdit.entry ~editable:true
1487 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1488 uri_entry#set_text dummy_uri;
1489 uri_entry#select_region ~start:1 ~stop:(String.length dummy_uri);
1491 GPack.hbox ~border_width:0
1492 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1494 GMisc.label ~text:"Enter the theorem or definition type:"
1495 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1496 let scrolled_window =
1497 GBin.scrolled_window ~border_width:5
1498 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1499 (* the content of the scrolled_window is moved below (see comment) *)
1501 GPack.hbox ~border_width:0
1502 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1504 GButton.button ~label:"Ok"
1505 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1506 let _ = okb#misc#set_sensitive false in
1508 GButton.button ~label:"Cancel"
1509 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1510 (* moved here to have visibility of the ok button *)
1512 TexTermEditor'.term_editor
1514 ~width:400 ~height:100 ~packing:scrolled_window#add
1515 ~share_id_to_uris_with:inputt ()
1516 ~isnotempty_callback:
1518 non_empty_type := b ;
1519 okb#misc#set_sensitive (b && uri_entry#text <> ""))
1522 let xxx = inputt#get_as_string in
1523 prerr_endline ("######################## " ^ xxx) ;
1524 newinputt#set_term xxx ;
1526 newinputt#set_term inputt#get_as_string ;
1530 uri_entry#connect#changed
1532 okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1534 ignore (window#connect#destroy GMain.Main.quit) ;
1535 ignore (cancelb#connect#clicked window#destroy) ;
1537 (okb#connect#clicked
1541 let metasenv,parsed = newinputt#get_metasenv_and_term [] [] in
1542 let uristr = "cic:" ^ uri_entry#text in
1543 let uri = UriManager.uri_of_string uristr in
1544 if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1545 raise NotAUriToAConstant
1549 ignore (Getter.resolve uri) ;
1550 raise UriAlreadyInUse
1552 Getter.Unresolved ->
1553 get_metasenv_and_term := (function () -> metasenv,parsed) ;
1554 get_uri := (function () -> uri) ;
1559 output_html outputhtml
1560 (`Error (`T (Printexc.to_string e)))
1566 let metasenv,expr = !get_metasenv_and_term () in
1567 let _ = CicTypeChecker.type_of_aux' metasenv [] expr in
1568 ProofEngine.set_proof
1569 (Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr)) ;
1570 set_proof_engine_goal (Some 1) ;
1571 refresh_goals notebook ;
1572 refresh_proof output ;
1573 !save_set_sensitive true ;
1575 ProofEngine.intros ~mk_fresh_name_callback () ;
1576 refresh_goals notebook ;
1577 refresh_proof output
1579 InvokeTactics.RefreshSequentException e ->
1580 output_html outputhtml
1581 (`Error (`T ("Exception raised during the refresh of the " ^
1582 "sequent: " ^ Printexc.to_string e)))
1583 | InvokeTactics.RefreshProofException e ->
1584 output_html outputhtml
1585 (`Error (`T ("Exception raised during the refresh of the " ^
1586 "proof: " ^ Printexc.to_string e)))
1588 output_html outputhtml
1589 (`Error (`T (Printexc.to_string e)))
1592 let check_term_in_scratch scratch_window metasenv context expr =
1594 let ty = CicTypeChecker.type_of_aux' metasenv context expr in
1595 let expr = Cic.Cast (expr,ty) in
1596 scratch_window#show () ;
1597 scratch_window#set_term expr ;
1598 scratch_window#set_context context ;
1599 scratch_window#set_metasenv metasenv ;
1600 scratch_window#sequent_viewer#load_sequent metasenv (111,context,expr)
1603 print_endline ("? " ^ CicPp.ppterm expr) ;
1607 let check scratch_window () =
1608 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1609 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1611 match ProofEngine.get_proof () with
1613 | Some (_,metasenv,_,_) -> metasenv
1616 match !ProofEngine.goal with
1619 let (_,canonical_context,_) =
1620 List.find (function (m,_,_) -> m=metano) metasenv
1625 let metasenv',expr = inputt#get_metasenv_and_term context metasenv in
1626 check_term_in_scratch scratch_window metasenv' context expr
1629 output_html outputhtml
1630 (`Error (`T (Printexc.to_string e)))
1634 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1636 show_in_show_window_uri (input_or_locate_uri ~title:"Show")
1639 output_html outputhtml
1640 (`Error (`T (Printexc.to_string e)))
1643 exception NotADefinition;;
1646 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1647 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1648 let notebook = (rendering_window ())#notebook in
1650 let uri = input_or_locate_uri ~title:"Open" in
1651 CicTypeChecker.typecheck uri ;
1652 let metasenv,bo,ty =
1653 match CicEnvironment.get_cooked_obj uri with
1654 Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
1655 | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
1658 | Cic.InductiveDefinition _ -> raise NotADefinition
1660 ProofEngine.set_proof (Some (uri, metasenv, bo, ty)) ;
1661 set_proof_engine_goal None ;
1662 refresh_goals notebook ;
1663 refresh_proof output ;
1664 !save_set_sensitive true
1666 InvokeTactics.RefreshSequentException e ->
1667 output_html outputhtml
1668 (`Error (`T ("Exception raised during the refresh of the " ^
1669 "sequent: " ^ Printexc.to_string e)))
1670 | InvokeTactics.RefreshProofException e ->
1671 output_html outputhtml
1672 (`Error (`T ("Exception raised during the refresh of the " ^
1673 "proof: " ^ Printexc.to_string e)))
1675 output_html outputhtml
1676 (`Error (`T (Printexc.to_string e)))
1679 let show_query_results results =
1682 ~modal:false ~title:"Query results." ~border_width:2 () in
1683 let vbox = GPack.vbox ~packing:window#add () in
1685 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1688 ~text:"Click on a URI to show that object"
1689 ~packing:hbox#add () in
1690 let scrolled_window =
1691 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1692 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1693 let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
1696 (function (uri,_) ->
1700 clist#set_row ~selectable:false n
1703 clist#columns_autosize () ;
1705 (clist#connect#select_row
1706 (fun ~row ~column ~event ->
1707 let (uristr,_) = List.nth results row in
1709 MQueryMisc.cic_textual_parser_uri_of_string
1710 (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
1713 CicTextualParser0.ConUri uri
1714 | CicTextualParser0.VarUri uri
1715 | CicTextualParser0.IndTyUri (uri,_)
1716 | CicTextualParser0.IndConUri (uri,_,_) ->
1717 show_in_show_window_uri uri
1723 let refine_constraints (must_obj,must_rel,must_sort) =
1724 let chosen = ref false in
1725 let use_only = ref false in
1728 ~modal:true ~title:"Constraints refinement."
1729 ~width:800 ~border_width:2 () in
1730 let vbox = GPack.vbox ~packing:window#add () in
1732 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1735 ~text: "\"Only\" constraints can be enforced or not."
1736 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1738 GButton.toggle_button ~label:"Enforce \"only\" constraints"
1739 ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1742 (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
1743 (* Notebook for the constraints choice *)
1745 GPack.notebook ~scrollable:true
1746 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1747 (* Rel constraints *)
1750 ~text: "Constraints on Rels" () in
1752 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1755 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1758 ~text: "You can now specify the constraints on Rels."
1759 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1760 let expected_height = 25 * (List.length must_rel + 2) in
1761 let height = if expected_height > 400 then 400 else expected_height in
1762 let scrolled_window =
1763 GBin.scrolled_window ~border_width:10 ~height ~width:600
1764 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1765 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1766 let mk_depth_button (hbox:GPack.box) d =
1767 let mutable_ref = ref (Some d) in
1769 GButton.toggle_button
1770 ~label:("depth = " ^ string_of_int d)
1772 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1775 (depthb#connect#toggled
1777 let sel_depth = if depthb#active then Some d else None in
1778 mutable_ref := sel_depth
1781 let rel_constraints =
1786 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1789 ~text:(MQGU.text_of_position (p:>MQGT.full_position))
1790 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1792 | `MainHypothesis None
1793 | `MainConclusion None -> p, ref None
1794 | `MainHypothesis (Some depth')
1795 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth'
1797 (* Sort constraints *)
1800 ~text: "Constraints on Sorts" () in
1802 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1805 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1808 ~text: "You can now specify the constraints on Sorts."
1809 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1810 let expected_height = 25 * (List.length must_sort + 2) in
1811 let height = if expected_height > 400 then 400 else expected_height in
1812 let scrolled_window =
1813 GBin.scrolled_window ~border_width:10 ~height ~width:600
1814 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1815 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1816 let sort_constraints =
1818 (function (p, sort) ->
1821 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1824 ~text:(MQGU.text_of_sort sort ^ " " ^ MQGU.text_of_position (p:>MQGT.full_position))
1825 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1827 | `MainHypothesis None
1828 | `MainConclusion None -> p, ref None, sort
1829 | `MainHypothesis (Some depth')
1830 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth', sort
1832 (* Obj constraints *)
1835 ~text: "Constraints on constants" () in
1837 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1840 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1843 ~text: "You can now specify the constraints on constants."
1844 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1845 let expected_height = 25 * (List.length must_obj + 2) in
1846 let height = if expected_height > 400 then 400 else expected_height in
1847 let scrolled_window =
1848 GBin.scrolled_window ~border_width:10 ~height ~width:600
1849 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1850 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1851 let obj_constraints =
1853 (function (p, uri) ->
1856 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1859 ~text:(uri ^ " " ^ (MQGU.text_of_position p))
1860 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1865 | `MainHypothesis None
1866 | `MainConclusion None -> p, ref None, uri
1867 | `MainHypothesis (Some depth')
1868 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth', uri
1870 (* Confirm/abort buttons *)
1872 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1874 GButton.button ~label:"Ok"
1875 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1877 GButton.button ~label:"Abort"
1878 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1880 ignore (window#connect#destroy GMain.Main.quit) ;
1881 ignore (cancelb#connect#clicked window#destroy) ;
1883 (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
1884 window#set_position `CENTER ;
1888 let chosen_must_rel =
1890 (function (position, ref_depth) -> MQGU.set_main_position position !ref_depth)
1893 let chosen_must_sort =
1895 (function (position, ref_depth, sort) ->
1896 MQGU.set_main_position position !ref_depth,sort)
1899 let chosen_must_obj =
1901 (function (position, ref_depth, uri) -> MQGU.set_full_position position !ref_depth, uri)
1904 (chosen_must_obj,chosen_must_rel,chosen_must_sort),
1906 (*CSC: ???????????????????????? I assume that must and only are the same... *)
1907 Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
1915 let completeSearchPattern () =
1916 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1917 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1919 let metasenv,expr = inputt#get_metasenv_and_term ~context:[] ~metasenv:[] in
1920 let must = CGSearchPattern.get_constraints expr in
1921 let must',only = refine_constraints must in
1923 MQG.query_of_constraints (Some CGSearchPattern.universe) must' only
1925 let results = MQI.execute mqi_handle query in
1926 show_query_results results
1929 output_html outputhtml
1930 (`Error (`T (Printexc.to_string e)))
1933 let insertQuery () =
1934 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
1936 let chosen = ref None in
1939 ~modal:true ~title:"Insert Query (Experts Only)" ~border_width:2 () in
1940 let vbox = GPack.vbox ~packing:window#add () in
1942 GMisc.label ~text:"Insert Query. For Experts Only."
1943 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1944 let scrolled_window =
1945 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1946 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1947 let input = GText.view ~editable:true
1948 ~packing:scrolled_window#add () in
1950 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1952 GButton.button ~label:"Ok"
1953 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1955 GButton.button ~label:"Load from file..."
1956 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1958 GButton.button ~label:"Abort"
1959 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1960 ignore (window#connect#destroy GMain.Main.quit) ;
1961 ignore (cancelb#connect#clicked window#destroy) ;
1963 (okb#connect#clicked
1965 chosen := Some (input#buffer#get_text ()) ; window#destroy ())) ;
1967 (loadb#connect#clicked
1970 GToolbox.select_file ~title:"Select Query File" ()
1974 let inch = open_in filename in
1975 let rec read_file () =
1977 let line = input_line inch in
1978 line ^ "\n" ^ read_file ()
1982 let text = read_file () in
1983 input#buffer#delete input#buffer#start_iter input#buffer#end_iter ;
1984 ignore (input#buffer#insert text))) ;
1985 window#set_position `CENTER ;
1992 MQI.execute mqi_handle (MQueryUtil.query_of_text (Lexing.from_string q))
1994 show_query_results results
1997 output_html outputhtml
1998 (`Error (`T (Printexc.to_string e)))
2001 let choose_must list_of_must only =
2002 let chosen = ref None in
2003 let user_constraints = ref [] in
2006 ~modal:true ~title:"Query refinement." ~border_width:2 () in
2007 let vbox = GPack.vbox ~packing:window#add () in
2009 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2013 ("You can now specify the genericity of the query. " ^
2014 "The more generic the slower.")
2015 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2017 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2021 "Suggestion: start with faster queries before moving to more generic ones."
2022 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2024 GPack.notebook ~scrollable:true
2025 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2028 let last = List.length list_of_must in
2034 (if !page = 1 then "More generic" else
2035 if !page = last then "More precise" else " ") () in
2036 let expected_height = 25 * (List.length must + 2) in
2037 let height = if expected_height > 400 then 400 else expected_height in
2038 let scrolled_window =
2039 GBin.scrolled_window ~border_width:10 ~height ~width:600
2040 ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2042 GList.clist ~columns:2 ~packing:scrolled_window#add
2043 ~titles:["URI" ; "Position"] ()
2047 (function (position, uri) ->
2050 [uri; MQGUtil.text_of_position position]
2052 clist#set_row ~selectable:false n
2055 clist#columns_autosize ()
2058 let label = GMisc.label ~text:"User provided" () in
2060 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2062 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2065 ~text:"Select the constraints that must be satisfied and press OK."
2066 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2067 let expected_height = 25 * (List.length only + 2) in
2068 let height = if expected_height > 400 then 400 else expected_height in
2069 let scrolled_window =
2070 GBin.scrolled_window ~border_width:10 ~height ~width:600
2071 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2073 GList.clist ~columns:2 ~packing:scrolled_window#add
2074 ~selection_mode:`MULTIPLE
2075 ~titles:["URI" ; "Position"] ()
2079 (function (position, uri) ->
2082 [uri; MQGUtil.text_of_position position]
2084 clist#set_row ~selectable:true n
2087 clist#columns_autosize () ;
2089 (clist#connect#select_row
2090 (fun ~row ~column ~event ->
2091 user_constraints := (List.nth only row)::!user_constraints)) ;
2093 (clist#connect#unselect_row
2094 (fun ~row ~column ~event ->
2097 (function uri -> uri != (List.nth only row)) !user_constraints)) ;
2100 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2102 GButton.button ~label:"Ok"
2103 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2105 GButton.button ~label:"Abort"
2106 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2108 ignore (window#connect#destroy GMain.Main.quit) ;
2109 ignore (cancelb#connect#clicked window#destroy) ;
2111 (okb#connect#clicked
2112 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2113 window#set_position `CENTER ;
2117 None -> raise NoChoice
2119 if n = List.length list_of_must then
2120 (* user provided constraints *)
2123 List.nth list_of_must n
2126 let searchPattern () =
2127 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
2128 let outputhtml = ((rendering_window ())#outputhtml(* : GHtml.xmhtml*)) in
2131 match ProofEngine.get_proof () with
2132 None -> assert false
2133 | Some proof -> proof
2135 match !ProofEngine.goal with
2139 TacticChaser.matchConclusion
2141 ~output_html:(fun m -> output_html outputhtml (`Msg (`T m)))
2142 ~choose_must () ~status:(proof, metano)
2145 user_uri_choice ~title:"Ambiguous input."
2146 ~msg: "Many lemmas can be successfully applied. Please, choose one:"
2149 inputt#set_term uri' ;
2150 InvokeTactics'.apply ()
2153 output_html outputhtml
2154 (`Error (`T (Printexc.to_string e)))
2157 let choose_selection mmlwidget (element : Gdome.element option) =
2158 let module G = Gdome in
2159 prerr_endline "Il bandolo" ;
2160 let rec aux element =
2161 if element#hasAttributeNS
2162 ~namespaceURI:Misc.helmns
2163 ~localName:(G.domString "xref")
2165 mmlwidget#set_selection (Some element)
2168 match element#get_parentNode with
2169 None -> assert false
2170 (*CSC: OCAML DIVERGES!
2171 | Some p -> aux (new G.element_of_node p)
2173 | Some p -> aux (new Gdome.element_of_node p)
2175 GdomeInit.DOMCastException _ ->
2177 "******* trying to select above the document root ********"
2181 | None -> mmlwidget#set_selection None
2184 (* STUFF TO BUILD THE GTK INTERFACE *)
2186 (* Stuff for the widget settings *)
2189 let export_to_postscript output =
2190 let lastdir = ref (Unix.getcwd ()) in
2193 GToolbox.select_file ~title:"Export to PostScript"
2194 ~dir:lastdir ~filename:"screenshot.ps" ()
2198 (output :> GMathView.math_view)#export_to_postscript
2199 ~filename:filename ();
2204 let activate_t1 output button_set_anti_aliasing
2205 button_set_transparency export_to_postscript_menu_item
2208 let is_set = button_t1#active in
2209 output#set_font_manager_type
2210 ~fm_type:(if is_set then `font_manager_t1 else `font_manager_gtk) ;
2213 button_set_anti_aliasing#misc#set_sensitive true ;
2214 button_set_transparency#misc#set_sensitive true ;
2215 export_to_postscript_menu_item#misc#set_sensitive true ;
2219 button_set_anti_aliasing#misc#set_sensitive false ;
2220 button_set_transparency#misc#set_sensitive false ;
2221 export_to_postscript_menu_item#misc#set_sensitive false ;
2225 let set_anti_aliasing output button_set_anti_aliasing () =
2226 output#set_anti_aliasing button_set_anti_aliasing#active
2229 let set_transparency output button_set_transparency () =
2230 output#set_transparency button_set_transparency#active
2234 let changefont output font_size_spinb () =
2235 output#set_font_size font_size_spinb#value_as_int
2238 let set_log_verbosity output log_verbosity_spinb () =
2239 output#set_log_verbosity log_verbosity_spinb#value_as_int
2242 class settings_window output sw
2243 export_to_postscript_menu_item selection_changed_callback
2245 let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2247 GPack.vbox ~packing:settings_window#add () in
2250 ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2251 ~border_width:5 ~packing:vbox#add () in
2253 GButton.toggle_button ~label:"activate t1 fonts"
2254 ~packing:(table#attach ~left:0 ~top:0) () in
2255 let button_set_anti_aliasing =
2256 GButton.toggle_button ~label:"set_anti_aliasing"
2257 ~packing:(table#attach ~left:0 ~top:1) () in
2258 let button_set_transparency =
2259 GButton.toggle_button ~label:"set_transparency"
2260 ~packing:(table#attach ~left:2 ~top:1) () in
2263 ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2264 ~border_width:5 ~packing:vbox#add () in
2265 let font_size_label =
2266 GMisc.label ~text:"font size:"
2267 ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2268 let font_size_spinb =
2270 GData.adjustment ~value:(float_of_int output#get_font_size)
2271 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2274 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2275 let log_verbosity_label =
2276 GMisc.label ~text:"log verbosity:"
2277 ~packing:(table#attach ~left:0 ~top:1) () in
2278 let log_verbosity_spinb =
2280 GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2283 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2285 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2287 GButton.button ~label:"Close"
2288 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2290 method show = settings_window#show
2292 button_set_anti_aliasing#misc#set_sensitive false ;
2293 button_set_transparency#misc#set_sensitive false ;
2294 (* Signals connection *)
2296 ignore(button_t1#connect#clicked
2297 (activate_t1 output button_set_anti_aliasing
2298 button_set_transparency export_to_postscript_menu_item button_t1)) ;
2300 ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2302 ignore(button_set_anti_aliasing#connect#toggled
2303 (set_anti_aliasing output button_set_anti_aliasing));
2304 ignore(button_set_transparency#connect#toggled
2305 (set_transparency output button_set_transparency)) ;
2307 ignore(log_verbosity_spinb#connect#changed
2308 (set_log_verbosity output log_verbosity_spinb)) ;
2309 ignore(closeb#connect#clicked settings_window#misc#hide)
2312 (* Scratch window *)
2314 class scratch_window =
2317 ~title:"MathML viewer"
2318 ~border_width:2 () in
2320 GPack.vbox ~packing:window#add () in
2322 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2324 GButton.button ~label:"Whd"
2325 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2327 GButton.button ~label:"Reduce"
2328 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2330 GButton.button ~label:"Simpl"
2331 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2332 let scrolled_window =
2333 GBin.scrolled_window ~border_width:10
2334 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2335 let sequent_viewer =
2336 TermViewer.sequent_viewer
2337 ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
2339 val mutable term = Cic.Rel 1 (* dummy value *)
2340 val mutable context = ([] : Cic.context) (* dummy value *)
2341 val mutable metasenv = ([] : Cic.metasenv) (* dummy value *)
2342 method sequent_viewer = sequent_viewer
2343 method show () = window#misc#hide () ; window#show ()
2345 method set_term t = term <- t
2346 method context = context
2347 method set_context t = context <- t
2348 method metasenv = metasenv
2349 method set_metasenv t = metasenv <- t
2352 (sequent_viewer#connect#selection_changed (choose_selection sequent_viewer));
2353 ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
2354 ignore(whdb#connect#clicked InvokeTactics'.whd_in_scratch) ;
2355 ignore(reduceb#connect#clicked InvokeTactics'.reduce_in_scratch) ;
2356 ignore(simplb#connect#clicked InvokeTactics'.simpl_in_scratch)
2359 let open_contextual_menu_for_selected_terms mmlwidget infos =
2360 let button = GdkEvent.Button.button infos in
2361 let terms_selected = List.length mmlwidget#get_selections > 0 in
2364 let time = GdkEvent.Button.time infos in
2365 let menu = GMenu.menu () in
2366 let f = new GMenu.factory menu in
2368 f#add_item "Whd" ~key:GdkKeysyms._W ~callback:InvokeTactics'.whd in
2369 let reduce_menu_item =
2370 f#add_item "Reduce" ~key:GdkKeysyms._R ~callback:InvokeTactics'.reduce in
2371 let simpl_menu_item =
2372 f#add_item "Simpl" ~key:GdkKeysyms._S ~callback:InvokeTactics'.simpl in
2373 let _ = f#add_separator () in
2374 let generalize_menu_item =
2375 f#add_item "Generalize"
2376 ~key:GdkKeysyms._G ~callback:InvokeTactics'.generalize in
2377 let _ = f#add_separator () in
2378 let clear_menu_item =
2379 f#add_item "Clear" ~key:GdkKeysyms._C ~callback:InvokeTactics'.clear in
2380 let clearbody_menu_item =
2381 f#add_item "ClearBody"
2382 ~key:GdkKeysyms._B ~callback:InvokeTactics'.clearbody
2384 whd_menu_item#misc#set_sensitive terms_selected ;
2385 reduce_menu_item#misc#set_sensitive terms_selected ;
2386 simpl_menu_item#misc#set_sensitive terms_selected ;
2387 generalize_menu_item#misc#set_sensitive terms_selected ;
2388 clear_menu_item#misc#set_sensitive terms_selected ;
2389 clearbody_menu_item#misc#set_sensitive terms_selected ;
2390 menu#popup ~button ~time
2396 let vbox1 = GPack.vbox () in
2398 val mutable proofw_ref = None
2399 val mutable compute_ref = None
2401 Lazy.force self#compute ;
2402 match proofw_ref with
2403 None -> assert false
2404 | Some proofw -> proofw
2405 method content = vbox1
2407 match compute_ref with
2408 None -> assert false
2409 | Some compute -> compute
2413 let scrolled_window1 =
2414 GBin.scrolled_window ~border_width:10
2415 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2417 TermViewer.sequent_viewer ~width:400 ~height:275
2418 ~packing:(scrolled_window1#add) () in
2419 let _ = proofw_ref <- Some proofw in
2421 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2423 GButton.button ~label:"Ring"
2424 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2426 GButton.button ~label:"Fourier"
2427 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2429 GButton.button ~label:"Reflexivity"
2430 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2432 GButton.button ~label:"Symmetry"
2433 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2435 GButton.button ~label:"Assumption"
2436 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2437 let contradictionb =
2438 GButton.button ~label:"Contradiction"
2439 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2441 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2443 GButton.button ~label:"Exists"
2444 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2446 GButton.button ~label:"Split"
2447 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2449 GButton.button ~label:"Left"
2450 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2452 GButton.button ~label:"Right"
2453 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2454 let searchpatternb =
2455 GButton.button ~label:"SearchPattern_Apply"
2456 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2458 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2460 GButton.button ~label:"Exact"
2461 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2463 GButton.button ~label:"Intros"
2464 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2466 GButton.button ~label:"Apply"
2467 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2468 let elimintrossimplb =
2469 GButton.button ~label:"ElimIntrosSimpl"
2470 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2472 GButton.button ~label:"ElimType"
2473 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2475 GButton.button ~label:"Fold_whd"
2476 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2478 GButton.button ~label:"Fold_reduce"
2479 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2481 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2483 GButton.button ~label:"Fold_simpl"
2484 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2486 GButton.button ~label:"Cut"
2487 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2489 GButton.button ~label:"Change"
2490 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2492 GButton.button ~label:"Let ... In"
2493 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2495 GButton.button ~label:"RewriteSimpl ->"
2496 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2497 let rewritebacksimplb =
2498 GButton.button ~label:"RewriteSimpl <-"
2499 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2501 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2503 GButton.button ~label:"Absurd"
2504 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2506 GButton.button ~label:"Decompose"
2507 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2509 GButton.button ~label:"Transitivity"
2510 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2512 GButton.button ~label:"Replace"
2513 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2515 GButton.button ~label:"Injection"
2516 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2518 GButton.button ~label:"Discriminate"
2519 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2520 (* Zack: spostare in una toolbar
2522 GButton.button ~label:"Generalize"
2523 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2525 GButton.button ~label:"ClearBody"
2526 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2528 GButton.button ~label:"Clear"
2529 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2531 GButton.button ~label:"Whd"
2532 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2534 GButton.button ~label:"Reduce"
2535 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2537 GButton.button ~label:"Simpl"
2538 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2541 ignore(exactb#connect#clicked InvokeTactics'.exact) ;
2542 ignore(applyb#connect#clicked InvokeTactics'.apply) ;
2543 ignore(elimintrossimplb#connect#clicked InvokeTactics'.elimintrossimpl) ;
2544 ignore(elimtypeb#connect#clicked InvokeTactics'.elimtype) ;
2545 ignore(foldwhdb#connect#clicked InvokeTactics'.fold_whd) ;
2546 ignore(foldreduceb#connect#clicked InvokeTactics'.fold_reduce) ;
2547 ignore(foldsimplb#connect#clicked InvokeTactics'.fold_simpl) ;
2548 ignore(cutb#connect#clicked InvokeTactics'.cut) ;
2549 ignore(changeb#connect#clicked InvokeTactics'.change) ;
2550 ignore(letinb#connect#clicked InvokeTactics'.letin) ;
2551 ignore(ringb#connect#clicked InvokeTactics'.ring) ;
2552 ignore(fourierb#connect#clicked InvokeTactics'.fourier) ;
2553 ignore(rewritesimplb#connect#clicked InvokeTactics'.rewritesimpl) ;
2554 ignore(rewritebacksimplb#connect#clicked InvokeTactics'.rewritebacksimpl) ;
2555 ignore(replaceb#connect#clicked InvokeTactics'.replace) ;
2556 ignore(reflexivityb#connect#clicked InvokeTactics'.reflexivity) ;
2557 ignore(symmetryb#connect#clicked InvokeTactics'.symmetry) ;
2558 ignore(transitivityb#connect#clicked InvokeTactics'.transitivity) ;
2559 ignore(existsb#connect#clicked InvokeTactics'.exists) ;
2560 ignore(splitb#connect#clicked InvokeTactics'.split) ;
2561 ignore(leftb#connect#clicked InvokeTactics'.left) ;
2562 ignore(rightb#connect#clicked InvokeTactics'.right) ;
2563 ignore(assumptionb#connect#clicked InvokeTactics'.assumption) ;
2564 ignore(absurdb#connect#clicked InvokeTactics'.absurd) ;
2565 ignore(contradictionb#connect#clicked InvokeTactics'.contradiction) ;
2566 ignore(introsb#connect#clicked InvokeTactics'.intros) ;
2567 ignore(decomposeb#connect#clicked InvokeTactics'.decompose) ;
2568 ignore(searchpatternb#connect#clicked searchPattern) ;
2569 ignore(injectionb#connect#clicked InvokeTactics'.injection) ;
2570 ignore(discriminateb#connect#clicked InvokeTactics'.discriminate) ;
2571 (* Zack: spostare in una toolbar
2572 ignore(whdb#connect#clicked whd) ;
2573 ignore(reduceb#connect#clicked reduce) ;
2574 ignore(simplb#connect#clicked simpl) ;
2575 ignore(clearbodyb#connect#clicked clearbody) ;
2576 ignore(clearb#connect#clicked clear) ;
2577 ignore(generalizeb#connect#clicked generalize) ;
2579 ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
2581 ((new GObj.event_ops proofw#as_widget)#connect#button_press
2582 (open_contextual_menu_for_selected_terms proofw)) ;
2588 let vbox1 = GPack.vbox () in
2589 let scrolled_window1 =
2590 GBin.scrolled_window ~border_width:10
2591 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2593 TermViewer.sequent_viewer ~width:400 ~height:275
2594 ~packing:(scrolled_window1#add) () in
2596 method proofw = (assert false : TermViewer.sequent_viewer)
2597 method content = vbox1
2598 method compute = (assert false : unit)
2602 let empty_page = new empty_page;;
2606 val notebook = GPack.notebook ()
2608 val mutable skip_switch_page_event = false
2609 val mutable empty = true
2610 method notebook = notebook
2612 let new_page = new page () in
2614 pages := !pages @ [n,lazy (setgoal n),new_page] ;
2615 notebook#append_page
2616 ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
2617 new_page#content#coerce
2618 method remove_all_pages ~skip_switch_page_event:skip =
2620 notebook#remove_page 0 (* let's remove the empty page *)
2622 List.iter (function _ -> notebook#remove_page 0) !pages ;
2624 skip_switch_page_event <- skip
2625 method set_current_page ~may_skip_switch_page_event n =
2626 let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
2627 let new_page = notebook#page_num page#content#coerce in
2628 if may_skip_switch_page_event && new_page <> notebook#current_page then
2629 skip_switch_page_event <- true ;
2630 notebook#goto_page new_page
2631 method set_empty_page =
2634 notebook#append_page
2635 ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
2636 empty_page#content#coerce
2638 let (_,_,page) = List.nth !pages notebook#current_page in
2642 (notebook#connect#switch_page
2644 let skip = skip_switch_page_event in
2645 skip_switch_page_event <- false ;
2648 let (metano,setgoal,page) = List.nth !pages i in
2649 set_proof_engine_goal (Some metano) ;
2650 Lazy.force (page#compute) ;
2652 if notify_hbugs_on_goal_change then
2659 let dump_environment () =
2661 let oc = open_out environmentfile in
2662 output_html (outputhtml ()) (`Msg (`T "Dumping environment ..."));
2663 CicEnvironment.dump_to_channel
2664 ~callback:(fun uri -> output_html (outputhtml ()) (`Msg (`T uri)))
2666 output_html (outputhtml ()) (`Msg (`T "... done!")) ;
2669 output_html (outputhtml ())
2670 (`Error (`T (Printf.sprintf "Dump failure, uncaught exception:%s"
2671 (Printexc.to_string exc))))
2673 let restore_environment () =
2675 let ic = open_in environmentfile in
2676 output_html (outputhtml ()) (`Msg (`T "Restoring environment ... "));
2677 CicEnvironment.restore_from_channel
2678 ~callback:(fun uri -> output_html (outputhtml ()) (`Msg (`T uri)))
2680 output_html (outputhtml ()) (`Msg (`T "... done!"));
2683 output_html (outputhtml ())
2684 (`Error (`T (Printf.sprintf "Restore failure, uncaught exception:%s"
2685 (Printexc.to_string exc))))
2690 class rendering_window output (notebook : notebook) =
2691 let scratch_window = new scratch_window in
2694 ~title:"gTopLevel - Helm's Proof Assistant"
2695 ~border_width:0 ~allow_shrink:false () in
2696 let vbox_for_menu = GPack.vbox ~packing:window#add () in
2698 let handle_box = GBin.handle_box ~border_width:2
2699 ~packing:(vbox_for_menu#pack ~padding:0) () in
2700 let menubar = GMenu.menu_bar ~packing:handle_box#add () in
2701 let factory0 = new GMenu.factory menubar in
2702 let accel_group = factory0#accel_group in
2704 let file_menu = factory0#add_submenu "File" in
2705 let factory1 = new GMenu.factory file_menu ~accel_group in
2706 (* let export_to_postscript_menu_item = *)
2710 factory1#add_item "New Block of (Co)Inductive Definitions..."
2711 ~key:GdkKeysyms._B ~callback:new_inductive
2714 factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
2717 let reopen_menu_item =
2718 factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
2722 factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
2723 ignore (factory1#add_separator ()) ;
2725 (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
2726 ~callback:load_unfinished_proof) ;
2727 let save_menu_item =
2728 factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S
2729 ~callback:save_unfinished_proof
2731 ignore (factory1#add_separator ()) ;
2732 ignore (factory1#add_item "Clear Environment" ~callback:CicEnvironment.empty);
2733 ignore (factory1#add_item "Dump Environment" ~callback:dump_environment);
2735 (factory1#add_item "Restore Environment" ~callback:restore_environment);
2737 (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
2738 ignore (!save_set_sensitive false);
2739 ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
2740 ignore (!qed_set_sensitive false);
2741 ignore (factory1#add_separator ()) ;
2743 let export_to_postscript_menu_item =
2744 factory1#add_item "Export to PostScript..."
2745 ~callback:(export_to_postscript output) in
2747 ignore (factory1#add_separator ()) ;
2749 (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) (*;
2750 export_to_postscript_menu_item *)
2753 let edit_menu = factory0#add_submenu "Edit Current Proof" in
2754 let factory2 = new GMenu.factory edit_menu ~accel_group in
2755 let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
2756 let proveit_menu_item =
2757 factory2#add_item "Prove It" ~key:GdkKeysyms._I
2758 ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
2760 let focus_menu_item =
2761 factory2#add_item "Focus" ~key:GdkKeysyms._F
2762 ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
2765 focus_and_proveit_set_sensitive :=
2767 proveit_menu_item#misc#set_sensitive b ;
2768 focus_menu_item#misc#set_sensitive b
2770 let _ = !focus_and_proveit_set_sensitive false in
2771 (* edit term menu *)
2772 let edit_term_menu = factory0#add_submenu "Edit Term" in
2773 let factory5 = new GMenu.factory edit_term_menu ~accel_group in
2774 let check_menu_item =
2775 factory5#add_item "Check Term" ~key:GdkKeysyms._C
2776 ~callback:(check scratch_window) in
2777 let _ = check_menu_item#misc#set_sensitive false in
2779 let search_menu = factory0#add_submenu "Search" in
2780 let factory4 = new GMenu.factory search_menu ~accel_group in
2782 factory4#add_item "Locate..." ~key:GdkKeysyms._T
2784 let searchPattern_menu_item =
2785 factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
2786 ~callback:completeSearchPattern in
2787 let _ = searchPattern_menu_item#misc#set_sensitive false in
2788 let show_menu_item =
2789 factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
2791 let insert_query_item =
2792 factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._Y
2793 ~callback:insertQuery in
2795 let hbugs_menu = factory0#add_submenu "HBugs" in
2796 let factory6 = new GMenu.factory hbugs_menu ~accel_group in
2798 factory6#add_check_item
2799 ~active:false ~key:GdkKeysyms._F5 ~callback:Hbugs.toggle "HBugs enabled"
2802 factory6#add_item ~key:GdkKeysyms._Return ~callback:Hbugs.notify
2803 "(Re)Submit status!"
2805 let _ = factory6#add_separator () in
2807 factory6#add_item ~callback:Hbugs.start_web_services "Start Web Services"
2810 factory6#add_item ~callback:Hbugs.stop_web_services "Stop Web Services"
2813 let settings_menu = factory0#add_submenu "Settings" in
2814 let factory3 = new GMenu.factory settings_menu ~accel_group in
2816 factory3#add_item "Edit Aliases..." ~key:GdkKeysyms._A
2817 ~callback:edit_aliases in
2818 let _ = factory3#add_separator () in
2820 factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
2821 ~callback:(function _ -> (settings_window ())#show ()) in
2822 let _ = factory3#add_separator () in
2824 factory3#add_item "Reload Stylesheets"
2827 ApplyStylesheets.reload_stylesheets () ;
2828 if ProofEngine.get_proof () <> None then
2830 refresh_goals notebook ;
2831 refresh_proof output
2833 InvokeTactics.RefreshSequentException e ->
2834 output_html (outputhtml ())
2835 (`Error (`T ("An error occurred while refreshing the " ^
2836 "sequent: " ^ Printexc.to_string e))) ;
2837 (*notebook#remove_all_pages ~skip_switch_page_event:false ;*)
2838 notebook#set_empty_page
2839 | InvokeTactics.RefreshProofException e ->
2840 output_html (outputhtml ())
2841 (`Error (`T ("An error occurred while refreshing the proof: " ^ Printexc.to_string e))) ;
2845 let _ = window#add_accel_group accel_group in
2849 ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
2851 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2852 let scrolled_window0 =
2853 GBin.scrolled_window ~border_width:10
2854 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2855 let _ = scrolled_window0#add output#coerce in
2857 GBin.frame ~label:"Insert Term"
2858 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2859 let scrolled_window1 =
2860 GBin.scrolled_window ~border_width:5
2861 ~packing:frame#add () in
2863 TexTermEditor'.term_editor
2865 ~width:400 ~height:100 ~packing:scrolled_window1#add ()
2866 ~isnotempty_callback:
2868 check_menu_item#misc#set_sensitive b ;
2869 searchPattern_menu_item#misc#set_sensitive b) in
2871 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2873 vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
2875 GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
2878 new Ui_logger.html_logger
2879 ~width:400 ~height: 100
2883 method outputhtml = outputhtml
2884 method inputt = inputt
2885 method output = (output : TermViewer.proof_viewer)
2886 method scratch_window = scratch_window
2887 method notebook = notebook
2888 method show = window#show
2890 notebook#set_empty_page ;
2891 (*export_to_postscript_menu_item#misc#set_sensitive false ;*)
2892 check_term := (check_term_in_scratch scratch_window) ;
2894 (* signal handlers here *)
2895 ignore(output#connect#selection_changed
2897 choose_selection output elem ;
2898 !focus_and_proveit_set_sensitive true
2900 ignore (output#connect#click (show_in_show_window_callback output)) ;
2901 let settings_window = new settings_window output scrolled_window0
2902 (*export_to_postscript_menu_item*)() (choose_selection output) in
2903 set_settings_window settings_window ;
2904 set_outputhtml outputhtml ;
2905 ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
2906 CicLogger.log_callback := (outputhtml#log_cic_msg ~append_NL:true)
2911 let initialize_everything () =
2912 let module U = Unix in
2913 let output = TermViewer.proof_viewer ~width:350 ~height:280 () in
2914 let notebook = new notebook in
2915 let rendering_window' = new rendering_window output notebook in
2916 set_rendering_window rendering_window' ;
2917 let print_error_as_html prefix msg =
2918 output_html (outputhtml ()) (`Error (`T (prefix ^ msg)))
2920 Gdome_xslt.setErrorCallback (Some (print_error_as_html "XSLT Error: "));
2921 Gdome_xslt.setDebugCallback
2922 (Some (print_error_as_html "XSLT Debug Message: "));
2923 rendering_window'#show () ;
2924 if restore_environment_on_boot && Sys.file_exists environmentfile then
2925 restore_environment ();
2930 ignore (GtkMain.Main.init ()) ;
2931 initialize_everything () ;
2932 MQIC.close mqi_handle;
2937 Sys.catch_break true;
2939 with Sys.Break -> () (* exit nicely, invoking at_exit functions *)