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)
43 module MQI = MQueryInterpreter
45 module MQGT = MQGTypes
47 module MQG = MQueryGenerator
49 (* first of all let's initialize the Helm_registry *)
51 let configuration_file = "gTopLevel.conf.xml" in
52 if not (Sys.file_exists configuration_file) then begin
53 eprintf "E: Can't find configuration file '%s'\n" configuration_file;
56 Helm_registry.load_from configuration_file
59 (* GLOBAL CONSTANTS *)
61 let mqi_handle = MQIC.init_if_connected ()
65 ~host:(Helm_registry.get "db.host")
66 ~user:(Helm_registry.get "db.user")
67 ~database:(Helm_registry.get "db.database")
70 let restore_environment_on_boot = true ;;
71 let notify_hbugs_on_goal_change = false ;;
73 let auto_disambiguation = ref true ;;
75 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
77 let check_term = ref (fun _ _ _ -> assert false);;
79 exception RenderingWindowsNotInitialized;;
81 let set_rendering_window,rendering_window =
82 let rendering_window_ref = ref None in
83 (function rw -> rendering_window_ref := Some rw),
85 match !rendering_window_ref with
86 None -> raise RenderingWindowsNotInitialized
91 exception SettingsWindowsNotInitialized;;
93 let set_settings_window,settings_window =
94 let settings_window_ref = ref None in
95 (function rw -> settings_window_ref := Some rw),
97 match !settings_window_ref with
98 None -> raise SettingsWindowsNotInitialized
103 exception QedSetSensitiveNotInitialized;;
104 let qed_set_sensitive =
105 ref (function _ -> raise QedSetSensitiveNotInitialized)
108 exception SaveSetSensitiveNotInitialized;;
109 let save_set_sensitive =
110 ref (function _ -> raise SaveSetSensitiveNotInitialized)
113 (* COMMAND LINE OPTIONS *)
119 "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
122 Arg.parse argspec ignore ""
124 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
128 let check_window uris =
131 ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
133 GPack.notebook ~scrollable:true ~packing:window#add () in
138 let scrolled_window =
139 GBin.scrolled_window ~border_width:10
141 (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
146 TermViewer.sequent_viewer
147 ~mml_of_cic_sequent:ApplyTransformation.mml_of_cic_sequent
148 ~packing:scrolled_window#add ~width:400 ~height:280 () in
150 let term = CicUtil.term_of_uri uri in
151 (Cic.Cast (term, fst(CicTypeChecker.type_of_aux' [] [] term
152 CicUniv.empty_ugraph )))
155 mmlwidget#load_sequent [] (111,[],expr)
158 HelmLogger.log (`Error (`T (Printexc.to_string e)))
163 (notebook#connect#switch_page
165 Lazy.force (List.nth render_terms i)))
170 let interactive_user_uri_choice
171 ~(selection_mode:[ `SINGLE | `MULTIPLE ])
172 ?(ok="Ok") ?(enable_button_for_non_vars=false) ~title ~msg uris
174 let only_constant_choices =
177 (fun uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
180 if selection_mode <> `SINGLE && !auto_disambiguation then
181 Lazy.force only_constant_choices
183 let choices = ref [] in
184 let chosen = ref false in
185 let use_only_constants = ref false in
187 GWindow.dialog ~modal:true ~title ~width:600 () in
189 GMisc.label ~text:msg
190 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
191 let scrolled_window =
192 GBin.scrolled_window ~border_width:10
193 ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
195 let expected_height = 18 * List.length uris in
196 let height = if expected_height > 400 then 400 else expected_height in
197 GList.clist ~columns:1 ~packing:scrolled_window#add
198 ~height ~selection_mode:(selection_mode :> Gtk.Tags.selection_mode) () in
199 let _ = List.map (function x -> clist#append [x]) uris in
201 GPack.hbox ~border_width:0
202 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
204 GMisc.label ~text:"None of the above. Try this one:"
205 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
207 GEdit.entry ~editable:true
208 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
210 GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
212 GButton.button ~label:ok
213 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
214 let _ = okb#misc#set_sensitive false in
219 if enable_button_for_non_vars then
220 hbox#pack ~expand:false ~fill:false ~padding:5 w)
221 ~label:"Try constants only" () in
226 if enable_button_for_non_vars then
227 hbox#pack ~expand:false ~fill:false ~padding:5 w)
230 GButton.button ~label:"Check"
231 ~packing:(hbox#pack ~padding:5) () in
232 let _ = checkb#misc#set_sensitive false in
234 GButton.button ~label:"Abort"
235 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
237 let check_callback () =
238 assert (List.length !choices > 0) ;
239 check_window !choices
241 ignore (window#connect#destroy GMain.Main.quit) ;
242 ignore (cancelb#connect#clicked window#destroy) ;
244 (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
246 (nonvarsb#connect#clicked
248 use_only_constants := true ;
252 ignore (autob#connect#clicked (fun () ->
253 auto_disambiguation := true;
254 (rendering_window ())#set_auto_disambiguation true;
255 use_only_constants := true ;
258 ignore (checkb#connect#clicked check_callback) ;
260 (clist#connect#select_row
261 (fun ~row ~column ~event ->
262 checkb#misc#set_sensitive true ;
263 okb#misc#set_sensitive true ;
264 choices := (List.nth uris row)::!choices)) ;
266 (clist#connect#unselect_row
267 (fun ~row ~column ~event ->
269 List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
271 (manual_input#connect#changed
273 if manual_input#text = "" then
276 checkb#misc#set_sensitive false ;
277 okb#misc#set_sensitive false ;
278 clist#misc#set_sensitive true
282 choices := [manual_input#text] ;
283 clist#unselect_all () ;
284 checkb#misc#set_sensitive true ;
285 okb#misc#set_sensitive true ;
286 clist#misc#set_sensitive false
288 window#set_position `CENTER ;
292 if !use_only_constants then
293 Lazy.force only_constant_choices
295 if List.length !choices > 0 then !choices else raise NoChoice
301 let interactive_interpretation_choice interpretations =
302 let chosen = ref None in
305 ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
306 let vbox = GPack.vbox ~packing:window#add () in
310 ("Ambiguous input since there are many well-typed interpretations." ^
311 " Please, choose one of them.")
312 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
314 GPack.notebook ~scrollable:true
315 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
318 (function interpretation ->
320 let expected_height = 18 * List.length interpretation in
321 let height = if expected_height > 400 then 400 else expected_height in
322 GList.clist ~columns:2 ~packing:notebook#append_page ~height
323 ~titles:["id" ; "URI"] ()
327 (function (id,uri) ->
328 let n = clist#append [id;uri] in
329 clist#set_row ~selectable:false n
332 clist#columns_autosize ()
335 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
337 GButton.button ~label:"Ok"
338 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
340 GButton.button ~label:"Abort"
341 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
343 ignore (window#connect#destroy GMain.Main.quit) ;
344 ignore (cancelb#connect#clicked window#destroy) ;
347 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
348 window#set_position `CENTER ;
352 None -> raise NoChoice
360 save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
363 let struri = UriManager.string_of_uri uri in
364 let idx = (String.rindex struri '/') + 1 in
365 String.sub struri idx (String.length struri - idx)
367 let path = pathname ^ "/" ^ name in
369 Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
373 Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
374 ~ask_dtd_to_the_getter:false
377 let innertypesuri = UriManager.innertypesuri_of_uri uri in
378 Xml.pp ~gzip:false xmlinnertypes (Some (path ^ ".types.xml")) ;
379 Http_getter.register' innertypesuri
380 (Helm_registry.get "local_library.url" ^
381 Str.replace_first (Str.regexp "^cic:") ""
382 (UriManager.string_of_uri innertypesuri) ^ ".xml"
384 (* constant type / variable / mutual inductive types definition *)
385 Xml.pp ~gzip:false xml (Some (path ^ ".xml")) ;
386 Http_getter.register' uri
387 (Helm_registry.get "local_library.url" ^
388 Str.replace_first (Str.regexp "^cic:") ""
389 (UriManager.string_of_uri uri) ^ ".xml"
396 match UriManager.bodyuri_of_uri uri with
398 | Some bodyuri -> bodyuri
400 Xml.pp ~gzip:false bodyxml' (Some (path ^ ".body.xml")) ;
401 Http_getter.register' bodyuri
402 (Helm_registry.get "local_library.url" ^
403 Str.replace_first (Str.regexp "^cic:") ""
404 (UriManager.string_of_uri bodyuri) ^ ".xml"
411 exception OpenConjecturesStillThere;;
412 exception WrongProof;;
414 let pathname_of_annuri uristring =
415 Helm_registry.get "local_library.dir" ^
416 Str.replace_first (Str.regexp "^cic:") "" uristring
419 let make_dirs dirpath =
420 ignore (Unix.system ("mkdir -p " ^ dirpath))
423 let save_obj uri obj =
425 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
426 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
428 Cic2acic.acic_object_of_cic_object ~eta_fix:false obj
430 (* let's save the theorem and register it to the getter *)
431 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
433 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
438 match ProofEngine.get_proof () with
440 | Some (uri,[],bo,ty) ->
441 let uri = match uri with Some uri -> uri | _ -> assert false in
442 (* we want to typecheck in the ENV *)
443 prerr_endline "-------------> QED";
445 CicTypeChecker.type_of_aux' [] [] bo CicUniv.empty_ugraph in
446 let b,u1 = CicReduction.are_convertible [] ty_bo ty u in
449 (*CSC: Wrong: [] is just plainly wrong *)
451 Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[],[])
453 let (acic,ids_to_inner_types,ids_to_inner_sorts) =
454 (rendering_window ())#output#load_proof proof
456 !qed_set_sensitive false ;
457 (* let's save the theorem and register it to the getter *)
459 pathname_of_annuri (UriManager.buri_of_uri uri)
461 let list_of_universes =
462 CicUnivUtils.universes_of_obj uri
463 (Cic.Constant ("",None,ty,[],[]))
465 let u1_clean = CicUniv.clean_ugraph u1 list_of_universes in
466 let u2 = CicUniv.fill_empty_nodes_with_uri u1_clean uri in
467 (**********************************************
468 TASSI: to uncomment whe universes will be ON
469 ***********************************************)
472 save_object_to_disk uri acic ids_to_inner_sorts
473 ids_to_inner_types pathname;
475 (* save the universe graph u2 *)
476 (* add the object to the env *)
477 CicEnvironment.add_type_checked_term uri ((
478 Cic.Constant ((UriManager.name_of_uri uri),
479 (Some bo),ty,[],[])),u2);
480 (* FIXME: the variable list!! *)
481 prerr_endline "-------------> FINE";
485 | _ -> raise OpenConjecturesStillThere
488 (** save an unfinished proof on the filesystem *)
489 let save_unfinished_proof () =
490 let (xml, bodyxml) = ProofEngine.get_current_status_as_xml () in
491 let proof_file_type = Helm_registry.get "gtoplevel.proof_file_type" in
492 let proof_file = Helm_registry.get "gtoplevel.proof_file" in
493 Xml.pp ~gzip:false xml (Some proof_file_type) ;
495 (`Msg (`T ("Current proof type saved to " ^ proof_file_type))) ;
496 Xml.pp ~gzip:false bodyxml (Some proof_file) ;
498 (`Msg (`T ("Current proof body saved to " ^ proof_file)))
501 (* Used to typecheck the loaded proofs *)
502 let typecheck_loaded_proof metasenv bo ty =
503 let module T = CicTypeChecker in
506 (fun metasenv ((_,context,ty) as conj) ->
507 ignore (T.type_of_aux' metasenv context ty CicUniv.empty_ugraph) ;
510 ignore (T.type_of_aux' metasenv [] ty CicUniv.empty_ugraph) ;
511 ignore (T.type_of_aux' metasenv [] bo CicUniv.empty_ugraph)
514 let decompose_uris_choice_callback uris =
515 (* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
516 let module U = UriManager in
519 match CicUtil.term_of_uri uri with
520 | Cic.MutInd (uri, typeno, _) -> (uri, typeno, [])
522 (interactive_user_uri_choice
523 ~selection_mode:`MULTIPLE ~ok:"Ok" ~enable_button_for_non_vars:false
524 ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose"
526 (function (uri,typeno,_) ->
527 U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1)
532 let mk_fresh_name_callback metasenv context name ~typ =
534 match FreshNamesGenerator.mk_fresh_name ~subst:[] metasenv context name ~typ with
535 Cic.Name fresh_name -> fresh_name
536 | Cic.Anonymous -> assert false
539 GToolbox.input_string ~title:"Enter a fresh hypothesis name" ~text:fresh_name
540 ("Enter a fresh name for the hypothesis " ^
542 (List.map (function None -> None | Some (n,_) -> Some n) context))
544 Some fresh_name' -> Cic.Name fresh_name'
545 | None -> raise NoChoice
548 let refresh_proof (output : TermViewer.proof_viewer) =
550 let uri,currentproof =
551 match ProofEngine.get_proof () with
553 | Some (uri,metasenv,bo,ty) ->
554 ProofEngine.set_proof (Some (uri,metasenv,bo,ty)) ;
555 if List.length metasenv = 0 then
557 !qed_set_sensitive true ;
562 (*CSC: Wrong: [] is just plainly wrong *)
563 let uri = match uri with Some uri -> uri | _ -> assert false in
565 Cic.CurrentProof (UriManager.name_of_uri uri,metasenv,bo,ty,[],[]))
567 ignore (output#load_proof currentproof)
570 match ProofEngine.get_proof () with
572 | Some (uri,metasenv,bo,ty) ->
573 debug_print ("Offending proof: " ^
574 CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[],[])));
575 raise (InvokeTactics.RefreshProofException e)
577 let set_proof_engine_goal g =
578 ProofEngine.goal := g
581 let refresh_goals ?(empty_notebook=true) notebook =
583 match !ProofEngine.goal with
585 if empty_notebook then
587 notebook#remove_all_pages ~skip_switch_page_event:false ;
588 notebook#set_empty_page
591 notebook#proofw#unload
594 match ProofEngine.get_proof () with
596 | Some (_,metasenv,_,_) -> metasenv
599 List.find (function (m,_,_) -> m=metano) metasenv
601 let regenerate_notebook () =
602 let skip_switch_page_event =
604 (m,_,_)::_ when m = metano -> false
607 notebook#remove_all_pages ~skip_switch_page_event ;
608 List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
610 if empty_notebook then
612 regenerate_notebook () ;
613 notebook#set_current_page
614 ~may_skip_switch_page_event:false metano
618 notebook#set_current_page
619 ~may_skip_switch_page_event:true metano ;
620 notebook#proofw#load_sequent metasenv currentsequent ;
625 match !ProofEngine.goal with
630 match ProofEngine.get_proof () with
632 | Some (_,metasenv,_,_) -> metasenv
635 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
637 ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent);
638 raise (InvokeTactics.RefreshSequentException e)
640 debug_print ("Offending sequent " ^ string_of_int metano ^ " unknown.");
641 raise (InvokeTactics.RefreshSequentException e)
643 module InvokeTacticsCallbacks =
645 let sequent_viewer () = (rendering_window ())#notebook#proofw
646 let term_editor () = (rendering_window ())#inputt
647 let scratch_window () = (rendering_window ())#scratch_window
649 let refresh_proof () =
650 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
653 let refresh_goals () =
654 let notebook = (rendering_window ())#notebook in
655 refresh_goals notebook
657 let decompose_uris_choice_callback = decompose_uris_choice_callback
658 let mk_fresh_name_callback = mk_fresh_name_callback
659 let mqi_handle = mqi_handle
663 module InvokeTactics' = InvokeTactics.Make (InvokeTacticsCallbacks);;
665 (* Just to initialize the Hbugs module *)
666 module Ignore = Hbugs.Initialize (InvokeTactics');;
667 Hbugs.set_describe_hint_callback (fun hint ->
669 | Hbugs_types.Use_apply_Luke term -> check_window [term]
673 let dummy_uri = "/dummy.con"
675 (** load an unfinished proof from filesystem *)
676 let load_unfinished_proof () =
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 let proof_file_type = Helm_registry.get "gtoplevel.proof_file_type" in
688 let proof_file = Helm_registry.get "gtoplevel.proof_file" in
689 match CicParser.obj_of_xml proof_file_type (Some proof_file) with
690 Cic.CurrentProof (_,metasenv,bo,ty,_,_) ->
691 typecheck_loaded_proof metasenv bo ty ;
692 ProofEngine.set_proof (Some (Some uri, metasenv, bo, ty));
693 refresh_proof output ;
694 set_proof_engine_goal
697 | (metano,_,_)::_ -> Some metano
699 refresh_goals notebook ;
701 (`Msg (`T ("Current proof type loaded from " ^ proof_file_type)));
703 (`Msg (`T ("Current proof body loaded from " ^ proof_file))) ;
704 !save_set_sensitive true;
707 InvokeTactics.RefreshSequentException e ->
709 (`Error (`T ("Exception raised during the refresh of the " ^
710 "sequent: " ^ Printexc.to_string e)))
711 | InvokeTactics.RefreshProofException e ->
713 (`Error (`T ("Exception raised during the refresh of the " ^
714 "proof: " ^ Printexc.to_string e)))
717 (`Error (`T (Printexc.to_string e)))
720 let clear_aliases () =
721 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
722 inputt#environment :=
723 DisambiguatingParser.EnvironmentP3.of_string
724 DisambiguatingParser.EnvironmentP3.empty
727 let edit_aliases () =
728 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
729 let disambiguation_env = inputt#environment in
730 let chosen_aliases = ref None in
733 ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
735 GPack.vbox ~border_width:0 ~packing:window#add () in
736 let scrolled_window =
737 GBin.scrolled_window ~border_width:10
738 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
739 let input = GText.view ~editable:true ~width:400 ~height:100
740 ~packing:scrolled_window#add () in
742 GPack.hbox ~border_width:0
743 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
745 GButton.button ~label:"Ok"
746 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
748 GButton.button ~label:"Clear"
749 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
751 GButton.button ~label:"Cancel"
752 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
753 ignore (window#connect#destroy GMain.Main.quit) ;
754 ignore (cancelb#connect#clicked window#destroy) ;
755 ignore (clearb#connect#clicked (fun () ->
756 input#buffer#set_text DisambiguatingParser.EnvironmentP3.empty)) ;
757 ignore (okb#connect#clicked (fun () ->
758 chosen_aliases := Some (input#buffer#get_text ());
761 (input#buffer#insert ~iter:(input#buffer#get_iter_at_char 0)
762 (DisambiguatingParser.EnvironmentP3.to_string !disambiguation_env ^ "\n"));
765 match !chosen_aliases with
767 | Some raw_aliases ->
768 let new_disambiguation_env =
770 DisambiguatingParser.EnvironmentP3.of_string raw_aliases
774 ("Error while parsing aliases: " ^ Printexc.to_string e)));
777 disambiguation_env := new_disambiguation_env
781 let module L = LogicalOperations in
782 let module G = Gdome in
783 let notebook = (rendering_window ())#notebook in
784 let output = (rendering_window ())#output in
786 output#make_sequent_of_selected_term ;
787 refresh_proof output ;
788 refresh_goals notebook
790 InvokeTactics.RefreshSequentException e ->
792 (`Error (`T ("Exception raised during the refresh of the " ^
793 "sequent: " ^ Printexc.to_string e)))
794 | InvokeTactics.RefreshProofException e ->
796 (`Error (`T ("Exception raised during the refresh of the " ^
797 "proof: " ^ Printexc.to_string e)))
800 (`Error (`T (Printexc.to_string e)))
804 let module L = LogicalOperations in
805 let module G = Gdome in
806 let notebook = (rendering_window ())#notebook in
807 let output = (rendering_window ())#output in
809 output#focus_sequent_of_selected_term ;
810 refresh_goals notebook
812 InvokeTactics.RefreshSequentException e ->
814 (`Error (`T ("Exception raised during the refresh of the " ^
815 "sequent: " ^ Printexc.to_string e)))
816 | InvokeTactics.RefreshProofException e ->
818 (`Error (`T ("Exception raised during the refresh of the " ^
819 "proof: " ^ Printexc.to_string e)))
822 (`Error (`T (Printexc.to_string e)))
825 exception NoPrevGoal;;
826 exception NoNextGoal;;
829 let module L = LogicalOperations in
830 let module G = Gdome in
831 let notebook = (rendering_window ())#notebook in
832 let output = (rendering_window ())#output in
834 match ProofEngine.get_proof () with
836 | Some (_,metasenv,_,_) -> metasenv
839 refresh_goals ~empty_notebook:false notebook
841 InvokeTactics.RefreshSequentException e ->
843 (`Error (`T ("Exception raised during the refresh of the " ^
844 "sequent: " ^ Printexc.to_string e)))
847 (`Error (`T (Printexc.to_string e)))
851 show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
854 GWindow.window ~width:800 ~border_width:2 () in
855 let scrolled_window =
856 GBin.scrolled_window ~border_width:10 ~packing:window#add () in
858 GMathViewAux.single_selection_math_view
859 ~packing:scrolled_window#add ~width:600 ~height:400 ()
861 let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
862 let href = Gdome.domString "href" in
863 let show_in_show_window_obj uri obj =
865 let mml,(_,(ids_to_terms,ids_to_father_ids,ids_to_conjectures,
866 ids_to_hypotheses,_,_)) =
867 ApplyTransformation.mml_of_cic_object obj
869 window#set_title (UriManager.string_of_uri uri) ;
870 window#misc#hide () ; window#show () ;
871 mmlwidget#load_root mml#get_documentElement ;
875 (`Error (`T (Printexc.to_string e)))
877 let show_in_show_window_uri uri =
878 let obj,_ = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
879 show_in_show_window_obj uri obj
881 let show_in_show_window_callback mmlwidget ((n : Gdome.element option),_,_,_) =
885 if n'#hasAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href then
887 (n'#getAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href)#to_string
889 show_in_show_window_uri (UriManager.uri_of_string uri)
891 ignore (mmlwidget#action_toggle n')
894 mmlwidget#connect#click (show_in_show_window_callback mmlwidget)
896 show_in_show_window_obj, show_in_show_window_uri,
897 show_in_show_window_callback
900 exception NoObjectsLocated;;
902 let user_uri_choice ~title ~msg uris =
905 [] -> raise NoObjectsLocated
909 interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
914 String.sub uri 4 (String.length uri - 4)
917 let locate_callback id =
918 let uris = MetadataQuery.locate ~dbd id in
919 HelmLogger.log (`Msg (`T ("Locate Query: " ^ id))) ;
920 HelmLogger.log (`Msg (`T "Result:")) ;
921 List.iter (fun uri -> HelmLogger.log (`Msg (`T uri))) uris;
922 user_uri_choice ~title:"Ambiguous input."
923 ~msg:(sprintf "Ambiguous input \"%s\". Please, choose one interpetation:" id)
928 let input_or_locate_uri ~title =
929 let uri = ref None in
932 ~width:400 ~modal:true ~title ~border_width:2 () in
933 let vbox = GPack.vbox ~packing:window#add () in
935 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
937 GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
939 GEdit.entry ~editable:true
940 ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
942 GButton.button ~label:"Check"
943 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
944 let _ = checkb#misc#set_sensitive false in
946 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
948 GMisc.label ~text:"You can also enter an indentifier to locate:"
949 ~packing:(hbox2#pack ~padding:5) () in
951 GEdit.entry ~editable:true
952 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
954 GButton.button ~label:"Locate"
955 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
956 let _ = locateb#misc#set_sensitive false in
958 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
960 GButton.button ~label:"Ok"
961 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
962 let _ = okb#misc#set_sensitive false in
964 GButton.button ~label:"Cancel"
965 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
967 ignore (window#connect#destroy GMain.Main.quit) ;
969 (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
970 let check_callback () =
971 let uri = "cic:" ^ manual_input#text in
973 ignore (Http_getter.resolve' (UriManager.uri_of_string uri)) ;
974 HelmLogger.log (`Msg (`T "OK")) ;
977 Http_getter_types.Key_not_found _ ->
979 (`Error (`T ("URI " ^ uri ^
980 " does not correspond to any object."))) ;
982 | UriManager.IllFormedUri _ ->
984 (`Error (`T ("URI " ^ uri ^ " is not well-formed."))) ;
988 (`Error (`T (Printexc.to_string e))) ;
994 if check_callback () then
996 uri := Some manual_input#text ;
1000 ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1002 (manual_input#connect#changed
1004 if manual_input#text = "" then
1006 checkb#misc#set_sensitive false ;
1007 okb#misc#set_sensitive false
1011 checkb#misc#set_sensitive true ;
1012 okb#misc#set_sensitive true
1015 (locate_input#connect#changed
1016 (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1018 (locateb#connect#clicked
1020 let id = locate_input#text in
1021 manual_input#set_text (locate_callback id) ;
1022 locate_input#delete_text 0 (String.length id)
1027 None -> raise NoChoice
1028 | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1031 exception AmbiguousInput;;
1033 (* A WIDGET TO ENTER CIC TERMS *)
1035 module DisambiguateCallbacks =
1037 let interactive_user_uri_choice =
1038 fun ~selection_mode ?ok ?enable_button_for_non_vars ~title ~msg ~id ->
1039 interactive_user_uri_choice ~selection_mode ?ok
1040 ?enable_button_for_non_vars ~title ~msg
1041 let interactive_interpretation_choice = interactive_interpretation_choice
1042 let input_or_locate_uri ~title ?id () = input_or_locate_uri ~title
1046 module TermEditor' = ChosenTermEditor.Make (DisambiguateCallbacks);;
1048 (* OTHER FUNCTIONS *)
1051 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1054 GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1056 None -> raise NoChoice
1058 let uri = locate_callback input in
1063 (`Error (`T (Printexc.to_string e)))
1067 exception UriAlreadyInUse;;
1068 exception NotAUriToAConstant;;
1070 let new_inductive () =
1071 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1072 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1073 let notebook = (rendering_window ())#notebook in
1075 let chosen = ref false in
1076 let inductive = ref true in
1077 let paramsno = ref 0 in
1078 let get_uri = ref (function _ -> assert false) in
1079 let get_base_uri = ref (function _ -> assert false) in
1080 let get_names = ref (function _ -> assert false) in
1081 let get_types_and_cons = ref (function _ -> assert false) in
1082 let get_context_and_subst = ref (function _ -> assert false) in
1085 ~width:600 ~modal:true ~position:`CENTER
1086 ~title:"New Block of Mutual (Co)Inductive Definitions"
1087 ~border_width:2 () in
1088 let vbox = GPack.vbox ~packing:window#add () in
1090 GPack.hbox ~border_width:0
1091 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1093 GMisc.label ~text:"Enter the URI for the new block:"
1094 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1096 GEdit.entry ~editable:true
1097 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1099 GPack.hbox ~border_width:0
1100 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1104 "Enter the number of left parameters in every arity and constructor type:"
1105 ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1106 let paramsno_entry =
1107 GEdit.entry ~editable:true ~text:"0"
1108 ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1110 GPack.hbox ~border_width:0
1111 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1113 GMisc.label ~text:"Are the definitions inductive or coinductive?"
1114 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1116 GButton.radio_button ~label:"Inductive"
1117 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1119 GButton.radio_button ~label:"Coinductive"
1120 ~group:inductiveb#group
1121 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1123 GPack.hbox ~border_width:0
1124 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1126 GMisc.label ~text:"Enter the list of the names of the types:"
1127 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1129 GEdit.entry ~editable:true
1130 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1132 GPack.hbox ~border_width:0
1133 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1135 GButton.button ~label:"> Next"
1136 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1137 let _ = okb#misc#set_sensitive true in
1139 GButton.button ~label:"Abort"
1140 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1141 ignore (window#connect#destroy GMain.Main.quit) ;
1142 ignore (cancelb#connect#clicked window#destroy) ;
1146 (okb#connect#clicked
1149 let uristr = "cic:" ^ uri_entry#text in
1150 let namesstr = names_entry#text in
1151 let paramsno' = int_of_string (paramsno_entry#text) in
1152 match Str.split (Str.regexp " +") namesstr with
1154 | (he::tl) as names ->
1155 let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1158 ignore (Http_getter.resolve' uri) ;
1159 raise UriAlreadyInUse
1160 with Http_getter_types.Key_not_found _ ->
1161 get_uri := (function () -> uri) ;
1162 get_names := (function () -> names) ;
1163 inductive := inductiveb#active ;
1164 paramsno := paramsno' ;
1170 (`Error (`T (Printexc.to_string e)))
1178 GBin.frame ~label:name
1179 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1180 let vbox = GPack.vbox ~packing:frame#add () in
1181 let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1183 GMisc.label ~text:("Enter its type:")
1184 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1185 let scrolled_window =
1186 GBin.scrolled_window ~border_width:5
1187 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1189 TermEditor'.term_editor
1191 ~width:400 ~height:20 ~packing:scrolled_window#add
1192 ~share_environment_with:inputt ()
1193 ~isnotempty_callback:
1195 (*non_empty_type := b ;*)
1196 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1199 GPack.hbox ~border_width:0
1200 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1202 GMisc.label ~text:("Enter the list of its constructors:")
1203 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1204 let cons_names_entry =
1205 GEdit.entry ~editable:true
1206 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1207 (newinputt,cons_names_entry)
1210 vbox#remove hboxn#coerce ;
1212 GPack.hbox ~border_width:0
1213 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1215 GButton.button ~label:"> Next"
1216 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1218 GButton.button ~label:"Abort"
1219 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1220 ignore (cancelb#connect#clicked window#destroy) ;
1222 (okb#connect#clicked
1225 let names = !get_names () in
1226 let types_and_cons =
1228 (fun name (newinputt,cons_names_entry) ->
1229 let consnamesstr = cons_names_entry#text in
1230 let cons_names = Str.split (Str.regexp " +") consnamesstr in
1231 let metasenv,expr,ugraph =
1232 newinputt#get_metasenv_and_term ~context:[] ~metasenv:[]
1235 [] -> expr,cons_names
1236 | _ -> raise AmbiguousInput
1237 ) names type_widgets
1239 let uri = !get_uri () in
1241 (* Let's see if so far the definition is well-typed *)
1244 (* To test if the arities of the inductive types are well *)
1245 (* typed, we check the inductive block definition where *)
1246 (* no constructor is given to each type. *)
1249 (fun name (ty,cons) -> (name, !inductive, ty, []))
1250 names types_and_cons
1252 CicTypeChecker.typecheck_mutual_inductive_defs uri
1253 (tys,params,paramsno)
1255 get_context_and_subst :=
1259 (fun (context,subst) name (ty,_) ->
1261 (Some (Cic.Name name, Cic.Decl ty))::context,
1262 (Cic.MutInd (uri,!i,[]))::subst
1265 ) ([],[]) names types_and_cons) ;
1266 let types_and_cons' =
1268 (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1269 names types_and_cons
1271 get_types_and_cons := (function () -> types_and_cons') ;
1277 (`Error (`T (Printexc.to_string e)))
1280 and phase3 name cons =
1281 let get_cons_types = ref (function () -> assert false) in
1284 ~width:600 ~modal:true ~position:`CENTER
1285 ~title:(name ^ " Constructors")
1286 ~border_width:2 () in
1287 let vbox = GPack.vbox ~packing:window2#add () in
1288 let cons_type_widgets =
1290 (function consname ->
1292 GPack.hbox ~border_width:0
1293 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1295 GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1296 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1297 let scrolled_window =
1298 GBin.scrolled_window ~border_width:5
1299 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1301 TermEditor'.term_editor
1303 ~width:400 ~height:20 ~packing:scrolled_window#add
1304 ~share_environment_with:inputt ()
1305 ~isnotempty_callback:
1307 (* (*non_empty_type := b ;*)
1308 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1313 GPack.hbox ~border_width:0
1314 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1316 GButton.button ~label:"> Next"
1317 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1318 let _ = okb#misc#set_sensitive true in
1320 GButton.button ~label:"Abort"
1321 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1322 ignore (window2#connect#destroy GMain.Main.quit) ;
1323 ignore (cancelb#connect#clicked window2#destroy) ;
1325 (okb#connect#clicked
1329 let context,subst= !get_context_and_subst () in
1333 let metasenv,expr,ugraph =
1334 inputt#get_metasenv_and_term ~context ~metasenv:[]
1338 let undebrujined_expr =
1340 (fun expr t -> CicSubstitution.subst t expr) expr subst
1342 name, undebrujined_expr
1343 | _ -> raise AmbiguousInput
1344 ) cons cons_type_widgets
1346 get_cons_types := (function () -> cons_types) ;
1351 (`Error (`T (Printexc.to_string e)))
1355 let okb_pressed = !chosen in
1357 if (not okb_pressed) then
1360 assert false (* The control never reaches this point *)
1363 (!get_cons_types ())
1366 (* No more phases left or Abort pressed *)
1372 let uri = !get_uri () in
1375 let tys = !get_types_and_cons () in
1376 let obj = Cic.InductiveDefinition(tys,params,!paramsno,[]) in
1380 debug_print (CicPp.ppobj obj);
1381 CicTypeChecker.typecheck_mutual_inductive_defs uri
1382 (tys,params,!paramsno) CicUniv.empty_ugraph
1385 debug_print "Offending mutual (co)inductive type declaration:" ;
1386 debug_print (CicPp.ppobj obj) ;
1387 (* I think we should fail here! *)
1388 CicUniv.empty_ugraph
1391 (* We already know that obj is well-typed. We need to add it to the *)
1392 (* environment in order to compute the inner-types without having to *)
1393 (* debrujin it or having to modify lots of other functions to avoid *)
1394 (* asking the environment for the MUTINDs we are defining now. *)
1396 (* u should be cleaned before adding it to the env *)
1397 CicEnvironment.put_inductive_definition uri (obj,u) ;
1399 (* TASSI: FIXME we should save the cleaned u here *)
1400 show_in_show_window_obj uri obj
1404 (`Error (`T (Printexc.to_string e)))
1408 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1409 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1410 let notebook = (rendering_window ())#notebook in
1412 let chosen = ref false in
1413 let get_metasenv_and_term = ref (function _ -> assert false) in
1414 let get_uri = ref (function _ -> assert false) in
1415 let non_empty_type = ref false in
1418 ~width:600 ~modal:true ~title:"New Proof or Definition"
1419 ~border_width:2 () in
1420 let vbox = GPack.vbox ~packing:window#add () in
1422 GPack.hbox ~border_width:0
1423 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1425 GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1426 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1428 GEdit.entry ~editable:true
1429 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1430 uri_entry#set_text dummy_uri;
1431 uri_entry#select_region ~start:1 ~stop:(String.length dummy_uri);
1433 GPack.hbox ~border_width:0
1434 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1436 GMisc.label ~text:"Enter the theorem or definition type:"
1437 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1438 let scrolled_window =
1439 GBin.scrolled_window ~border_width:5
1440 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1441 (* the content of the scrolled_window is moved below (see comment) *)
1443 GPack.hbox ~border_width:0
1444 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1446 GButton.button ~label:"Ok"
1447 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1448 let _ = okb#misc#set_sensitive false in
1450 GButton.button ~label:"Cancel"
1451 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1452 (* moved here to have visibility of the ok button *)
1454 TermEditor'.term_editor
1456 ~width:400 ~height:100 ~packing:scrolled_window#add
1457 ~share_environment_with:inputt ()
1458 ~isnotempty_callback:
1460 non_empty_type := b ;
1461 okb#misc#set_sensitive (b && uri_entry#text <> ""))
1464 newinputt#set_term inputt#get_as_string ;
1467 uri_entry#connect#changed
1469 okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1471 ignore (window#connect#destroy GMain.Main.quit) ;
1472 ignore (cancelb#connect#clicked window#destroy) ;
1474 (okb#connect#clicked
1478 let metasenv,parsed,ugraph = newinputt#get_metasenv_and_term [] [] in
1479 let uristr = "cic:" ^ uri_entry#text in
1480 let uri = UriManager.uri_of_string uristr in
1481 if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1482 raise NotAUriToAConstant
1486 ignore (Http_getter.resolve' uri) ;
1487 raise UriAlreadyInUse
1488 with Http_getter_types.Key_not_found _ ->
1489 get_metasenv_and_term := (function () -> metasenv,parsed) ;
1490 get_uri := (function () -> uri) ;
1496 (`Error (`T (Printexc.to_string e)))
1502 let metasenv,expr = !get_metasenv_and_term () in
1503 let _ = CicTypeChecker.type_of_aux' metasenv [] expr in
1504 ProofEngine.set_proof
1505 (Some (Some (!get_uri ()), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr));
1506 set_proof_engine_goal (Some 1) ;
1507 refresh_goals notebook ;
1508 refresh_proof output ;
1509 !save_set_sensitive true ;
1511 ProofEngine.intros ~mk_fresh_name_callback () ;
1512 refresh_goals notebook ;
1513 refresh_proof output
1515 InvokeTactics.RefreshSequentException e ->
1517 (`Error (`T ("Exception raised during the refresh of the " ^
1518 "sequent: " ^ Printexc.to_string e)))
1519 | InvokeTactics.RefreshProofException e ->
1521 (`Error (`T ("Exception raised during the refresh of the " ^
1522 "proof: " ^ Printexc.to_string e)))
1525 (`Error (`T (Printexc.to_string e)))
1528 let check_term_in_scratch scratch_window metasenv context expr =
1531 CicTypeChecker.type_of_aux' metasenv context expr CicUniv.empty_ugraph
1533 let expr = Cic.Cast (expr,ty) in
1534 scratch_window#show () ;
1535 scratch_window#set_term expr ;
1536 scratch_window#set_context context ;
1537 scratch_window#set_metasenv metasenv ;
1538 scratch_window#sequent_viewer#load_sequent metasenv (111,context,expr)
1541 print_endline ("? " ^ CicPp.ppterm expr) ;
1545 let check scratch_window () =
1546 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1548 match ProofEngine.get_proof () with
1550 | Some (_,metasenv,_,_) -> metasenv
1553 match !ProofEngine.goal with
1556 let (_,canonical_context,_) =
1557 List.find (function (m,_,_) -> m=metano) metasenv
1562 let metasenv',expr,ugraph =
1563 inputt#get_metasenv_and_term context metasenv
1565 check_term_in_scratch scratch_window metasenv' context expr
1569 (`Error (`T (Printexc.to_string e)))
1574 show_in_show_window_uri (input_or_locate_uri ~title:"Show")
1578 (`Error (`T (Printexc.to_string e)))
1581 exception NotADefinition;;
1584 let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1585 let notebook = (rendering_window ())#notebook in
1587 let uri = input_or_locate_uri ~title:"Open" in
1588 ignore(CicTypeChecker.typecheck uri CicUniv.empty_ugraph);
1589 (* TASSI: typecheck mette la uri nell'env... cosa fa la open_ ?*)
1590 let metasenv,bo,ty =
1591 match fst(CicEnvironment.get_cooked_obj CicUniv.empty_ugraph uri ) with
1592 Cic.Constant (_,Some bo,ty,_,_) -> [],bo,ty
1593 | Cic.CurrentProof (_,metasenv,bo,ty,_,_) -> metasenv,bo,ty
1596 | Cic.InductiveDefinition _ -> raise NotADefinition
1598 ProofEngine.set_proof (Some (Some uri, metasenv, bo, ty)) ;
1599 set_proof_engine_goal None ;
1600 refresh_goals notebook ;
1601 refresh_proof output ;
1602 !save_set_sensitive true
1604 InvokeTactics.RefreshSequentException e ->
1606 (`Error (`T ("Exception raised during the refresh of the " ^
1607 "sequent: " ^ Printexc.to_string e)))
1608 | InvokeTactics.RefreshProofException e ->
1610 (`Error (`T ("Exception raised during the refresh of the " ^
1611 "proof: " ^ Printexc.to_string e)))
1614 (`Error (`T (Printexc.to_string e)))
1617 let show_query_results results =
1620 ~modal:false ~title:"Query results." ~border_width:2 () in
1621 let vbox = GPack.vbox ~packing:window#add () in
1623 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1626 ~text:"Click on a URI to show that object"
1627 ~packing:hbox#add () in
1628 let scrolled_window =
1629 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1630 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1631 let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
1634 (function (uri,_) ->
1638 clist#set_row ~selectable:false n
1641 clist#columns_autosize () ;
1643 (clist#connect#select_row
1644 (fun ~row ~column ~event ->
1645 let (uristr,_) = List.nth results row in
1646 match CicUtil.term_of_uri uristr with
1647 | Cic.Const (uri, _)
1649 | Cic.MutInd (uri, _, _)
1650 | Cic.MutConstruct (uri, _, _, _) ->
1651 show_in_show_window_uri uri
1658 let refine_constraints (must_obj,must_rel,must_sort) =
1659 let chosen = ref false in
1660 let use_only = ref false in
1663 ~modal:true ~title:"Constraints refinement."
1664 ~width:800 ~border_width:2 () in
1665 let vbox = GPack.vbox ~packing:window#add () in
1667 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1670 ~text: "\"Only\" constraints can be enforced or not."
1671 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1673 GButton.toggle_button ~label:"Enforce \"only\" constraints"
1674 ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1677 (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
1678 (* Notebook for the constraints choice *)
1680 GPack.notebook ~scrollable:true
1681 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1682 (* Rel constraints *)
1685 ~text: "Constraints on Rels" () in
1687 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1690 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1693 ~text: "You can now specify the constraints on Rels."
1694 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1695 let expected_height = 25 * (List.length must_rel + 2) in
1696 let height = if expected_height > 400 then 400 else expected_height in
1697 let scrolled_window =
1698 GBin.scrolled_window ~border_width:10 ~height ~width:600
1699 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1700 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1701 let mk_depth_button (hbox:GPack.box) d =
1702 let mutable_ref = ref (Some d) in
1704 GButton.toggle_button
1705 ~label:("depth = " ^ string_of_int d)
1707 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1710 (depthb#connect#toggled
1712 let sel_depth = if depthb#active then Some d else None in
1713 mutable_ref := sel_depth
1716 let rel_constraints =
1721 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1724 ~text:(MQGU.text_of_position (p:>MQGT.full_position))
1725 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1727 | `MainHypothesis None
1728 | `MainConclusion None -> p, ref None
1729 | `MainHypothesis (Some depth')
1730 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth'
1732 (* Sort constraints *)
1735 ~text: "Constraints on Sorts" () in
1737 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1740 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1743 ~text: "You can now specify the constraints on Sorts."
1744 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1745 let expected_height = 25 * (List.length must_sort + 2) in
1746 let height = if expected_height > 400 then 400 else expected_height in
1747 let scrolled_window =
1748 GBin.scrolled_window ~border_width:10 ~height ~width:600
1749 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1750 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1751 let sort_constraints =
1753 (function (p, sort) ->
1756 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1759 ~text:(MQGU.text_of_sort sort ^ " " ^ MQGU.text_of_position (p:>MQGT.full_position))
1760 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1762 | `MainHypothesis None
1763 | `MainConclusion None -> p, ref None, sort
1764 | `MainHypothesis (Some depth')
1765 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth', sort
1767 (* Obj constraints *)
1770 ~text: "Constraints on constants" () in
1772 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1775 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1778 ~text: "You can now specify the constraints on constants."
1779 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1780 let expected_height = 25 * (List.length must_obj + 2) in
1781 let height = if expected_height > 400 then 400 else expected_height in
1782 let scrolled_window =
1783 GBin.scrolled_window ~border_width:10 ~height ~width:600
1784 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1785 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1786 let obj_constraints =
1788 (function (p, uri) ->
1791 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1794 ~text:(uri ^ " " ^ (MQGU.text_of_position p))
1795 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1800 | `MainHypothesis None
1801 | `MainConclusion None -> p, ref None, uri
1802 | `MainHypothesis (Some depth')
1803 | `MainConclusion (Some depth') -> p, mk_depth_button hbox depth', uri
1805 (* Confirm/abort buttons *)
1807 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1809 GButton.button ~label:"Ok"
1810 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1812 GButton.button ~label:"Abort"
1813 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1815 ignore (window#connect#destroy GMain.Main.quit) ;
1816 ignore (cancelb#connect#clicked window#destroy) ;
1818 (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
1819 window#set_position `CENTER ;
1823 let chosen_must_rel =
1825 (function (position, ref_depth) -> MQGU.set_main_position position !ref_depth)
1828 let chosen_must_sort =
1830 (function (position, ref_depth, sort) ->
1831 MQGU.set_main_position position !ref_depth,sort)
1834 let chosen_must_obj =
1836 (function (position, ref_depth, uri) -> MQGU.set_full_position position !ref_depth, uri)
1839 (chosen_must_obj,chosen_must_rel,chosen_must_sort),
1841 (*CSC: ???????????????????????? I assume that must and only are the same... *)
1842 Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
1850 let completeSearchPattern () =
1851 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1853 let metasenv,expr,ugraph =
1854 inputt#get_metasenv_and_term ~context:[] ~metasenv:[] in
1855 let must = CGSearchPattern.get_constraints expr in
1856 let must',only = refine_constraints must in
1858 MQG.query_of_constraints (Some CGSearchPattern.universe) must' only
1860 let results = MQI.execute mqi_handle query in
1861 show_query_results results
1865 (`Error (`T (Printexc.to_string e)))
1868 let insertQuery () =
1870 let chosen = ref None in
1873 ~modal:true ~title:"Insert Query (Experts Only)" ~border_width:2 () in
1874 let vbox = GPack.vbox ~packing:window#add () in
1876 GMisc.label ~text:"Insert Query. For Experts Only."
1877 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1878 let scrolled_window =
1879 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1880 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1881 let input = GText.view ~editable:true
1882 ~packing:scrolled_window#add () in
1884 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1886 GButton.button ~label:"Ok"
1887 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1889 GButton.button ~label:"Load from file..."
1890 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1892 GButton.button ~label:"Abort"
1893 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1894 ignore (window#connect#destroy GMain.Main.quit) ;
1895 ignore (cancelb#connect#clicked window#destroy) ;
1897 (okb#connect#clicked
1899 chosen := Some (input#buffer#get_text ()) ; window#destroy ())) ;
1901 (loadb#connect#clicked
1904 GToolbox.select_file ~title:"Select Query File" ()
1908 let inch = open_in filename in
1909 let rec read_file () =
1911 let line = input_line inch in
1912 line ^ "\n" ^ read_file ()
1916 let text = read_file () in
1917 input#buffer#delete input#buffer#start_iter input#buffer#end_iter ;
1918 ignore (input#buffer#insert text))) ;
1919 window#set_position `CENTER ;
1926 MQI.execute mqi_handle (MQueryUtil.query_of_text (Lexing.from_string q))
1928 show_query_results results
1932 (`Error (`T (Printexc.to_string e)))
1935 let choose_must list_of_must only =
1936 let chosen = ref None in
1937 let user_constraints = ref [] in
1940 ~modal:true ~title:"Query refinement." ~border_width:2 () in
1941 let vbox = GPack.vbox ~packing:window#add () in
1943 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1947 ("You can now specify the genericity of the query. " ^
1948 "The more generic the slower.")
1949 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1951 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1955 "Suggestion: start with faster queries before moving to more generic ones."
1956 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1958 GPack.notebook ~scrollable:true
1959 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1962 let last = List.length list_of_must in
1968 (if !page = 1 then "More generic" else
1969 if !page = last then "More precise" else " ") () in
1970 let expected_height = 25 * (List.length must + 2) in
1971 let height = if expected_height > 400 then 400 else expected_height in
1972 let scrolled_window =
1973 GBin.scrolled_window ~border_width:10 ~height ~width:600
1974 ~packing:(notebook#append_page ~tab_label:label#coerce) () in
1976 GList.clist ~columns:2 ~packing:scrolled_window#add
1977 ~titles:["URI" ; "Position"] ()
1981 (function (position, uri) ->
1984 [uri; MQGUtil.text_of_position position]
1986 clist#set_row ~selectable:false n
1989 clist#columns_autosize ()
1992 let label = GMisc.label ~text:"User provided" () in
1994 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
1996 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1999 ~text:"Select the constraints that must be satisfied and press OK."
2000 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2001 let expected_height = 25 * (List.length only + 2) in
2002 let height = if expected_height > 400 then 400 else expected_height in
2003 let scrolled_window =
2004 GBin.scrolled_window ~border_width:10 ~height ~width:600
2005 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2007 GList.clist ~columns:2 ~packing:scrolled_window#add
2008 ~selection_mode:`MULTIPLE
2009 ~titles:["URI" ; "Position"] ()
2013 (function (position, uri) ->
2016 [uri; MQGUtil.text_of_position position]
2018 clist#set_row ~selectable:true n
2021 clist#columns_autosize () ;
2023 (clist#connect#select_row
2024 (fun ~row ~column ~event ->
2025 user_constraints := (List.nth only row)::!user_constraints)) ;
2027 (clist#connect#unselect_row
2028 (fun ~row ~column ~event ->
2031 (function uri -> uri != (List.nth only row)) !user_constraints)) ;
2034 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2036 GButton.button ~label:"Ok"
2037 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2039 GButton.button ~label:"Abort"
2040 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2042 ignore (window#connect#destroy GMain.Main.quit) ;
2043 ignore (cancelb#connect#clicked window#destroy) ;
2045 (okb#connect#clicked
2046 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2047 window#set_position `CENTER ;
2051 None -> raise NoChoice
2053 if n = List.length list_of_must then
2054 (* user provided constraints *)
2057 List.nth list_of_must n
2060 let searchPattern () =
2061 let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
2064 match ProofEngine.get_proof () with
2065 None -> assert false
2066 | Some proof -> proof
2068 match !ProofEngine.goal with
2071 let uris' = List.map fst (MetadataQuery.hint ~dbd (proof, metano)) in
2073 user_uri_choice ~title:"Ambiguous input."
2074 ~msg: "Many lemmas can be successfully applied. Please, choose one:"
2077 inputt#set_term uri' ;
2078 InvokeTactics'.apply ()
2082 (`Error (`T (Printexc.to_string e)))
2085 let choose_selection mmlwidget (element : Gdome.element option) =
2086 let module G = Gdome in
2087 let rec aux element =
2088 if element#hasAttributeNS
2089 ~namespaceURI:Misc.helm_ns
2090 ~localName:(G.domString "xref")
2092 mmlwidget#set_selection (Some element)
2095 match element#get_parentNode with
2096 None -> assert false
2097 (*CSC: OCAML DIVERGES!
2098 | Some p -> aux (new G.element_of_node p)
2100 | Some p -> aux (new Gdome.element_of_node p)
2102 GdomeInit.DOMCastException _ ->
2104 "******* trying to select above the document root ********"
2108 | None -> mmlwidget#set_selection None
2111 (* STUFF TO BUILD THE GTK INTERFACE *)
2113 (* Stuff for the widget settings *)
2116 let export_to_postscript output =
2117 let lastdir = ref (Unix.getcwd ()) in
2120 GToolbox.select_file ~title:"Export to PostScript"
2121 ~dir:lastdir ~filename:"screenshot.ps" ()
2125 (output :> GMathView.math_view)#export_to_postscript
2126 ~filename:filename ();
2131 let activate_t1 output button_set_anti_aliasing
2132 button_set_transparency export_to_postscript_menu_item
2135 let is_set = button_t1#active in
2136 output#set_font_manager_type
2137 ~fm_type:(if is_set then `font_manager_t1 else `font_manager_gtk) ;
2140 button_set_anti_aliasing#misc#set_sensitive true ;
2141 button_set_transparency#misc#set_sensitive true ;
2142 export_to_postscript_menu_item#misc#set_sensitive true ;
2146 button_set_anti_aliasing#misc#set_sensitive false ;
2147 button_set_transparency#misc#set_sensitive false ;
2148 export_to_postscript_menu_item#misc#set_sensitive false ;
2152 let set_anti_aliasing output button_set_anti_aliasing () =
2153 output#set_anti_aliasing button_set_anti_aliasing#active
2156 let set_transparency output button_set_transparency () =
2157 output#set_transparency button_set_transparency#active
2161 let changefont output font_size_spinb () =
2162 output#set_font_size font_size_spinb#value_as_int
2165 let set_log_verbosity output log_verbosity_spinb () =
2166 output#set_log_verbosity log_verbosity_spinb#value_as_int
2169 class settings_window output sw
2170 export_to_postscript_menu_item selection_changed_callback
2172 let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2174 GPack.vbox ~packing:settings_window#add () in
2177 ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2178 ~border_width:5 ~packing:vbox#add () in
2180 GButton.toggle_button ~label:"activate t1 fonts"
2181 ~packing:(table#attach ~left:0 ~top:0) () in
2182 let button_set_anti_aliasing =
2183 GButton.toggle_button ~label:"set_anti_aliasing"
2184 ~packing:(table#attach ~left:0 ~top:1) () in
2185 let button_set_transparency =
2186 GButton.toggle_button ~label:"set_transparency"
2187 ~packing:(table#attach ~left:2 ~top:1) () in
2190 ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2191 ~border_width:5 ~packing:vbox#add () in
2192 let font_size_label =
2193 GMisc.label ~text:"font size:"
2194 ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2195 let font_size_spinb =
2197 GData.adjustment ~value:(float_of_int output#get_font_size)
2198 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2201 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2202 let log_verbosity_label =
2203 GMisc.label ~text:"log verbosity:"
2204 ~packing:(table#attach ~left:0 ~top:1) () in
2205 let log_verbosity_spinb =
2207 GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2210 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2212 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2214 GButton.button ~label:"Close"
2215 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2217 method show = settings_window#show
2219 button_set_anti_aliasing#misc#set_sensitive false ;
2220 button_set_transparency#misc#set_sensitive false ;
2221 (* Signals connection *)
2223 ignore(button_t1#connect#clicked
2224 (activate_t1 output button_set_anti_aliasing
2225 button_set_transparency export_to_postscript_menu_item button_t1)) ;
2227 ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2229 ignore(button_set_anti_aliasing#connect#toggled
2230 (set_anti_aliasing output button_set_anti_aliasing));
2231 ignore(button_set_transparency#connect#toggled
2232 (set_transparency output button_set_transparency)) ;
2234 ignore(log_verbosity_spinb#connect#changed
2235 (set_log_verbosity output log_verbosity_spinb)) ;
2236 ignore(closeb#connect#clicked settings_window#misc#hide)
2239 (* Scratch window *)
2241 class scratch_window =
2244 ~title:"MathML viewer"
2245 ~border_width:2 () in
2247 GPack.vbox ~packing:window#add () in
2249 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2251 GButton.button ~label:"Whd"
2252 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2254 GButton.button ~label:"Reduce"
2255 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2257 GButton.button ~label:"Simpl"
2258 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2259 let scrolled_window =
2260 GBin.scrolled_window ~border_width:10
2261 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2262 let sequent_viewer =
2263 TermViewer.sequent_viewer
2264 ~mml_of_cic_sequent:ApplyTransformation.mml_of_cic_sequent
2265 ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
2267 val mutable term = Cic.Rel 1 (* dummy value *)
2268 val mutable context = ([] : Cic.context) (* dummy value *)
2269 val mutable metasenv = ([] : Cic.metasenv) (* dummy value *)
2270 method sequent_viewer = sequent_viewer
2271 method show () = window#misc#hide () ; window#show ()
2273 method set_term t = term <- t
2274 method context = context
2275 method set_context t = context <- t
2276 method metasenv = metasenv
2277 method set_metasenv t = metasenv <- t
2280 (sequent_viewer#connect#selection_changed (choose_selection sequent_viewer));
2281 ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
2282 ignore(whdb#connect#clicked InvokeTactics'.whd_in_scratch) ;
2283 ignore(reduceb#connect#clicked InvokeTactics'.reduce_in_scratch) ;
2284 ignore(simplb#connect#clicked InvokeTactics'.simpl_in_scratch)
2287 let open_contextual_menu_for_selected_terms mmlwidget infos =
2288 let button = GdkEvent.Button.button infos in
2289 let terms_selected = List.length mmlwidget#get_selections > 0 in
2292 let time = GdkEvent.Button.time infos in
2293 let menu = GMenu.menu () in
2294 let f = new GMenu.factory menu in
2296 f#add_item "Whd" ~key:GdkKeysyms._W ~callback:InvokeTactics'.whd in
2297 let reduce_menu_item =
2298 f#add_item "Reduce" ~key:GdkKeysyms._R ~callback:InvokeTactics'.reduce in
2299 let simpl_menu_item =
2300 f#add_item "Simpl" ~key:GdkKeysyms._S ~callback:InvokeTactics'.simpl in
2301 let _ = f#add_separator () in
2302 let generalize_menu_item =
2303 f#add_item "Generalize"
2304 ~key:GdkKeysyms._G ~callback:InvokeTactics'.generalize in
2305 let _ = f#add_separator () in
2306 let clear_menu_item =
2307 f#add_item "Clear" ~key:GdkKeysyms._C ~callback:InvokeTactics'.clear in
2308 let clearbody_menu_item =
2309 f#add_item "ClearBody"
2310 ~key:GdkKeysyms._B ~callback:InvokeTactics'.clearbody
2312 whd_menu_item#misc#set_sensitive terms_selected ;
2313 reduce_menu_item#misc#set_sensitive terms_selected ;
2314 simpl_menu_item#misc#set_sensitive terms_selected ;
2315 generalize_menu_item#misc#set_sensitive terms_selected ;
2316 clear_menu_item#misc#set_sensitive terms_selected ;
2317 clearbody_menu_item#misc#set_sensitive terms_selected ;
2318 menu#popup ~button ~time
2324 let vbox1 = GPack.vbox () in
2326 val mutable proofw_ref = None
2327 val mutable compute_ref = None
2329 Lazy.force self#compute ;
2330 match proofw_ref with
2331 None -> assert false
2332 | Some proofw -> proofw
2333 method content = vbox1
2335 match compute_ref with
2336 None -> assert false
2337 | Some compute -> compute
2341 let scrolled_window1 =
2342 GBin.scrolled_window ~border_width:10
2343 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2345 TermViewer.sequent_viewer
2346 ~mml_of_cic_sequent:ApplyTransformation.mml_of_cic_sequent
2347 ~width:400 ~height:275 ~packing:(scrolled_window1#add) () in
2348 let _ = proofw_ref <- Some proofw in
2350 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2352 GButton.button ~label:"Ring"
2353 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2355 GButton.button ~label:"Fourier"
2356 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2358 GButton.button ~label:"Reflexivity"
2359 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2361 GButton.button ~label:"Symmetry"
2362 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2364 GButton.button ~label:"Assumption"
2365 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2366 let contradictionb =
2367 GButton.button ~label:"Contradiction"
2368 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2370 GButton.button ~label:"Auto"
2371 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2373 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2375 GButton.button ~label:"Exists"
2376 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2378 GButton.button ~label:"Split"
2379 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2381 GButton.button ~label:"Left"
2382 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2384 GButton.button ~label:"Right"
2385 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2386 let searchpatternb =
2387 GButton.button ~label:"SearchPattern_Apply"
2388 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2390 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2392 GButton.button ~label:"Exact"
2393 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2395 GButton.button ~label:"Intros"
2396 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2398 GButton.button ~label:"Apply"
2399 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2400 let elimintrossimplb =
2401 GButton.button ~label:"ElimIntrosSimpl"
2402 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2404 GButton.button ~label:"ElimType"
2405 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2407 GButton.button ~label:"Fold_whd"
2408 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2410 GButton.button ~label:"Fold_reduce"
2411 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2413 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2415 GButton.button ~label:"Fold_simpl"
2416 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2418 GButton.button ~label:"Cut"
2419 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2421 GButton.button ~label:"Change"
2422 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2424 GButton.button ~label:"Let ... In"
2425 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2427 GButton.button ~label:"RewriteSimpl ->"
2428 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2429 let rewritebacksimplb =
2430 GButton.button ~label:"RewriteSimpl <-"
2431 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2433 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2435 GButton.button ~label:"Absurd"
2436 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2438 GButton.button ~label:"Decompose"
2439 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2441 GButton.button ~label:"Transitivity"
2442 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2444 GButton.button ~label:"Replace"
2445 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2447 GButton.button ~label:"Injection"
2448 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2450 GButton.button ~label:"Discriminate"
2451 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2452 (* Zack: spostare in una toolbar
2454 GButton.button ~label:"Generalize"
2455 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2457 GButton.button ~label:"ClearBody"
2458 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2460 GButton.button ~label:"Clear"
2461 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2463 GButton.button ~label:"Whd"
2464 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2466 GButton.button ~label:"Reduce"
2467 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2469 GButton.button ~label:"Simpl"
2470 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2473 ignore(exactb#connect#clicked InvokeTactics'.exact) ;
2474 ignore(applyb#connect#clicked InvokeTactics'.apply) ;
2475 ignore(elimintrossimplb#connect#clicked InvokeTactics'.elimintrossimpl) ;
2476 ignore(elimtypeb#connect#clicked InvokeTactics'.elimtype) ;
2477 ignore(foldwhdb#connect#clicked InvokeTactics'.fold_whd) ;
2478 ignore(foldreduceb#connect#clicked InvokeTactics'.fold_reduce) ;
2479 ignore(foldsimplb#connect#clicked InvokeTactics'.fold_simpl) ;
2480 ignore(cutb#connect#clicked InvokeTactics'.cut) ;
2481 ignore(changeb#connect#clicked InvokeTactics'.change) ;
2482 ignore(letinb#connect#clicked InvokeTactics'.letin) ;
2483 ignore(ringb#connect#clicked InvokeTactics'.ring) ;
2484 ignore(fourierb#connect#clicked InvokeTactics'.fourier) ;
2485 ignore(rewritesimplb#connect#clicked InvokeTactics'.rewritesimpl) ;
2486 ignore(rewritebacksimplb#connect#clicked InvokeTactics'.rewritebacksimpl) ;
2487 ignore(replaceb#connect#clicked InvokeTactics'.replace) ;
2488 ignore(reflexivityb#connect#clicked InvokeTactics'.reflexivity) ;
2489 ignore(symmetryb#connect#clicked InvokeTactics'.symmetry) ;
2490 ignore(transitivityb#connect#clicked InvokeTactics'.transitivity) ;
2491 ignore(existsb#connect#clicked InvokeTactics'.exists) ;
2492 ignore(splitb#connect#clicked InvokeTactics'.split) ;
2493 ignore(leftb#connect#clicked InvokeTactics'.left) ;
2494 ignore(rightb#connect#clicked InvokeTactics'.right) ;
2495 ignore(assumptionb#connect#clicked InvokeTactics'.assumption) ;
2496 ignore(absurdb#connect#clicked InvokeTactics'.absurd) ;
2497 ignore(contradictionb#connect#clicked InvokeTactics'.contradiction) ;
2498 ignore(introsb#connect#clicked InvokeTactics'.intros) ;
2499 ignore(decomposeb#connect#clicked InvokeTactics'.decompose) ;
2500 ignore(searchpatternb#connect#clicked searchPattern) ;
2501 ignore(injectionb#connect#clicked InvokeTactics'.injection) ;
2502 ignore(discriminateb#connect#clicked InvokeTactics'.discriminate) ;
2503 ignore(autob#connect#clicked InvokeTactics'.auto) ;
2504 (* Zack: spostare in una toolbar
2505 ignore(whdb#connect#clicked whd) ;
2506 ignore(reduceb#connect#clicked reduce) ;
2507 ignore(simplb#connect#clicked simpl) ;
2508 ignore(clearbodyb#connect#clicked clearbody) ;
2509 ignore(clearb#connect#clicked clear) ;
2510 ignore(generalizeb#connect#clicked generalize) ;
2512 ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
2514 ((new GObj.event_ops proofw#as_widget)#connect#button_press
2515 (open_contextual_menu_for_selected_terms proofw)) ;
2521 let vbox1 = GPack.vbox () in
2522 let scrolled_window1 =
2523 GBin.scrolled_window ~border_width:10
2524 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2526 TermViewer.sequent_viewer
2527 ~mml_of_cic_sequent:ApplyTransformation.mml_of_cic_sequent
2528 ~width:400 ~height:275 ~packing:(scrolled_window1#add) () in
2530 method proofw = (assert false : TermViewer.sequent_viewer)
2531 method content = vbox1
2532 method compute = (assert false : unit)
2536 let empty_page = new empty_page;;
2540 val notebook = GPack.notebook ()
2542 val mutable skip_switch_page_event = false
2543 val mutable empty = true
2544 method notebook = notebook
2546 let new_page = new page () in
2548 pages := !pages @ [n,lazy (setgoal n),new_page] ;
2549 notebook#append_page
2550 ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
2551 new_page#content#coerce
2552 method remove_all_pages ~skip_switch_page_event:skip =
2554 notebook#remove_page 0 (* let's remove the empty page *)
2556 List.iter (function _ -> notebook#remove_page 0) !pages ;
2558 skip_switch_page_event <- skip
2559 method set_current_page ~may_skip_switch_page_event n =
2560 let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
2561 let new_page = notebook#page_num page#content#coerce in
2562 if may_skip_switch_page_event && new_page <> notebook#current_page then
2563 skip_switch_page_event <- true ;
2564 notebook#goto_page new_page
2565 method set_empty_page =
2568 notebook#append_page
2569 ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
2570 empty_page#content#coerce
2572 let (_,_,page) = List.nth !pages notebook#current_page in
2576 (notebook#connect#switch_page
2578 let skip = skip_switch_page_event in
2579 skip_switch_page_event <- false ;
2582 let (metano,setgoal,page) = List.nth !pages i in
2583 set_proof_engine_goal (Some metano) ;
2584 Lazy.force (page#compute) ;
2586 if notify_hbugs_on_goal_change then
2593 let dump_environment () =
2595 let oc = open_out (Helm_registry.get "gtoplevel.environment_file") in
2596 HelmLogger.log (`Msg (`T "Dumping environment ..."));
2597 CicEnvironment.dump_to_channel oc;
2598 HelmLogger.log (`Msg (`T "... done!")) ;
2602 (`Error (`T (Printf.sprintf "Dump failure, uncaught exception:%s"
2603 (Printexc.to_string exc))))
2605 let restore_environment () =
2607 let ic = open_in (Helm_registry.get "gtoplevel.environment_file") in
2608 HelmLogger.log (`Msg (`T "Restoring environment ... "));
2609 CicEnvironment.restore_from_channel ic;
2610 HelmLogger.log (`Msg (`T "... done!"));
2614 (`Error (`T (Printf.sprintf "Restore failure, uncaught exception:%s"
2615 (Printexc.to_string exc))))
2620 class rendering_window output (notebook : notebook) =
2621 let scratch_window = new scratch_window in
2624 ~title:"gTopLevel - Helm's Proof Assistant"
2625 ~border_width:0 ~allow_shrink:false () in
2626 let vbox_for_menu = GPack.vbox ~packing:window#add () in
2628 let handle_box = GBin.handle_box ~border_width:2
2629 ~packing:(vbox_for_menu#pack ~padding:0) () in
2630 let menubar = GMenu.menu_bar ~packing:handle_box#add () in
2631 let factory0 = new GMenu.factory menubar in
2632 let accel_group = factory0#accel_group in
2634 let file_menu = factory0#add_submenu "File" in
2635 let factory1 = new GMenu.factory file_menu ~accel_group in
2636 (* let export_to_postscript_menu_item = *)
2640 factory1#add_item "New Block of (Co)Inductive Definitions..."
2641 ~key:GdkKeysyms._B ~callback:new_inductive
2644 factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
2647 let reopen_menu_item =
2648 factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
2652 factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
2653 ignore (factory1#add_separator ()) ;
2655 (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
2656 ~callback:load_unfinished_proof) ;
2657 let save_menu_item =
2658 factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S
2659 ~callback:save_unfinished_proof
2661 ignore (factory1#add_separator ()) ;
2662 ignore (factory1#add_item "Clear Environment" ~callback:CicEnvironment.empty);
2663 ignore (factory1#add_item "Dump Environment" ~callback:dump_environment);
2665 (factory1#add_item "Restore Environment" ~callback:restore_environment);
2667 (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
2668 ignore (!save_set_sensitive false);
2669 ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
2670 ignore (!qed_set_sensitive false);
2671 ignore (factory1#add_separator ()) ;
2673 let export_to_postscript_menu_item =
2674 factory1#add_item "Export to PostScript..."
2675 ~callback:(export_to_postscript output) in
2677 ignore (factory1#add_separator ()) ;
2679 (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) (*;
2680 export_to_postscript_menu_item *)
2683 let edit_menu = factory0#add_submenu "Edit Current Proof" in
2684 let factory2 = new GMenu.factory edit_menu ~accel_group in
2685 let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
2686 let proveit_menu_item =
2687 factory2#add_item "Prove It" ~key:GdkKeysyms._I
2688 ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
2690 let focus_menu_item =
2691 factory2#add_item "Focus" ~key:GdkKeysyms._F
2692 ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
2695 focus_and_proveit_set_sensitive :=
2697 proveit_menu_item#misc#set_sensitive b ;
2698 focus_menu_item#misc#set_sensitive b
2700 let _ = !focus_and_proveit_set_sensitive false in
2701 (* edit term menu *)
2702 let edit_term_menu = factory0#add_submenu "Edit Term" in
2703 let factory5 = new GMenu.factory edit_term_menu ~accel_group in
2704 let check_menu_item =
2705 factory5#add_item "Check Term" ~key:GdkKeysyms._C
2706 ~callback:(check scratch_window) in
2707 let _ = check_menu_item#misc#set_sensitive false in
2709 let search_menu = factory0#add_submenu "Search" in
2710 let factory4 = new GMenu.factory search_menu ~accel_group in
2712 factory4#add_item "Locate..." ~key:GdkKeysyms._T
2714 let searchPattern_menu_item =
2715 factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
2716 ~callback:completeSearchPattern in
2717 let _ = searchPattern_menu_item#misc#set_sensitive false in
2718 let show_menu_item =
2719 factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
2721 let insert_query_item =
2722 factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._Y
2723 ~callback:insertQuery in
2725 let hbugs_menu = factory0#add_submenu "HBugs" in
2726 let factory6 = new GMenu.factory hbugs_menu ~accel_group in
2728 factory6#add_check_item
2729 ~active:false ~key:GdkKeysyms._F5 ~callback:Hbugs.toggle "HBugs enabled"
2732 factory6#add_item ~key:GdkKeysyms._Return ~callback:Hbugs.notify
2733 "(Re)Submit status!"
2735 let _ = factory6#add_separator () in
2737 factory6#add_item ~callback:Hbugs.start_web_services "Start Web Services"
2740 factory6#add_item ~callback:Hbugs.stop_web_services "Stop Web Services"
2743 let settings_menu = factory0#add_submenu "Settings" in
2744 let factory3 = new GMenu.factory settings_menu ~accel_group in
2746 factory3#add_item "Edit Aliases..." ~key:GdkKeysyms._A
2747 ~callback:edit_aliases in
2749 factory3#add_item "Clear Aliases" ~key:GdkKeysyms._K
2750 ~callback:clear_aliases in
2752 factory3#add_check_item "Auto disambiguation"
2753 ~callback:(fun checked -> auto_disambiguation := checked) in
2754 let _ = factory3#add_separator () in
2756 factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
2757 ~callback:(function _ -> (settings_window ())#show ()) in
2758 let _ = factory3#add_separator () in
2760 factory3#add_item "Reload Stylesheets"
2763 if ProofEngine.get_proof () <> None then
2765 refresh_goals notebook ;
2766 refresh_proof output
2768 InvokeTactics.RefreshSequentException e ->
2770 (`Error (`T ("An error occurred while refreshing the " ^
2771 "sequent: " ^ Printexc.to_string e))) ;
2772 (*notebook#remove_all_pages ~skip_switch_page_event:false ;*)
2773 notebook#set_empty_page
2774 | InvokeTactics.RefreshProofException e ->
2776 (`Error (`T ("An error occurred while refreshing the proof: " ^ Printexc.to_string e))) ;
2780 let _ = window#add_accel_group accel_group in
2784 ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
2786 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2787 let scrolled_window0 =
2788 GBin.scrolled_window ~border_width:10
2789 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2790 let _ = scrolled_window0#add output#coerce in
2792 GBin.frame ~label:"Insert Term"
2793 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2794 let scrolled_window1 =
2795 GBin.scrolled_window ~border_width:5
2796 ~packing:frame#add () in
2798 TermEditor'.term_editor
2800 ~width:400 ~height:100 ~packing:scrolled_window1#add ()
2801 ~isnotempty_callback:
2803 check_menu_item#misc#set_sensitive b ;
2804 searchPattern_menu_item#misc#set_sensitive b) in
2806 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2808 vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
2810 GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
2813 new HelmGtkLogger.html_logger
2814 ~width:400 ~height: 100 ~show:true ~packing:frame#add ()
2817 method inputt = inputt
2818 method output = (output : TermViewer.proof_viewer)
2819 method scratch_window = scratch_window
2820 method notebook = notebook
2821 method show = window#show
2822 method set_auto_disambiguation set = autoitem#set_active set
2824 notebook#set_empty_page ;
2825 (*export_to_postscript_menu_item#misc#set_sensitive false ;*)
2826 check_term := (check_term_in_scratch scratch_window) ;
2828 (* signal handlers here *)
2829 ignore(output#connect#selection_changed
2831 choose_selection output elem ;
2832 !focus_and_proveit_set_sensitive true
2834 ignore (output#connect#click (show_in_show_window_callback output)) ;
2835 let settings_window = new settings_window output scrolled_window0
2836 (*export_to_postscript_menu_item*)() (choose_selection output) in
2837 set_settings_window settings_window ;
2838 ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true ))
2843 let initialize_everything () =
2845 TermViewer.proof_viewer
2846 ~mml_of_cic_object:ApplyTransformation.mml_of_cic_object
2847 ~width:350 ~height:280 ()
2849 let notebook = new notebook in
2850 let rendering_window' = new rendering_window output notebook in
2851 rendering_window'#set_auto_disambiguation !auto_disambiguation;
2852 set_rendering_window rendering_window';
2853 let print_error_as_html prefix msg =
2854 HelmLogger.log (`Error (`T (prefix ^ msg)))
2856 Gdome_xslt.setErrorCallback (Some (print_error_as_html "XSLT Error: "));
2857 Gdome_xslt.setDebugCallback
2858 (Some (print_error_as_html "XSLT Debug Message: "));
2859 rendering_window'#show () ;
2860 if restore_environment_on_boot &&
2861 Sys.file_exists (Helm_registry.get "gtoplevel.environment_file")
2863 restore_environment ();
2868 ignore (GtkMain.Main.init ()) ;
2869 initialize_everything () ;
2870 MQIC.close mqi_handle;
2875 (* CicEnvironment.set_trust (fun _ -> false); *)
2876 Sys.catch_break true;
2878 with Sys.Break -> () (* exit nicely, invoking at_exit functions *)