1 (* Copyright (C) 2000-2002, 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 (******************************************************************************)
37 (* GLOBAL CONSTANTS *)
39 let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
40 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
44 " <body bgColor=\"white\">"
54 Sys.getenv "GTOPLEVEL_PROOFFILE"
56 Not_found -> "/public/currentproof"
61 Sys.getenv "GTOPLEVEL_PROOFFILETYPE"
63 Not_found -> "/public/currentprooftype"
66 (*CSC: the getter should handle the innertypes, not the FS *)
70 Sys.getenv "GTOPLEVEL_INNERTYPESFILE"
72 Not_found -> "/public/innertypes"
75 let constanttypefile =
77 Sys.getenv "GTOPLEVEL_CONSTANTTYPEFILE"
79 Not_found -> "/public/constanttype"
82 let postgresqlconnectionstring =
84 Sys.getenv "POSTGRESQL_CONNECTION_STRING"
86 Not_found -> "host=mowgli.cs.unibo.it dbname=helm_mowgli_new_schema user=helm"
89 let empty_id_to_uris = ([],function _ -> None);;
92 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
94 let htmlheader_and_content = ref htmlheader;;
96 let current_cic_infos = ref None;;
97 let current_goal_infos = ref None;;
98 let current_scratch_infos = ref None;;
100 let id_to_uris = ref empty_id_to_uris;;
102 let check_term = ref (fun _ _ _ -> assert false);;
103 let mml_of_cic_term_ref = ref (fun _ _ -> assert false);;
105 exception RenderingWindowsNotInitialized;;
107 let set_rendering_window,rendering_window =
108 let rendering_window_ref = ref None in
109 (function rw -> rendering_window_ref := Some rw),
111 match !rendering_window_ref with
112 None -> raise RenderingWindowsNotInitialized
117 exception SettingsWindowsNotInitialized;;
119 let set_settings_window,settings_window =
120 let settings_window_ref = ref None in
121 (function rw -> settings_window_ref := Some rw),
123 match !settings_window_ref with
124 None -> raise SettingsWindowsNotInitialized
129 exception OutputHtmlNotInitialized;;
131 let set_outputhtml,outputhtml =
132 let outputhtml_ref = ref None in
133 (function rw -> outputhtml_ref := Some rw),
135 match !outputhtml_ref with
136 None -> raise OutputHtmlNotInitialized
137 | Some outputhtml -> outputhtml
141 exception QedSetSensitiveNotInitialized;;
142 let qed_set_sensitive =
143 ref (function _ -> raise QedSetSensitiveNotInitialized)
146 exception SaveSetSensitiveNotInitialized;;
147 let save_set_sensitive =
148 ref (function _ -> raise SaveSetSensitiveNotInitialized)
151 (* COMMAND LINE OPTIONS *)
157 "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
160 Arg.parse argspec ignore ""
164 let term_of_cic_textual_parser_uri uri =
165 let module C = Cic in
166 let module CTP = CicTextualParser0 in
168 CTP.ConUri uri -> C.Const (uri,[])
169 | CTP.VarUri uri -> C.Var (uri,[])
170 | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
171 | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
174 let string_of_cic_textual_parser_uri uri =
175 let module C = Cic in
176 let module CTP = CicTextualParser0 in
179 CTP.ConUri uri -> UriManager.string_of_uri uri
180 | CTP.VarUri uri -> UriManager.string_of_uri uri
181 | CTP.IndTyUri (uri,tyno) ->
182 UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
183 | CTP.IndConUri (uri,tyno,consno) ->
184 UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
187 (* 4 = String.length "cic:" *)
188 String.sub uri' 4 (String.length uri' - 4)
191 let output_html outputhtml msg =
192 htmlheader_and_content := !htmlheader_and_content ^ msg ;
193 outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
194 outputhtml#set_topline (-1)
197 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
201 let check_window outputhtml uris =
204 ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
206 GPack.notebook ~scrollable:true ~packing:window#add () in
211 let scrolled_window =
212 GBin.scrolled_window ~border_width:10
214 (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
219 GMathViewAux.single_selection_math_view
220 ~packing:scrolled_window#add ~width:400 ~height:280 () in
223 term_of_cic_textual_parser_uri
224 (Disambiguate.cic_textual_parser_uri_of_string uri)
226 (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
229 let mml = !mml_of_cic_term_ref 111 expr in
230 mmlwidget#load_doc ~dom:mml
233 output_html outputhtml
234 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
239 (notebook#connect#switch_page
240 (function i -> Lazy.force (List.nth render_terms i)))
246 interactive_user_uri_choice ~(selection_mode:[`SINGLE|`EXTENDED]) ?(ok="Ok")
247 ?(enable_button_for_non_vars=false) ~title ~msg uris
249 let choices = ref [] in
250 let chosen = ref false in
251 let use_only_constants = ref false in
253 GWindow.dialog ~modal:true ~title ~width:600 () in
255 GMisc.label ~text:msg
256 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
257 let scrolled_window =
258 GBin.scrolled_window ~border_width:10
259 ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
261 let expected_height = 18 * List.length uris in
262 let height = if expected_height > 400 then 400 else expected_height in
263 GList.clist ~columns:1 ~packing:scrolled_window#add
264 ~height ~selection_mode:(selection_mode :> Gtk.Tags.selection_mode) () in
265 let _ = List.map (function x -> clist#append [x]) uris in
267 GPack.hbox ~border_width:0
268 ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
270 GMisc.label ~text:"None of the above. Try this one:"
271 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
273 GEdit.entry ~editable:true
274 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
276 GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
278 GButton.button ~label:ok
279 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
280 let _ = okb#misc#set_sensitive false in
285 if enable_button_for_non_vars then
286 hbox#pack ~expand:false ~fill:false ~padding:5 w)
287 ~label:"Try constants only" () in
289 GButton.button ~label:"Check"
290 ~packing:(hbox#pack ~padding:5) () in
291 let _ = checkb#misc#set_sensitive false in
293 GButton.button ~label:"Abort"
294 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
296 let check_callback () =
297 assert (List.length !choices > 0) ;
298 check_window (outputhtml ()) !choices
300 ignore (window#connect#destroy GMain.Main.quit) ;
301 ignore (cancelb#connect#clicked window#destroy) ;
303 (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
305 (nonvarsb#connect#clicked
307 use_only_constants := true ;
311 ignore (checkb#connect#clicked check_callback) ;
313 (clist#connect#select_row
314 (fun ~row ~column ~event ->
315 checkb#misc#set_sensitive true ;
316 okb#misc#set_sensitive true ;
317 choices := (List.nth uris row)::!choices)) ;
319 (clist#connect#unselect_row
320 (fun ~row ~column ~event ->
322 List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
324 (manual_input#connect#changed
326 if manual_input#text = "" then
329 checkb#misc#set_sensitive false ;
330 okb#misc#set_sensitive false ;
331 clist#misc#set_sensitive true
335 choices := [manual_input#text] ;
336 clist#unselect_all () ;
337 checkb#misc#set_sensitive true ;
338 okb#misc#set_sensitive true ;
339 clist#misc#set_sensitive false
341 window#set_position `CENTER ;
345 if !use_only_constants then
347 (function uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
350 if List.length !choices > 0 then !choices else raise NoChoice
355 let interactive_interpretation_choice interpretations =
356 let chosen = ref None in
359 ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
360 let vbox = GPack.vbox ~packing:window#add () in
364 ("Ambiguous input since there are many well-typed interpretations." ^
365 " Please, choose one of them.")
366 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
368 GPack.notebook ~scrollable:true
369 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
372 (function interpretation ->
374 let expected_height = 18 * List.length interpretation in
375 let height = if expected_height > 400 then 400 else expected_height in
376 GList.clist ~columns:2 ~packing:notebook#append_page ~height
377 ~titles:["id" ; "URI"] ()
381 (function (id,uri) ->
382 let n = clist#append [id;uri] in
383 clist#set_row ~selectable:false n
386 clist#columns_autosize ()
389 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
391 GButton.button ~label:"Ok"
392 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
394 GButton.button ~label:"Abort"
395 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
397 ignore (window#connect#destroy GMain.Main.quit) ;
398 ignore (cancelb#connect#clicked window#destroy) ;
401 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
402 window#set_position `CENTER ;
406 None -> raise NoChoice
413 (* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
415 let query = ref "" in
416 MQueryGenerator.set_confirm_query
417 (function q -> query := MQueryUtil.text_of_query q ; true) ;
418 function result -> !query ^ " <h1>Result:</h1> " ^ MQueryUtil.text_of_result result "<br>"
421 let domImpl = Gdome.domImplementation ();;
423 let parseStyle name =
425 domImpl#createDocumentFromURI
427 ~uri:("http://phd.cs.unibo.it:8081/getxslt?uri=" ^ name) ?mode:None
429 ~uri:("styles/" ^ name) ()
431 Gdome_xslt.processStylesheet style
434 let d_c = parseStyle "drop_coercions.xsl";;
435 let tc1 = parseStyle "objtheorycontent.xsl";;
436 let hc2 = parseStyle "content_to_html.xsl";;
437 let l = parseStyle "link.xsl";;
439 let c1 = parseStyle "rootcontent.xsl";;
440 let g = parseStyle "genmmlid.xsl";;
441 let c2 = parseStyle "annotatedpres.xsl";;
444 let getterURL = Configuration.getter_url;;
445 let processorURL = Configuration.processor_url;;
447 let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
448 let mml_args ~explode_all =
449 ("explodeall",(if explode_all then "true()" else "false()"))::
450 ["processorURL", "'" ^ processorURL ^ "'" ;
451 "getterURL", "'" ^ getterURL ^ "'" ;
452 "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
453 "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
454 "UNICODEvsSYMBOL", "'symbol'" ;
455 "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
456 "encoding", "'iso-8859-1'" ;
457 "media-type", "'text/html'" ;
458 "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
459 "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
460 "naturalLanguage", "'yes'" ;
461 "annotations", "'no'" ;
462 "URLs_or_URIs", "'URIs'" ;
463 "topurl", "'http://phd.cs.unibo.it/helm'" ;
464 "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
467 let sequent_styles = [d_c ; c1 ; g ; c2 ; l];;
469 ["processorURL", "'" ^ processorURL ^ "'" ;
470 "getterURL", "'" ^ getterURL ^ "'" ;
471 "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
472 "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
473 "UNICODEvsSYMBOL", "'symbol'" ;
474 "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
475 "encoding", "'iso-8859-1'" ;
476 "media-type", "'text/html'" ;
477 "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
478 "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
479 "naturalLanguage", "'no'" ;
480 "annotations", "'no'" ;
481 "explodeall", "true()" ;
482 "URLs_or_URIs", "'URIs'" ;
483 "topurl", "'http://phd.cs.unibo.it/helm'" ;
484 "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
487 let parse_file filename =
488 let inch = open_in filename in
489 let rec read_lines () =
491 let line = input_line inch in
499 let applyStylesheets input styles args =
500 List.fold_left (fun i style -> Gdome_xslt.applyStylesheet i style args)
505 mml_of_cic_object ~explode_all uri annobj ids_to_inner_sorts ids_to_inner_types
507 (*CSC: ????????????????? *)
509 Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:true
513 Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
514 ~ask_dtd_to_the_getter:true
518 None -> Xml2Gdome.document_of_xml domImpl xml
520 Xml.pp xml (Some constanttypefile) ;
521 Xml2Gdome.document_of_xml domImpl bodyxml'
523 (*CSC: We save the innertypes to disk so that we can retrieve them in the *)
524 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
526 Xml.pp xmlinnertypes (Some innertypesfile) ;
527 let output = applyStylesheets input mml_styles (mml_args ~explode_all) in
532 save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
535 let struri = UriManager.string_of_uri uri in
536 let idx = (String.rindex struri '/') + 1 in
537 String.sub struri idx (String.length struri - idx)
539 let path = pathname ^ "/" ^ name in
541 Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
545 Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
546 ~ask_dtd_to_the_getter:false
549 let innertypesuri = UriManager.innertypesuri_of_uri uri in
550 Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
551 Getter.register innertypesuri
552 (Configuration.annotations_url ^
553 Str.replace_first (Str.regexp "^cic:") ""
554 (UriManager.string_of_uri innertypesuri) ^ ".xml"
556 (* constant type / variable / mutual inductive types definition *)
557 Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
559 (Configuration.annotations_url ^
560 Str.replace_first (Str.regexp "^cic:") ""
561 (UriManager.string_of_uri uri) ^ ".xml"
568 match UriManager.bodyuri_of_uri uri with
570 | Some bodyuri -> bodyuri
572 Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
573 Getter.register bodyuri
574 (Configuration.annotations_url ^
575 Str.replace_first (Str.regexp "^cic:") ""
576 (UriManager.string_of_uri bodyuri) ^ ".xml"
583 exception RefreshSequentException of exn;;
584 exception RefreshProofException of exn;;
586 let refresh_proof (output : GMathViewAux.single_selection_math_view) =
588 let uri,currentproof =
589 match !ProofEngine.proof with
591 | Some (uri,metasenv,bo,ty) ->
592 !qed_set_sensitive (List.length metasenv = 0) ;
593 (*CSC: Wrong: [] is just plainly wrong *)
594 uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
597 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
598 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
600 Cic2acic.acic_object_of_cic_object currentproof
603 mml_of_cic_object ~explode_all:true uri acic ids_to_inner_sorts
606 output#load_doc ~dom:mml ;
608 Some (ids_to_terms,ids_to_father_ids,ids_to_conjectures,ids_to_hypotheses)
611 match !ProofEngine.proof with
613 | Some (uri,metasenv,bo,ty) ->
614 prerr_endline ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[]))) ; flush stderr ;
615 raise (RefreshProofException e)
618 let refresh_sequent ?(empty_notebook=true) notebook =
620 match !ProofEngine.goal with
622 if empty_notebook then
624 notebook#remove_all_pages ~skip_switch_page_event:false ;
625 notebook#set_empty_page
628 notebook#proofw#unload
631 match !ProofEngine.proof with
633 | Some (_,metasenv,_,_) -> metasenv
635 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
636 let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
637 SequentPp.XmlPp.print_sequent metasenv currentsequent
639 let regenerate_notebook () =
640 let skip_switch_page_event =
642 (m,_,_)::_ when m = metano -> false
645 notebook#remove_all_pages ~skip_switch_page_event ;
646 List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
648 if empty_notebook then
650 regenerate_notebook () ;
651 notebook#set_current_page ~may_skip_switch_page_event:false metano
655 let sequent_doc = Xml2Gdome.document_of_xml domImpl sequent_gdome in
657 applyStylesheets sequent_doc sequent_styles sequent_args
659 notebook#set_current_page ~may_skip_switch_page_event:true metano;
660 notebook#proofw#load_doc ~dom:sequent_mml
662 current_goal_infos :=
663 Some (ids_to_terms,ids_to_father_ids,ids_to_hypotheses)
667 match !ProofEngine.goal with
672 match !ProofEngine.proof with
674 | Some (_,metasenv,_,_) -> metasenv
677 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
678 prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
679 raise (RefreshSequentException e)
680 with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unkown."); raise (RefreshSequentException e)
684 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
685 ~name:"/home/galata/miohelm/guruguru1" ~indent:true ()) ;
688 let mml_of_cic_term metano term =
690 match !ProofEngine.proof with
692 | Some (_,metasenv,_,_) -> metasenv
695 match !ProofEngine.goal with
698 let (_,canonical_context,_) =
699 List.find (function (m,_,_) -> m=metano) metasenv
703 let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
704 SequentPp.XmlPp.print_sequent metasenv (metano,context,term)
707 Xml2Gdome.document_of_xml domImpl sequent_gdome
710 applyStylesheets sequent_doc sequent_styles sequent_args ;
712 current_scratch_infos :=
713 Some (term,ids_to_terms,ids_to_father_ids,ids_to_hypotheses) ;
717 exception OpenConjecturesStillThere;;
718 exception WrongProof;;
720 let pathname_of_annuri uristring =
721 Configuration.annotations_dir ^
722 Str.replace_first (Str.regexp "^cic:") "" uristring
725 let make_dirs dirpath =
726 ignore (Unix.system ("mkdir -p " ^ dirpath))
729 let save_obj uri obj =
731 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
732 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
734 Cic2acic.acic_object_of_cic_object obj
736 (* let's save the theorem and register it to the getter *)
737 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
739 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
744 match !ProofEngine.proof with
746 | Some (uri,[],bo,ty) ->
748 CicReduction.are_convertible []
749 (CicTypeChecker.type_of_aux' [] [] bo) ty
752 (*CSC: Wrong: [] is just plainly wrong *)
753 let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
755 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
756 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
758 Cic2acic.acic_object_of_cic_object proof
761 mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
764 ((rendering_window ())#output : GMathViewAux.single_selection_math_view)#load_doc mml ;
765 !qed_set_sensitive false ;
766 (* let's save the theorem and register it to the getter *)
767 let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
769 save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
773 (ids_to_terms,ids_to_father_ids,ids_to_conjectures,
778 | _ -> raise OpenConjecturesStillThere
782 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
783 match !ProofEngine.proof with
785 | Some (uri, metasenv, bo, ty) ->
787 (*CSC: Wrong: [] is just plainly wrong *)
788 Cic.CurrentProof (UriManager.name_of_uri uri,metasenv,bo,ty,[])
790 let (acurrentproof,_,_,ids_to_inner_sorts,_,_,_) =
791 Cic2acic.acic_object_of_cic_object currentproof
795 Cic2Xml.print_object uri ~ids_to_inner_sorts
796 ~ask_dtd_to_the_getter:true acurrentproof
798 xml,Some bodyxml -> xml,bodyxml
799 | _,None -> assert false
801 Xml.pp ~quiet:true xml (Some prooffiletype) ;
802 output_html outputhtml
803 ("<h1 color=\"Green\">Current proof type saved to " ^
804 prooffiletype ^ "</h1>") ;
805 Xml.pp ~quiet:true bodyxml (Some prooffile) ;
806 output_html outputhtml
807 ("<h1 color=\"Green\">Current proof body saved to " ^
811 (* Used to typecheck the loaded proofs *)
812 let typecheck_loaded_proof metasenv bo ty =
813 let module T = CicTypeChecker in
816 (fun metasenv ((_,context,ty) as conj) ->
817 ignore (T.type_of_aux' metasenv context ty) ;
820 ignore (T.type_of_aux' metasenv [] ty) ;
821 ignore (T.type_of_aux' metasenv [] bo)
825 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
826 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
827 let notebook = (rendering_window ())#notebook in
830 GToolbox.input_string ~title:"Load Unfinished Proof" ~text:"/dummy.con"
833 None -> raise NoChoice
835 let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
836 match CicParser.obj_of_xml prooffiletype (Some prooffile) with
837 Cic.CurrentProof (_,metasenv,bo,ty,_) ->
838 typecheck_loaded_proof metasenv bo ty ;
840 Some (uri, metasenv, bo, ty) ;
844 | (metano,_,_)::_ -> Some metano
846 refresh_proof output ;
847 refresh_sequent notebook ;
848 output_html outputhtml
849 ("<h1 color=\"Green\">Current proof type loaded from " ^
850 prooffiletype ^ "</h1>") ;
851 output_html outputhtml
852 ("<h1 color=\"Green\">Current proof body loaded from " ^
853 prooffile ^ "</h1>") ;
854 !save_set_sensitive true
857 RefreshSequentException e ->
858 output_html outputhtml
859 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
860 "sequent: " ^ Printexc.to_string e ^ "</h1>")
861 | RefreshProofException e ->
862 output_html outputhtml
863 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
864 "proof: " ^ Printexc.to_string e ^ "</h1>")
866 output_html outputhtml
867 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
870 let edit_aliases () =
871 let chosen = ref false in
874 ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
876 GPack.vbox ~border_width:0 ~packing:window#add () in
877 let scrolled_window =
878 GBin.scrolled_window ~border_width:10
879 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
880 let input = GEdit.text ~editable:true ~width:400 ~height:100
881 ~packing:scrolled_window#add () in
883 GPack.hbox ~border_width:0
884 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
886 GButton.button ~label:"Ok"
887 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
889 GButton.button ~label:"Cancel"
890 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
891 ignore (window#connect#destroy GMain.Main.quit) ;
892 ignore (cancelb#connect#clicked window#destroy) ;
894 (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
895 let dom,resolve_id = !id_to_uris in
897 (input#insert_text ~pos:0
902 match resolve_id v with
907 (string_of_cic_textual_parser_uri uri)
913 let inputtext = input#get_chars 0 input#length in
915 let alfa = "[a-zA-Z_-]" in
916 let digit = "[0-9]" in
917 let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
918 let blanks = "\( \|\t\|\n\)+" in
919 let nonblanks = "[^ \t\n]+" in
920 let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
922 ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
926 let n' = Str.search_forward regexpr inputtext n in
927 let id = Str.matched_group 2 inputtext in
929 Disambiguate.cic_textual_parser_uri_of_string
930 ("cic:" ^ (Str.matched_group 5 inputtext))
932 let dom,resolve_id = aux (n' + 1) in
933 if List.mem id dom then
937 (function id' -> if id = id' then Some uri else resolve_id id')
939 Not_found -> empty_id_to_uris
943 id_to_uris := dom,resolve_id
947 let module L = LogicalOperations in
948 let module G = Gdome in
949 let notebook = (rendering_window ())#notebook in
950 let output = (rendering_window ())#output in
951 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
952 match (rendering_window ())#output#get_selection with
955 ((node : Gdome.element)#getAttributeNS
957 ((element : G.element)#getAttributeNS
960 ~localName:(G.domString "xref"))#to_string
962 if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
966 match !current_cic_infos with
967 Some (ids_to_terms, ids_to_father_ids, _, _) ->
969 L.to_sequent id ids_to_terms ids_to_father_ids ;
970 refresh_proof output ;
971 refresh_sequent notebook
972 | None -> assert false (* "ERROR: No current term!!!" *)
974 RefreshSequentException e ->
975 output_html outputhtml
976 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
977 "sequent: " ^ Printexc.to_string e ^ "</h1>")
978 | RefreshProofException e ->
979 output_html outputhtml
980 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
981 "proof: " ^ Printexc.to_string e ^ "</h1>")
983 output_html outputhtml
984 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
986 | None -> assert false (* "ERROR: No selection!!!" *)
990 let module L = LogicalOperations in
991 let module G = Gdome in
992 let notebook = (rendering_window ())#notebook in
993 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
994 match (rendering_window ())#output#get_selection with
997 ((node : Gdome.element)#getAttributeNS
999 ((element : G.element)#getAttributeNS
1001 ~namespaceURI:helmns
1002 ~localName:(G.domString "xref"))#to_string
1004 if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1008 match !current_cic_infos with
1009 Some (ids_to_terms, ids_to_father_ids, _, _) ->
1011 L.focus id ids_to_terms ids_to_father_ids ;
1012 refresh_sequent notebook
1013 | None -> assert false (* "ERROR: No current term!!!" *)
1015 RefreshSequentException e ->
1016 output_html outputhtml
1017 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1018 "sequent: " ^ Printexc.to_string e ^ "</h1>")
1019 | RefreshProofException e ->
1020 output_html outputhtml
1021 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1022 "proof: " ^ Printexc.to_string e ^ "</h1>")
1024 output_html outputhtml
1025 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1027 | None -> assert false (* "ERROR: No selection!!!" *)
1030 exception NoPrevGoal;;
1031 exception NoNextGoal;;
1033 let setgoal metano =
1034 let module L = LogicalOperations in
1035 let module G = Gdome in
1036 let notebook = (rendering_window ())#notebook in
1037 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1039 match !ProofEngine.proof with
1040 None -> assert false
1041 | Some (_,metasenv,_,_) -> metasenv
1044 refresh_sequent ~empty_notebook:false notebook
1046 RefreshSequentException e ->
1047 output_html outputhtml
1048 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1049 "sequent: " ^ Printexc.to_string e ^ "</h1>")
1051 output_html outputhtml
1052 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1056 show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
1059 GWindow.window ~width:800 ~border_width:2 () in
1060 let scrolled_window =
1061 GBin.scrolled_window ~border_width:10 ~packing:window#add () in
1063 GMathViewAux.single_selection_math_view ~packing:scrolled_window#add ~width:600 ~height:400 () in
1064 let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
1065 let href = Gdome.domString "href" in
1066 let show_in_show_window_obj uri obj =
1067 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1070 (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
1071 ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
1073 Cic2acic.acic_object_of_cic_object obj
1076 mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
1079 window#set_title (UriManager.string_of_uri uri) ;
1080 window#misc#hide () ; window#show () ;
1081 mmlwidget#load_doc mml ;
1084 output_html outputhtml
1085 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1087 let show_in_show_window_uri uri =
1088 let obj = CicEnvironment.get_obj uri in
1089 show_in_show_window_obj uri obj
1091 let show_in_show_window_callback mmlwidget (n : Gdome.element) _ =
1092 if n#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
1094 (n#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
1096 show_in_show_window_uri (UriManager.uri_of_string uri)
1099 "'get_action' and 'action_toggle' not yet implemented in lablgtkmathview 0.3.99"
1100 (* TODO commented out because not yet implemented in lablgtkmathview 0.3.99 *)
1102 if mmlwidget#get_action <> None then
1103 mmlwidget#action_toggle
1107 mmlwidget#connect#click (show_in_show_window_callback mmlwidget)
1109 show_in_show_window_obj, show_in_show_window_uri,
1110 show_in_show_window_callback
1113 exception NoObjectsLocated;;
1115 let user_uri_choice ~title ~msg uris =
1118 [] -> raise NoObjectsLocated
1122 interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
1127 String.sub uri 4 (String.length uri - 4)
1130 let locate_callback id =
1131 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1132 let result = MQueryGenerator.locate id in
1136 Disambiguate.wrong_xpointer_format_from_wrong_xpointer_format' uri)
1139 (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>")
1141 output_html outputhtml html ;
1142 user_uri_choice ~title:"Ambiguous input."
1144 ("Ambiguous input \"" ^ id ^
1145 "\". Please, choose one interpetation:")
1150 let input_or_locate_uri ~title =
1151 let uri = ref None in
1154 ~width:400 ~modal:true ~title ~border_width:2 () in
1155 let vbox = GPack.vbox ~packing:window#add () in
1157 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1159 GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
1161 GEdit.entry ~editable:true
1162 ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
1164 GButton.button ~label:"Check"
1165 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1166 let _ = checkb#misc#set_sensitive false in
1168 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1170 GMisc.label ~text:"You can also enter an indentifier to locate:"
1171 ~packing:(hbox2#pack ~padding:5) () in
1173 GEdit.entry ~editable:true
1174 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1176 GButton.button ~label:"Locate"
1177 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1178 let _ = locateb#misc#set_sensitive false in
1180 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1182 GButton.button ~label:"Ok"
1183 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
1184 let _ = okb#misc#set_sensitive false in
1186 GButton.button ~label:"Cancel"
1187 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
1189 ignore (window#connect#destroy GMain.Main.quit) ;
1191 (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
1192 let check_callback () =
1193 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1194 let uri = "cic:" ^ manual_input#text in
1196 ignore (Getter.resolve (UriManager.uri_of_string uri)) ;
1197 output_html outputhtml "<h1 color=\"Green\">OK</h1>" ;
1200 Getter.Unresolved ->
1201 output_html outputhtml
1202 ("<h1 color=\"Red\">URI " ^ uri ^
1203 " does not correspond to any object.</h1>") ;
1205 | UriManager.IllFormedUri _ ->
1206 output_html outputhtml
1207 ("<h1 color=\"Red\">URI " ^ uri ^ " is not well-formed.</h1>") ;
1210 output_html outputhtml
1211 ("<h1 color=\"Red\">" ^ Printexc.to_string e ^ "</h1>") ;
1215 (okb#connect#clicked
1217 if check_callback () then
1219 uri := Some manual_input#text ;
1223 ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1225 (manual_input#connect#changed
1227 if manual_input#text = "" then
1229 checkb#misc#set_sensitive false ;
1230 okb#misc#set_sensitive false
1234 checkb#misc#set_sensitive true ;
1235 okb#misc#set_sensitive true
1238 (locate_input#connect#changed
1239 (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1241 (locateb#connect#clicked
1243 let id = locate_input#text in
1244 manual_input#set_text (locate_callback id) ;
1245 locate_input#delete_text 0 (String.length id)
1248 GMain.Main.main () ;
1250 None -> raise NoChoice
1251 | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1254 exception AmbiguousInput;;
1256 (* A WIDGET TO ENTER CIC TERMS *)
1260 let output_html msg = output_html (outputhtml ()) msg;;
1261 let interactive_user_uri_choice =
1262 fun ~selection_mode ?ok ?enable_button_for_non_vars ~title ~msg ~id ->
1263 interactive_user_uri_choice ~selection_mode ?ok
1264 ?enable_button_for_non_vars ~title ~msg;;
1265 let interactive_interpretation_choice = interactive_interpretation_choice;;
1266 let input_or_locate_uri = input_or_locate_uri;;
1270 module Disambiguate' = Disambiguate.Make(Callbacks);;
1272 class term_editor ?packing ?width ?height ?isnotempty_callback () =
1273 let input = GEdit.text ~editable:true ?width ?height ?packing () in
1275 match isnotempty_callback with
1278 ignore(input#connect#changed (function () -> callback (input#length > 0)))
1281 method coerce = input#coerce
1283 input#delete_text 0 input#length
1284 (* CSC: txt is now a string, but should be of type Cic.term *)
1285 method set_term txt =
1287 ignore ((input#insert_text txt) ~pos:0)
1288 (* CSC: this method should disappear *)
1289 method get_as_string =
1290 input#get_chars 0 input#length
1291 method get_metasenv_and_term ~context ~metasenv =
1295 Some (n,_) -> Some n
1299 let lexbuf = Lexing.from_string (input#get_chars 0 input#length) in
1300 let dom,mk_metasenv_and_expr =
1301 CicTextualParserContext.main
1302 ~context:name_context ~metasenv CicTextualLexer.token lexbuf
1304 let id_to_uris',metasenv,expr =
1305 Disambiguate'.disambiguate_input context metasenv dom mk_metasenv_and_expr
1306 ~id_to_uris:!id_to_uris
1308 id_to_uris := id_to_uris' ;
1313 (* OTHER FUNCTIONS *)
1316 let inputt = ((rendering_window ())#inputt : term_editor) in
1317 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1320 GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1322 None -> raise NoChoice
1324 let uri = locate_callback input in
1328 output_html outputhtml
1329 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1333 exception UriAlreadyInUse;;
1334 exception NotAUriToAConstant;;
1336 let new_inductive () =
1337 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1338 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
1339 let notebook = (rendering_window ())#notebook in
1341 let chosen = ref false in
1342 let inductive = ref true in
1343 let paramsno = ref 0 in
1344 let get_uri = ref (function _ -> assert false) in
1345 let get_base_uri = ref (function _ -> assert false) in
1346 let get_names = ref (function _ -> assert false) in
1347 let get_types_and_cons = ref (function _ -> assert false) in
1348 let get_context_and_subst = ref (function _ -> assert false) in
1351 ~width:600 ~modal:true ~position:`CENTER
1352 ~title:"New Block of Mutual (Co)Inductive Definitions"
1353 ~border_width:2 () in
1354 let vbox = GPack.vbox ~packing:window#add () in
1356 GPack.hbox ~border_width:0
1357 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1359 GMisc.label ~text:"Enter the URI for the new block:"
1360 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1362 GEdit.entry ~editable:true
1363 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1365 GPack.hbox ~border_width:0
1366 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1370 "Enter the number of left parameters in every arity and constructor type:"
1371 ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1372 let paramsno_entry =
1373 GEdit.entry ~editable:true ~text:"0"
1374 ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1376 GPack.hbox ~border_width:0
1377 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1379 GMisc.label ~text:"Are the definitions inductive or coinductive?"
1380 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1382 GButton.radio_button ~label:"Inductive"
1383 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1385 GButton.radio_button ~label:"Coinductive"
1386 ~group:inductiveb#group
1387 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1389 GPack.hbox ~border_width:0
1390 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1392 GMisc.label ~text:"Enter the list of the names of the types:"
1393 ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1395 GEdit.entry ~editable:true
1396 ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1398 GPack.hbox ~border_width:0
1399 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1401 GButton.button ~label:"> Next"
1402 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1403 let _ = okb#misc#set_sensitive true in
1405 GButton.button ~label:"Abort"
1406 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1407 ignore (window#connect#destroy GMain.Main.quit) ;
1408 ignore (cancelb#connect#clicked window#destroy) ;
1412 (okb#connect#clicked
1415 let uristr = "cic:" ^ uri_entry#text in
1416 let namesstr = names_entry#text in
1417 let paramsno' = int_of_string (paramsno_entry#text) in
1418 match Str.split (Str.regexp " +") namesstr with
1420 | (he::tl) as names ->
1421 let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1424 ignore (Getter.resolve uri) ;
1425 raise UriAlreadyInUse
1427 Getter.Unresolved ->
1428 get_uri := (function () -> uri) ;
1429 get_names := (function () -> names) ;
1430 inductive := inductiveb#active ;
1431 paramsno := paramsno' ;
1436 output_html outputhtml
1437 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1445 GBin.frame ~label:name
1446 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1447 let vbox = GPack.vbox ~packing:frame#add () in
1448 let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1450 GMisc.label ~text:("Enter its type:")
1451 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1452 let scrolled_window =
1453 GBin.scrolled_window ~border_width:5
1454 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1456 new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
1457 ~isnotempty_callback:
1459 (*non_empty_type := b ;*)
1460 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1463 GPack.hbox ~border_width:0
1464 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1466 GMisc.label ~text:("Enter the list of its constructors:")
1467 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1468 let cons_names_entry =
1469 GEdit.entry ~editable:true
1470 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1471 (newinputt,cons_names_entry)
1474 vbox#remove hboxn#coerce ;
1476 GPack.hbox ~border_width:0
1477 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1479 GButton.button ~label:"> Next"
1480 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1482 GButton.button ~label:"Abort"
1483 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1484 ignore (cancelb#connect#clicked window#destroy) ;
1486 (okb#connect#clicked
1489 let names = !get_names () in
1490 let types_and_cons =
1492 (fun name (newinputt,cons_names_entry) ->
1493 let consnamesstr = cons_names_entry#text in
1494 let cons_names = Str.split (Str.regexp " +") consnamesstr in
1496 newinputt#get_metasenv_and_term ~context:[] ~metasenv:[]
1499 [] -> expr,cons_names
1500 | _ -> raise AmbiguousInput
1501 ) names type_widgets
1503 let uri = !get_uri () in
1505 (* Let's see if so far the definition is well-typed *)
1508 (* To test if the arities of the inductive types are well *)
1509 (* typed, we check the inductive block definition where *)
1510 (* no constructor is given to each type. *)
1513 (fun name (ty,cons) -> (name, !inductive, ty, []))
1514 names types_and_cons
1516 CicTypeChecker.typecheck_mutual_inductive_defs uri
1517 (tys,params,paramsno)
1519 get_context_and_subst :=
1523 (fun (context,subst) name (ty,_) ->
1525 (Some (Cic.Name name, Cic.Decl ty))::context,
1526 (Cic.MutInd (uri,!i,[]))::subst
1529 ) ([],[]) names types_and_cons) ;
1530 let types_and_cons' =
1532 (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1533 names types_and_cons
1535 get_types_and_cons := (function () -> types_and_cons') ;
1540 output_html outputhtml
1541 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1544 and phase3 name cons =
1545 let get_cons_types = ref (function () -> assert false) in
1548 ~width:600 ~modal:true ~position:`CENTER
1549 ~title:(name ^ " Constructors")
1550 ~border_width:2 () in
1551 let vbox = GPack.vbox ~packing:window2#add () in
1552 let cons_type_widgets =
1554 (function consname ->
1556 GPack.hbox ~border_width:0
1557 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1559 GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1560 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1561 let scrolled_window =
1562 GBin.scrolled_window ~border_width:5
1563 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1565 new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
1566 ~isnotempty_callback:
1568 (* (*non_empty_type := b ;*)
1569 okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1574 GPack.hbox ~border_width:0
1575 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1577 GButton.button ~label:"> Next"
1578 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1579 let _ = okb#misc#set_sensitive true in
1581 GButton.button ~label:"Abort"
1582 ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1583 ignore (window2#connect#destroy GMain.Main.quit) ;
1584 ignore (cancelb#connect#clicked window2#destroy) ;
1586 (okb#connect#clicked
1590 let context,subst= !get_context_and_subst () in
1595 inputt#get_metasenv_and_term ~context ~metasenv:[]
1599 let undebrujined_expr =
1601 (fun expr t -> CicSubstitution.subst t expr) expr subst
1603 name, undebrujined_expr
1604 | _ -> raise AmbiguousInput
1605 ) cons cons_type_widgets
1607 get_cons_types := (function () -> cons_types) ;
1611 output_html outputhtml
1612 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1615 GMain.Main.main () ;
1616 let okb_pressed = !chosen in
1618 if (not okb_pressed) then
1621 assert false (* The control never reaches this point *)
1624 (!get_cons_types ())
1627 (* No more phases left or Abort pressed *)
1629 GMain.Main.main () ;
1633 let uri = !get_uri () in
1636 let tys = !get_types_and_cons () in
1637 let obj = Cic.InductiveDefinition tys params !paramsno in
1640 prerr_endline (CicPp.ppobj obj) ;
1641 CicTypeChecker.typecheck_mutual_inductive_defs uri
1642 (tys,params,!paramsno) ;
1645 prerr_endline "Offending mutual (co)inductive type declaration:" ;
1646 prerr_endline (CicPp.ppobj obj) ;
1648 (* We already know that obj is well-typed. We need to add it to the *)
1649 (* environment in order to compute the inner-types without having to *)
1650 (* debrujin it or having to modify lots of other functions to avoid *)
1651 (* asking the environment for the MUTINDs we are defining now. *)
1652 CicEnvironment.put_inductive_definition uri obj ;
1654 show_in_show_window_obj uri obj
1657 output_html outputhtml
1658 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1662 let inputt = ((rendering_window ())#inputt : term_editor) in
1663 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1664 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
1665 let notebook = (rendering_window ())#notebook in
1667 let chosen = ref false in
1668 let get_metasenv_and_term = ref (function _ -> assert false) in
1669 let get_uri = ref (function _ -> assert false) in
1670 let non_empty_type = ref false in
1673 ~width:600 ~modal:true ~title:"New Proof or Definition"
1674 ~border_width:2 () in
1675 let vbox = GPack.vbox ~packing:window#add () in
1677 GPack.hbox ~border_width:0
1678 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1680 GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1681 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1683 GEdit.entry ~editable:true
1684 ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1686 GPack.hbox ~border_width:0
1687 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1689 GMisc.label ~text:"Enter the theorem or definition type:"
1690 ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1691 let scrolled_window =
1692 GBin.scrolled_window ~border_width:5
1693 ~packing:(vbox#pack ~expand:true ~padding:0) () in
1694 (* the content of the scrolled_window is moved below (see comment) *)
1696 GPack.hbox ~border_width:0
1697 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1699 GButton.button ~label:"Ok"
1700 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1701 let _ = okb#misc#set_sensitive false in
1703 GButton.button ~label:"Cancel"
1704 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1705 (* moved here to have visibility of the ok button *)
1707 new term_editor ~width:400 ~height:100 ~packing:scrolled_window#add ()
1708 ~isnotempty_callback:
1710 non_empty_type := b ;
1711 okb#misc#set_sensitive (b && uri_entry#text <> ""))
1714 newinputt#set_term inputt#get_as_string ;
1717 uri_entry#connect#changed
1719 okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1721 ignore (window#connect#destroy GMain.Main.quit) ;
1722 ignore (cancelb#connect#clicked window#destroy) ;
1724 (okb#connect#clicked
1728 let metasenv,parsed = newinputt#get_metasenv_and_term [] [] in
1729 let uristr = "cic:" ^ uri_entry#text in
1730 let uri = UriManager.uri_of_string uristr in
1731 if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1732 raise NotAUriToAConstant
1736 ignore (Getter.resolve uri) ;
1737 raise UriAlreadyInUse
1739 Getter.Unresolved ->
1740 get_metasenv_and_term := (function () -> metasenv,parsed) ;
1741 get_uri := (function () -> uri) ;
1746 output_html outputhtml
1747 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1750 GMain.Main.main () ;
1753 let metasenv,expr = !get_metasenv_and_term () in
1754 let _ = CicTypeChecker.type_of_aux' metasenv [] expr in
1755 ProofEngine.proof :=
1756 Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
1757 ProofEngine.goal := Some 1 ;
1758 refresh_sequent notebook ;
1759 refresh_proof output ;
1760 !save_set_sensitive true ;
1763 RefreshSequentException e ->
1764 output_html outputhtml
1765 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1766 "sequent: " ^ Printexc.to_string e ^ "</h1>")
1767 | RefreshProofException e ->
1768 output_html outputhtml
1769 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1770 "proof: " ^ Printexc.to_string e ^ "</h1>")
1772 output_html outputhtml
1773 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1776 let check_term_in_scratch scratch_window metasenv context expr =
1778 let ty = CicTypeChecker.type_of_aux' metasenv context expr in
1779 let mml = mml_of_cic_term 111 (Cic.Cast (expr,ty)) in
1780 scratch_window#show () ;
1781 scratch_window#mmlwidget#load_doc ~dom:mml
1784 print_endline ("? " ^ CicPp.ppterm expr) ;
1788 let check scratch_window () =
1789 let inputt = ((rendering_window ())#inputt : term_editor) in
1790 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1792 match !ProofEngine.proof with
1794 | Some (_,metasenv,_,_) -> metasenv
1797 match !ProofEngine.goal with
1800 let (_,canonical_context,_) =
1801 List.find (function (m,_,_) -> m=metano) metasenv
1806 let metasenv',expr = inputt#get_metasenv_and_term context metasenv in
1807 check_term_in_scratch scratch_window metasenv' context expr
1810 output_html outputhtml
1811 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1814 let decompose_uris_choice_callback uris =
1815 (* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
1816 let module U = UriManager in
1819 match Disambiguate.cic_textual_parser_uri_of_string uri with
1820 CicTextualParser0.IndTyUri (uri,typeno) -> (uri,typeno,[])
1821 | _ -> assert false)
1822 (interactive_user_uri_choice
1823 ~selection_mode:`EXTENDED ~ok:"Ok" ~enable_button_for_non_vars:false
1824 ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose"
1826 (function (uri,typeno,_) ->
1827 U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1)
1832 (***********************)
1834 (***********************)
1836 let call_tactic tactic () =
1837 let notebook = (rendering_window ())#notebook in
1838 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
1839 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1840 let savedproof = !ProofEngine.proof in
1841 let savedgoal = !ProofEngine.goal in
1845 refresh_sequent notebook ;
1846 refresh_proof output
1848 RefreshSequentException e ->
1849 output_html outputhtml
1850 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1851 "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
1852 ProofEngine.proof := savedproof ;
1853 ProofEngine.goal := savedgoal ;
1854 refresh_sequent notebook
1855 | RefreshProofException e ->
1856 output_html outputhtml
1857 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1858 "proof: " ^ Printexc.to_string e ^ "</h1>") ;
1859 ProofEngine.proof := savedproof ;
1860 ProofEngine.goal := savedgoal ;
1861 refresh_sequent notebook ;
1862 refresh_proof output
1864 output_html outputhtml
1865 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1866 ProofEngine.proof := savedproof ;
1867 ProofEngine.goal := savedgoal ;
1871 let call_tactic_with_input tactic () =
1872 let notebook = (rendering_window ())#notebook in
1873 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
1874 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1875 let inputt = ((rendering_window ())#inputt : term_editor) in
1876 let savedproof = !ProofEngine.proof in
1877 let savedgoal = !ProofEngine.goal in
1878 let uri,metasenv,bo,ty =
1879 match !ProofEngine.proof with
1880 None -> assert false
1881 | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
1883 let canonical_context =
1884 match !ProofEngine.goal with
1885 None -> assert false
1887 let (_,canonical_context,_) =
1888 List.find (function (m,_,_) -> m=metano) metasenv
1893 let metasenv',expr =
1894 inputt#get_metasenv_and_term canonical_context metasenv
1896 ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
1898 refresh_sequent notebook ;
1899 refresh_proof output ;
1902 RefreshSequentException e ->
1903 output_html outputhtml
1904 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1905 "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
1906 ProofEngine.proof := savedproof ;
1907 ProofEngine.goal := savedgoal ;
1908 refresh_sequent notebook
1909 | RefreshProofException e ->
1910 output_html outputhtml
1911 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1912 "proof: " ^ Printexc.to_string e ^ "</h1>") ;
1913 ProofEngine.proof := savedproof ;
1914 ProofEngine.goal := savedgoal ;
1915 refresh_sequent notebook ;
1916 refresh_proof output
1918 output_html outputhtml
1919 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1920 ProofEngine.proof := savedproof ;
1921 ProofEngine.goal := savedgoal ;
1924 let call_tactic_with_goal_input tactic () =
1925 let module L = LogicalOperations in
1926 let module G = Gdome in
1927 let notebook = (rendering_window ())#notebook in
1928 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
1929 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1930 let savedproof = !ProofEngine.proof in
1931 let savedgoal = !ProofEngine.goal in
1932 match notebook#proofw#get_selection with
1935 ((node : Gdome.element)#getAttributeNS
1936 ~namespaceURI:helmns
1937 ~localName:(G.domString "xref"))#to_string
1939 if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1943 match !current_goal_infos with
1944 Some (ids_to_terms, ids_to_father_ids,_) ->
1946 tactic (Hashtbl.find ids_to_terms id) ;
1947 refresh_sequent notebook ;
1948 refresh_proof output
1949 | None -> assert false (* "ERROR: No current term!!!" *)
1951 RefreshSequentException e ->
1952 output_html outputhtml
1953 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1954 "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
1955 ProofEngine.proof := savedproof ;
1956 ProofEngine.goal := savedgoal ;
1957 refresh_sequent notebook
1958 | RefreshProofException e ->
1959 output_html outputhtml
1960 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1961 "proof: " ^ Printexc.to_string e ^ "</h1>") ;
1962 ProofEngine.proof := savedproof ;
1963 ProofEngine.goal := savedgoal ;
1964 refresh_sequent notebook ;
1965 refresh_proof output
1967 output_html outputhtml
1968 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1969 ProofEngine.proof := savedproof ;
1970 ProofEngine.goal := savedgoal ;
1973 output_html outputhtml
1974 ("<h1 color=\"red\">No term selected</h1>")
1977 let call_tactic_with_input_and_goal_input tactic () =
1978 let module L = LogicalOperations in
1979 let module G = Gdome in
1980 let notebook = (rendering_window ())#notebook in
1981 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
1982 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1983 let inputt = ((rendering_window ())#inputt : term_editor) in
1984 let savedproof = !ProofEngine.proof in
1985 let savedgoal = !ProofEngine.goal in
1986 match notebook#proofw#get_selection with
1989 ((node : Gdome.element)#getAttributeNS
1990 ~namespaceURI:helmns
1991 ~localName:(G.domString "xref"))#to_string
1993 if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1997 match !current_goal_infos with
1998 Some (ids_to_terms, ids_to_father_ids,_) ->
2000 let uri,metasenv,bo,ty =
2001 match !ProofEngine.proof with
2002 None -> assert false
2003 | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
2005 let canonical_context =
2006 match !ProofEngine.goal with
2007 None -> assert false
2009 let (_,canonical_context,_) =
2010 List.find (function (m,_,_) -> m=metano) metasenv
2012 canonical_context in
2013 let (metasenv',expr) =
2014 inputt#get_metasenv_and_term canonical_context metasenv
2016 ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
2017 tactic ~goal_input:(Hashtbl.find ids_to_terms id)
2019 refresh_sequent notebook ;
2020 refresh_proof output ;
2022 | None -> assert false (* "ERROR: No current term!!!" *)
2024 RefreshSequentException e ->
2025 output_html outputhtml
2026 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2027 "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2028 ProofEngine.proof := savedproof ;
2029 ProofEngine.goal := savedgoal ;
2030 refresh_sequent notebook
2031 | RefreshProofException e ->
2032 output_html outputhtml
2033 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2034 "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2035 ProofEngine.proof := savedproof ;
2036 ProofEngine.goal := savedgoal ;
2037 refresh_sequent notebook ;
2038 refresh_proof output
2040 output_html outputhtml
2041 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2042 ProofEngine.proof := savedproof ;
2043 ProofEngine.goal := savedgoal ;
2046 output_html outputhtml
2047 ("<h1 color=\"red\">No term selected</h1>")
2050 let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
2051 let module L = LogicalOperations in
2052 let module G = Gdome in
2053 let mmlwidget = (scratch_window#mmlwidget : GMathViewAux.single_selection_math_view) in
2054 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2055 let savedproof = !ProofEngine.proof in
2056 let savedgoal = !ProofEngine.goal in
2057 match mmlwidget#get_selection with
2060 ((node : Gdome.element)#getAttributeNS
2061 ~namespaceURI:helmns
2062 ~localName:(G.domString "xref"))#to_string
2064 if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2068 match !current_scratch_infos with
2069 (* term is the whole goal in the scratch_area *)
2070 Some (term,ids_to_terms, ids_to_father_ids,_) ->
2072 let expr = tactic term (Hashtbl.find ids_to_terms id) in
2073 let mml = mml_of_cic_term 111 expr in
2074 scratch_window#show () ;
2075 scratch_window#mmlwidget#load_doc ~dom:mml
2076 | None -> assert false (* "ERROR: No current term!!!" *)
2079 output_html outputhtml
2080 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2083 output_html outputhtml
2084 ("<h1 color=\"red\">No term selected</h1>")
2087 let call_tactic_with_hypothesis_input tactic () =
2088 let module L = LogicalOperations in
2089 let module G = Gdome in
2090 let notebook = (rendering_window ())#notebook in
2091 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
2092 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2093 let savedproof = !ProofEngine.proof in
2094 let savedgoal = !ProofEngine.goal in
2095 match notebook#proofw#get_selection with
2098 ((node : Gdome.element)#getAttributeNS
2099 ~namespaceURI:helmns
2100 ~localName:(G.domString "xref"))#to_string
2102 if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2106 match !current_goal_infos with
2107 Some (_,_,ids_to_hypotheses) ->
2109 tactic (Hashtbl.find ids_to_hypotheses id) ;
2110 refresh_sequent notebook ;
2111 refresh_proof output
2112 | None -> assert false (* "ERROR: No current term!!!" *)
2114 RefreshSequentException e ->
2115 output_html outputhtml
2116 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2117 "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2118 ProofEngine.proof := savedproof ;
2119 ProofEngine.goal := savedgoal ;
2120 refresh_sequent notebook
2121 | RefreshProofException e ->
2122 output_html outputhtml
2123 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2124 "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2125 ProofEngine.proof := savedproof ;
2126 ProofEngine.goal := savedgoal ;
2127 refresh_sequent notebook ;
2128 refresh_proof output
2130 output_html outputhtml
2131 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2132 ProofEngine.proof := savedproof ;
2133 ProofEngine.goal := savedgoal ;
2136 output_html outputhtml
2137 ("<h1 color=\"red\">No term selected</h1>")
2141 let intros = call_tactic ProofEngine.intros;;
2142 let exact = call_tactic_with_input ProofEngine.exact;;
2143 let apply = call_tactic_with_input ProofEngine.apply;;
2144 let elimintrossimpl = call_tactic_with_input ProofEngine.elim_intros_simpl;;
2145 let elimtype = call_tactic_with_input ProofEngine.elim_type;;
2146 let whd = call_tactic_with_goal_input ProofEngine.whd;;
2147 let reduce = call_tactic_with_goal_input ProofEngine.reduce;;
2148 let simpl = call_tactic_with_goal_input ProofEngine.simpl;;
2149 let fold_whd = call_tactic_with_input ProofEngine.fold_whd;;
2150 let fold_reduce = call_tactic_with_input ProofEngine.fold_reduce;;
2151 let fold_simpl = call_tactic_with_input ProofEngine.fold_simpl;;
2152 let cut = call_tactic_with_input ProofEngine.cut;;
2153 let change = call_tactic_with_input_and_goal_input ProofEngine.change;;
2154 let letin = call_tactic_with_input ProofEngine.letin;;
2155 let ring = call_tactic ProofEngine.ring;;
2156 let clearbody = call_tactic_with_hypothesis_input ProofEngine.clearbody;;
2157 let clear = call_tactic_with_hypothesis_input ProofEngine.clear;;
2158 let fourier = call_tactic ProofEngine.fourier;;
2159 let rewritesimpl = call_tactic_with_input ProofEngine.rewrite_simpl;;
2160 let rewritebacksimpl = call_tactic_with_input ProofEngine.rewrite_back_simpl;;
2161 let replace = call_tactic_with_input_and_goal_input ProofEngine.replace;;
2162 let reflexivity = call_tactic ProofEngine.reflexivity;;
2163 let symmetry = call_tactic ProofEngine.symmetry;;
2164 let transitivity = call_tactic_with_input ProofEngine.transitivity;;
2165 let exists = call_tactic ProofEngine.exists;;
2166 let split = call_tactic ProofEngine.split;;
2167 let left = call_tactic ProofEngine.left;;
2168 let right = call_tactic ProofEngine.right;;
2169 let assumption = call_tactic ProofEngine.assumption;;
2170 let generalize = call_tactic_with_goal_input ProofEngine.generalize;;
2171 let absurd = call_tactic_with_input ProofEngine.absurd;;
2172 let contradiction = call_tactic ProofEngine.contradiction;;
2174 call_tactic_with_input
2175 (ProofEngine.decompose ~uris_choice_callback:decompose_uris_choice_callback);;
2177 let whd_in_scratch scratch_window =
2178 call_tactic_with_goal_input_in_scratch ProofEngine.whd_in_scratch
2181 let reduce_in_scratch scratch_window =
2182 call_tactic_with_goal_input_in_scratch ProofEngine.reduce_in_scratch
2185 let simpl_in_scratch scratch_window =
2186 call_tactic_with_goal_input_in_scratch ProofEngine.simpl_in_scratch
2192 (**********************)
2193 (* END OF TACTICS *)
2194 (**********************)
2198 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2200 show_in_show_window_uri (input_or_locate_uri ~title:"Show")
2203 output_html outputhtml
2204 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2207 exception NotADefinition;;
2210 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2211 let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
2212 let notebook = (rendering_window ())#notebook in
2214 let uri = input_or_locate_uri ~title:"Open" in
2215 CicTypeChecker.typecheck uri ;
2216 let metasenv,bo,ty =
2217 match CicEnvironment.get_cooked_obj uri with
2218 Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
2219 | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
2222 | Cic.InductiveDefinition _ -> raise NotADefinition
2224 ProofEngine.proof :=
2225 Some (uri, metasenv, bo, ty) ;
2226 ProofEngine.goal := None ;
2227 refresh_sequent notebook ;
2228 refresh_proof output
2230 RefreshSequentException e ->
2231 output_html outputhtml
2232 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2233 "sequent: " ^ Printexc.to_string e ^ "</h1>")
2234 | RefreshProofException e ->
2235 output_html outputhtml
2236 ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2237 "proof: " ^ Printexc.to_string e ^ "</h1>")
2239 output_html outputhtml
2240 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2243 let show_query_results results =
2246 ~modal:false ~title:"Query results." ~border_width:2 () in
2247 let vbox = GPack.vbox ~packing:window#add () in
2249 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2252 ~text:"Click on a URI to show that object"
2253 ~packing:hbox#add () in
2254 let scrolled_window =
2255 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
2256 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2257 let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
2260 (function (uri,_) ->
2264 clist#set_row ~selectable:false n
2267 clist#columns_autosize () ;
2269 (clist#connect#select_row
2270 (fun ~row ~column ~event ->
2271 let (uristr,_) = List.nth results row in
2273 Disambiguate.cic_textual_parser_uri_of_string
2274 (Disambiguate.wrong_xpointer_format_from_wrong_xpointer_format'
2277 CicTextualParser0.ConUri uri
2278 | CicTextualParser0.VarUri uri
2279 | CicTextualParser0.IndTyUri (uri,_)
2280 | CicTextualParser0.IndConUri (uri,_,_) ->
2281 show_in_show_window_uri uri
2287 let refine_constraints (must_obj,must_rel,must_sort) =
2288 let chosen = ref false in
2289 let use_only = ref false in
2292 ~modal:true ~title:"Constraints refinement."
2293 ~width:800 ~border_width:2 () in
2294 let vbox = GPack.vbox ~packing:window#add () in
2296 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2299 ~text: "\"Only\" constraints can be enforced or not."
2300 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2302 GButton.toggle_button ~label:"Enforce \"only\" constraints"
2303 ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2306 (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
2307 (* Notebook for the constraints choice *)
2309 GPack.notebook ~scrollable:true
2310 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2311 (* Rel constraints *)
2314 ~text: "Constraints on Rels" () in
2316 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
2319 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
2322 ~text: "You can now specify the constraints on Rels."
2323 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2324 let expected_height = 25 * (List.length must_rel + 2) in
2325 let height = if expected_height > 400 then 400 else expected_height in
2326 let scrolled_window =
2327 GBin.scrolled_window ~border_width:10 ~height ~width:600
2328 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
2329 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
2330 let rel_constraints =
2332 (function (position,depth) ->
2335 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
2339 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2341 None -> position, ref None
2343 let mutable_ref = ref (Some depth') in
2345 GButton.toggle_button
2346 ~label:("depth = " ^ string_of_int depth') ~active:true
2347 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2350 (depthb#connect#toggled
2352 let sel_depth = if depthb#active then Some depth' else None in
2353 mutable_ref := sel_depth
2355 position, mutable_ref
2357 (* Sort constraints *)
2360 ~text: "Constraints on Sorts" () in
2362 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
2365 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
2368 ~text: "You can now specify the constraints on Sorts."
2369 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2370 let expected_height = 25 * (List.length must_sort + 2) in
2371 let height = if expected_height > 400 then 400 else expected_height in
2372 let scrolled_window =
2373 GBin.scrolled_window ~border_width:10 ~height ~width:600
2374 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
2375 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
2376 let sort_constraints =
2378 (function (position,depth,sort) ->
2381 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
2384 ~text:(sort ^ " " ^ position)
2385 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2387 None -> position, ref None, sort
2389 let mutable_ref = ref (Some depth') in
2391 GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
2393 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2396 (depthb#connect#toggled
2398 let sel_depth = if depthb#active then Some depth' else None in
2399 mutable_ref := sel_depth
2401 position, mutable_ref, sort
2403 (* Obj constraints *)
2406 ~text: "Constraints on constants" () in
2408 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
2411 GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
2414 ~text: "You can now specify the constraints on constants."
2415 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2416 let expected_height = 25 * (List.length must_obj + 2) in
2417 let height = if expected_height > 400 then 400 else expected_height in
2418 let scrolled_window =
2419 GBin.scrolled_window ~border_width:10 ~height ~width:600
2420 ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
2421 let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
2422 let obj_constraints =
2424 (function (uri,position,depth) ->
2427 ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
2430 ~text:(uri ^ " " ^ position)
2431 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2433 None -> uri, position, ref None
2435 let mutable_ref = ref (Some depth') in
2437 GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
2439 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2442 (depthb#connect#toggled
2444 let sel_depth = if depthb#active then Some depth' else None in
2445 mutable_ref := sel_depth
2447 uri, position, mutable_ref
2449 (* Confirm/abort buttons *)
2451 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2453 GButton.button ~label:"Ok"
2454 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2456 GButton.button ~label:"Abort"
2457 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2459 ignore (window#connect#destroy GMain.Main.quit) ;
2460 ignore (cancelb#connect#clicked window#destroy) ;
2462 (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
2463 window#set_position `CENTER ;
2465 GMain.Main.main () ;
2467 let chosen_must_rel =
2469 (function (position,ref_depth) -> position,!ref_depth) rel_constraints in
2470 let chosen_must_sort =
2472 (function (position,ref_depth,sort) -> position,!ref_depth,sort)
2475 let chosen_must_obj =
2477 (function (uri,position,ref_depth) -> uri,position,!ref_depth)
2480 (chosen_must_obj,chosen_must_rel,chosen_must_sort),
2482 (*CSC: ???????????????????????? I assume that must and only are the same... *)
2483 Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
2491 let completeSearchPattern () =
2492 let inputt = ((rendering_window ())#inputt : term_editor) in
2493 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2495 let metasenv,expr = inputt#get_metasenv_and_term ~context:[] ~metasenv:[] in
2496 let must = MQueryLevels2.get_constraints expr in
2497 let must',only = refine_constraints must in
2498 let results = MQueryGenerator.searchPattern must' only in
2499 show_query_results results
2502 output_html outputhtml
2503 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2506 let insertQuery () =
2507 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2509 let chosen = ref None in
2512 ~modal:true ~title:"Insert Query (Experts Only)" ~border_width:2 () in
2513 let vbox = GPack.vbox ~packing:window#add () in
2515 GMisc.label ~text:"Insert Query. For Experts Only."
2516 ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2517 let scrolled_window =
2518 GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
2519 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2520 let input = GEdit.text ~editable:true
2521 ~packing:scrolled_window#add () in
2523 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2525 GButton.button ~label:"Ok"
2526 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2528 GButton.button ~label:"Load from file..."
2529 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2531 GButton.button ~label:"Abort"
2532 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2533 ignore (window#connect#destroy GMain.Main.quit) ;
2534 ignore (cancelb#connect#clicked window#destroy) ;
2536 (okb#connect#clicked
2538 chosen := Some (input#get_chars 0 input#length) ; window#destroy ())) ;
2540 (loadb#connect#clicked
2543 GToolbox.select_file ~title:"Select Query File" ()
2547 let inch = open_in filename in
2548 let rec read_file () =
2550 let line = input_line inch in
2551 line ^ "\n" ^ read_file ()
2555 let text = read_file () in
2556 input#delete_text 0 input#length ;
2557 ignore (input#insert_text text ~pos:0))) ;
2558 window#set_position `CENTER ;
2560 GMain.Main.main () ;
2565 Mqint.execute (MQueryUtil.query_of_text (Lexing.from_string q))
2567 show_query_results results
2570 output_html outputhtml
2571 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2574 let choose_must list_of_must only =
2575 let chosen = ref None in
2576 let user_constraints = ref [] in
2579 ~modal:true ~title:"Query refinement." ~border_width:2 () in
2580 let vbox = GPack.vbox ~packing:window#add () in
2582 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2586 ("You can now specify the genericity of the query. " ^
2587 "The more generic the slower.")
2588 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2590 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2594 "Suggestion: start with faster queries before moving to more generic ones."
2595 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2597 GPack.notebook ~scrollable:true
2598 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2601 let last = List.length list_of_must in
2607 (if !page = 1 then "More generic" else
2608 if !page = last then "More precise" else " ") () in
2609 let expected_height = 25 * (List.length must + 2) in
2610 let height = if expected_height > 400 then 400 else expected_height in
2611 let scrolled_window =
2612 GBin.scrolled_window ~border_width:10 ~height ~width:600
2613 ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2615 GList.clist ~columns:2 ~packing:scrolled_window#add
2616 ~titles:["URI" ; "Position"] ()
2620 (function (uri,position) ->
2623 [uri; if position then "MainConclusion" else "Conclusion"]
2625 clist#set_row ~selectable:false n
2628 clist#columns_autosize ()
2631 let label = GMisc.label ~text:"User provided" () in
2633 GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2635 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2638 ~text:"Select the constraints that must be satisfied and press OK."
2639 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2640 let expected_height = 25 * (List.length only + 2) in
2641 let height = if expected_height > 400 then 400 else expected_height in
2642 let scrolled_window =
2643 GBin.scrolled_window ~border_width:10 ~height ~width:600
2644 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2646 GList.clist ~columns:2 ~packing:scrolled_window#add
2647 ~selection_mode:`EXTENDED
2648 ~titles:["URI" ; "Position"] ()
2652 (function (uri,position) ->
2655 [uri; if position then "MainConclusion" else "Conclusion"]
2657 clist#set_row ~selectable:true n
2660 clist#columns_autosize () ;
2662 (clist#connect#select_row
2663 (fun ~row ~column ~event ->
2664 user_constraints := (List.nth only row)::!user_constraints)) ;
2666 (clist#connect#unselect_row
2667 (fun ~row ~column ~event ->
2670 (function uri -> uri != (List.nth only row)) !user_constraints)) ;
2673 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2675 GButton.button ~label:"Ok"
2676 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2678 GButton.button ~label:"Abort"
2679 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2681 ignore (window#connect#destroy GMain.Main.quit) ;
2682 ignore (cancelb#connect#clicked window#destroy) ;
2684 (okb#connect#clicked
2685 (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2686 window#set_position `CENTER ;
2688 GMain.Main.main () ;
2690 None -> raise NoChoice
2692 if n = List.length list_of_must then
2693 (* user provided constraints *)
2696 List.nth list_of_must n
2699 let searchPattern () =
2700 let inputt = ((rendering_window ())#inputt : term_editor) in
2701 let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2704 match !ProofEngine.proof with
2705 None -> assert false
2706 | Some (_,metasenv,_,_) -> metasenv
2708 match !ProofEngine.goal with
2711 let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
2712 let list_of_must,only = MQueryLevels.out_restr metasenv ey ty in
2713 let must = choose_must list_of_must only in
2714 let torigth_restriction (u,b) =
2717 "http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion"
2719 "http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion"
2723 let rigth_must = List.map torigth_restriction must in
2724 let rigth_only = Some (List.map torigth_restriction only) in
2726 MQueryGenerator.searchPattern
2727 (rigth_must,[],[]) (rigth_only,None,None) in
2731 Disambiguate.wrong_xpointer_format_from_wrong_xpointer_format' uri
2734 " <h1>Backward Query: </h1>" ^
2735 " <pre>" ^ get_last_query result ^ "</pre>"
2737 output_html outputhtml html ;
2739 let rec filter_out =
2743 let tl',exc = filter_out tl in
2746 ProofEngine.can_apply
2747 (term_of_cic_textual_parser_uri
2748 (Disambiguate.cic_textual_parser_uri_of_string uri))
2756 "<h1 color=\"red\"> ^ Exception raised trying to apply " ^
2757 uri ^ ": " ^ Printexc.to_string e ^ " </h1>" ^ exc
2764 " <h1>Objects that can actually be applied: </h1> " ^
2765 String.concat "<br>" uris' ^ exc ^
2766 " <h1>Number of false matches: " ^
2767 string_of_int (List.length uris - List.length uris') ^ "</h1>" ^
2768 " <h1>Number of good matches: " ^
2769 string_of_int (List.length uris') ^ "</h1>"
2771 output_html outputhtml html' ;
2773 user_uri_choice ~title:"Ambiguous input."
2775 "Many lemmas can be successfully applied. Please, choose one:"
2778 inputt#set_term uri' ;
2782 output_html outputhtml
2783 ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2786 let choose_selection
2787 (mmlwidget : GMathViewAux.single_selection_math_view) (element : Gdome.element option)
2789 let module G = Gdome in
2790 let rec aux element =
2791 if element#hasAttributeNS
2792 ~namespaceURI:helmns
2793 ~localName:(G.domString "xref")
2795 mmlwidget#set_selection (Some element)
2798 match element#get_parentNode with
2799 None -> assert false
2800 (*CSC: OCAML DIVERGES!
2801 | Some p -> aux (new G.element_of_node p)
2803 | Some p -> aux (new Gdome.element_of_node p)
2805 GdomeInit.DOMCastException _ ->
2806 Printf.printf "******* trying to select above the document root ********\n" ; flush stdout
2811 | None -> mmlwidget#set_selection None
2814 (* STUFF TO BUILD THE GTK INTERFACE *)
2816 (* Stuff for the widget settings *)
2818 let export_to_postscript (output : GMathViewAux.single_selection_math_view) =
2819 let lastdir = ref (Unix.getcwd ()) in
2822 GToolbox.select_file ~title:"Export to PostScript"
2823 ~dir:lastdir ~filename:"screenshot.ps" ()
2827 output#export_to_postscript ~filename:filename ();
2830 let activate_t1 (output : GMathViewAux.single_selection_math_view) button_set_anti_aliasing
2831 button_set_transparency export_to_postscript_menu_item
2834 let is_set = button_t1#active in
2835 output#set_font_manager_type
2836 (if is_set then `font_manager_t1 else `font_manager_gtk) ;
2839 button_set_anti_aliasing#misc#set_sensitive true ;
2840 button_set_transparency#misc#set_sensitive true ;
2841 export_to_postscript_menu_item#misc#set_sensitive true ;
2845 button_set_anti_aliasing#misc#set_sensitive false ;
2846 button_set_transparency#misc#set_sensitive false ;
2847 export_to_postscript_menu_item#misc#set_sensitive false ;
2851 let set_anti_aliasing output button_set_anti_aliasing () =
2852 output#set_anti_aliasing button_set_anti_aliasing#active
2855 let set_transparency output button_set_transparency () =
2856 output#set_transparency button_set_transparency#active
2859 let changefont output font_size_spinb () =
2860 output#set_font_size font_size_spinb#value_as_int
2863 let set_log_verbosity output log_verbosity_spinb () =
2864 output#set_log_verbosity log_verbosity_spinb#value_as_int
2867 class settings_window (output : GMathViewAux.single_selection_math_view) sw
2868 export_to_postscript_menu_item selection_changed_callback
2870 let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2872 GPack.vbox ~packing:settings_window#add () in
2875 ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2876 ~border_width:5 ~packing:vbox#add () in
2878 GButton.toggle_button ~label:"activate t1 fonts"
2879 ~packing:(table#attach ~left:0 ~top:0) () in
2880 let button_set_anti_aliasing =
2881 GButton.toggle_button ~label:"set_anti_aliasing"
2882 ~packing:(table#attach ~left:0 ~top:1) () in
2883 let button_set_transparency =
2884 GButton.toggle_button ~label:"set_transparency"
2885 ~packing:(table#attach ~left:2 ~top:1) () in
2888 ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2889 ~border_width:5 ~packing:vbox#add () in
2890 let font_size_label =
2891 GMisc.label ~text:"font size:"
2892 ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2893 let font_size_spinb =
2895 GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2898 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2899 let log_verbosity_label =
2900 GMisc.label ~text:"log verbosity:"
2901 ~packing:(table#attach ~left:0 ~top:1) () in
2902 let log_verbosity_spinb =
2904 GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2907 ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2909 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2911 GButton.button ~label:"Close"
2912 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2914 method show = settings_window#show
2916 button_set_anti_aliasing#misc#set_sensitive false ;
2917 button_set_transparency#misc#set_sensitive false ;
2918 (* Signals connection *)
2919 ignore(button_t1#connect#clicked
2920 (activate_t1 output button_set_anti_aliasing
2921 button_set_transparency export_to_postscript_menu_item button_t1)) ;
2922 ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2923 ignore(button_set_anti_aliasing#connect#toggled
2924 (set_anti_aliasing output button_set_anti_aliasing));
2925 ignore(button_set_transparency#connect#toggled
2926 (set_transparency output button_set_transparency)) ;
2927 ignore(log_verbosity_spinb#connect#changed
2928 (set_log_verbosity output log_verbosity_spinb)) ;
2929 ignore(closeb#connect#clicked settings_window#misc#hide)
2932 (* Scratch window *)
2934 class scratch_window =
2936 GWindow.window ~title:"MathML viewer" ~border_width:2 () in
2938 GPack.vbox ~packing:window#add () in
2940 GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2942 GButton.button ~label:"Whd"
2943 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2945 GButton.button ~label:"Reduce"
2946 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2948 GButton.button ~label:"Simpl"
2949 ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2950 let scrolled_window =
2951 GBin.scrolled_window ~border_width:10
2952 ~packing:(vbox#pack ~expand:true ~padding:5) () in
2954 GMathViewAux.single_selection_math_view
2955 ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
2957 method mmlwidget = mmlwidget
2958 method show () = window#misc#hide () ; window#show ()
2960 ignore(mmlwidget#connect#selection_changed (choose_selection mmlwidget)) ;
2961 ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
2962 ignore(whdb#connect#clicked (whd_in_scratch self)) ;
2963 ignore(reduceb#connect#clicked (reduce_in_scratch self)) ;
2964 ignore(simplb#connect#clicked (simpl_in_scratch self))
2968 let vbox1 = GPack.vbox () in
2970 val mutable proofw_ref = None
2971 val mutable compute_ref = None
2973 Lazy.force self#compute ;
2974 match proofw_ref with
2975 None -> assert false
2976 | Some proofw -> proofw
2977 method content = vbox1
2979 match compute_ref with
2980 None -> assert false
2981 | Some compute -> compute
2985 let scrolled_window1 =
2986 GBin.scrolled_window ~border_width:10
2987 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2989 GMathViewAux.single_selection_math_view ~width:400 ~height:275
2990 ~packing:(scrolled_window1#add) () in
2991 let _ = proofw_ref <- Some proofw in
2993 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2995 GButton.button ~label:"Exact"
2996 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2998 GButton.button ~label:"Intros"
2999 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3001 GButton.button ~label:"Apply"
3002 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3003 let elimintrossimplb =
3004 GButton.button ~label:"ElimIntrosSimpl"
3005 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3007 GButton.button ~label:"ElimType"
3008 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3010 GButton.button ~label:"Whd"
3011 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3013 GButton.button ~label:"Reduce"
3014 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3016 GButton.button ~label:"Simpl"
3017 ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3019 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3021 GButton.button ~label:"Fold_whd"
3022 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3024 GButton.button ~label:"Fold_reduce"
3025 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3027 GButton.button ~label:"Fold_simpl"
3028 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3030 GButton.button ~label:"Cut"
3031 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3033 GButton.button ~label:"Change"
3034 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3036 GButton.button ~label:"Let ... In"
3037 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3039 GButton.button ~label:"Ring"
3040 ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3042 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3044 GButton.button ~label:"ClearBody"
3045 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3047 GButton.button ~label:"Clear"
3048 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3050 GButton.button ~label:"Fourier"
3051 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3053 GButton.button ~label:"RewriteSimpl ->"
3054 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3055 let rewritebacksimplb =
3056 GButton.button ~label:"RewriteSimpl <-"
3057 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3059 GButton.button ~label:"Replace"
3060 ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3062 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3064 GButton.button ~label:"Reflexivity"
3065 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3067 GButton.button ~label:"Symmetry"
3068 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3070 GButton.button ~label:"Transitivity"
3071 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3073 GButton.button ~label:"Exists"
3074 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3076 GButton.button ~label:"Split"
3077 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3079 GButton.button ~label:"Left"
3080 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3082 GButton.button ~label:"Right"
3083 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3085 GButton.button ~label:"Assumption"
3086 ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3088 GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3090 GButton.button ~label:"Generalize"
3091 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
3093 GButton.button ~label:"Absurd"
3094 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
3095 let contradictionb =
3096 GButton.button ~label:"Contradiction"
3097 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
3098 let searchpatternb =
3099 GButton.button ~label:"SearchPattern_Apply"
3100 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
3102 GButton.button ~label:"Decompose"
3103 ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
3105 ignore(exactb#connect#clicked exact) ;
3106 ignore(applyb#connect#clicked apply) ;
3107 ignore(elimintrossimplb#connect#clicked elimintrossimpl) ;
3108 ignore(elimtypeb#connect#clicked elimtype) ;
3109 ignore(whdb#connect#clicked whd) ;
3110 ignore(reduceb#connect#clicked reduce) ;
3111 ignore(simplb#connect#clicked simpl) ;
3112 ignore(foldwhdb#connect#clicked fold_whd) ;
3113 ignore(foldreduceb#connect#clicked fold_reduce) ;
3114 ignore(foldsimplb#connect#clicked fold_simpl) ;
3115 ignore(cutb#connect#clicked cut) ;
3116 ignore(changeb#connect#clicked change) ;
3117 ignore(letinb#connect#clicked letin) ;
3118 ignore(ringb#connect#clicked ring) ;
3119 ignore(clearbodyb#connect#clicked clearbody) ;
3120 ignore(clearb#connect#clicked clear) ;
3121 ignore(fourierb#connect#clicked fourier) ;
3122 ignore(rewritesimplb#connect#clicked rewritesimpl) ;
3123 ignore(rewritebacksimplb#connect#clicked rewritebacksimpl) ;
3124 ignore(replaceb#connect#clicked replace) ;
3125 ignore(reflexivityb#connect#clicked reflexivity) ;
3126 ignore(symmetryb#connect#clicked symmetry) ;
3127 ignore(transitivityb#connect#clicked transitivity) ;
3128 ignore(existsb#connect#clicked exists) ;
3129 ignore(splitb#connect#clicked split) ;
3130 ignore(leftb#connect#clicked left) ;
3131 ignore(rightb#connect#clicked right) ;
3132 ignore(assumptionb#connect#clicked assumption) ;
3133 ignore(generalizeb#connect#clicked generalize) ;
3134 ignore(absurdb#connect#clicked absurd) ;
3135 ignore(contradictionb#connect#clicked contradiction) ;
3136 ignore(introsb#connect#clicked intros) ;
3137 ignore(searchpatternb#connect#clicked searchPattern) ;
3138 ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
3139 ignore(decomposeb#connect#clicked decompose) ;
3145 let vbox1 = GPack.vbox () in
3146 let scrolled_window1 =
3147 GBin.scrolled_window ~border_width:10
3148 ~packing:(vbox1#pack ~expand:true ~padding:5) () in
3150 GMathViewAux.single_selection_math_view ~width:400 ~height:275
3151 ~packing:(scrolled_window1#add) () in
3153 method proofw = (assert false : GMathViewAux.single_selection_math_view)
3154 method content = vbox1
3155 method compute = (assert false : unit)
3159 let empty_page = new empty_page;;
3163 val notebook = GPack.notebook ()
3165 val mutable skip_switch_page_event = false
3166 val mutable empty = true
3167 method notebook = notebook
3169 let new_page = new page () in
3171 pages := !pages @ [n,lazy (setgoal n),new_page] ;
3172 notebook#append_page
3173 ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
3174 new_page#content#coerce
3175 method remove_all_pages ~skip_switch_page_event:skip =
3177 notebook#remove_page 0 (* let's remove the empty page *)
3179 List.iter (function _ -> notebook#remove_page 0) !pages ;
3181 skip_switch_page_event <- skip
3182 method set_current_page ~may_skip_switch_page_event n =
3183 let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
3184 let new_page = notebook#page_num page#content#coerce in
3185 if may_skip_switch_page_event && new_page <> notebook#current_page then
3186 skip_switch_page_event <- true ;
3187 notebook#goto_page new_page
3188 method set_empty_page =
3191 notebook#append_page
3192 ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
3193 empty_page#content#coerce
3195 let (_,_,page) = List.nth !pages notebook#current_page in
3199 (notebook#connect#switch_page
3201 let skip = skip_switch_page_event in
3202 skip_switch_page_event <- false ;
3205 let (metano,setgoal,page) = List.nth !pages i in
3206 ProofEngine.goal := Some metano ;
3207 Lazy.force (page#compute) ;
3216 class rendering_window output (notebook : notebook) =
3217 let scratch_window = new scratch_window in
3219 GWindow.window ~title:"MathML viewer" ~border_width:0
3220 ~allow_shrink:false () in
3221 let vbox_for_menu = GPack.vbox ~packing:window#add () in
3223 let handle_box = GBin.handle_box ~border_width:2
3224 ~packing:(vbox_for_menu#pack ~padding:0) () in
3225 let menubar = GMenu.menu_bar ~packing:handle_box#add () in
3226 let factory0 = new GMenu.factory menubar in
3227 let accel_group = factory0#accel_group in
3229 let file_menu = factory0#add_submenu "File" in
3230 let factory1 = new GMenu.factory file_menu ~accel_group in
3231 let export_to_postscript_menu_item =
3234 factory1#add_item "New Block of (Co)Inductive Definitions..."
3235 ~key:GdkKeysyms._B ~callback:new_inductive
3238 factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
3241 let reopen_menu_item =
3242 factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
3246 factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
3247 ignore (factory1#add_separator ()) ;
3249 (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
3251 let save_menu_item =
3252 factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S ~callback:save
3255 (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
3256 ignore (!save_set_sensitive false);
3257 ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
3258 ignore (!qed_set_sensitive false);
3259 ignore (factory1#add_separator ()) ;
3260 let export_to_postscript_menu_item =
3261 factory1#add_item "Export to PostScript..."
3262 ~callback:(export_to_postscript output) in
3263 ignore (factory1#add_separator ()) ;
3265 (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) ;
3266 export_to_postscript_menu_item
3269 let edit_menu = factory0#add_submenu "Edit Current Proof" in
3270 let factory2 = new GMenu.factory edit_menu ~accel_group in
3271 let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
3272 let proveit_menu_item =
3273 factory2#add_item "Prove It" ~key:GdkKeysyms._I
3274 ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
3276 let focus_menu_item =
3277 factory2#add_item "Focus" ~key:GdkKeysyms._F
3278 ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
3281 focus_and_proveit_set_sensitive :=
3283 proveit_menu_item#misc#set_sensitive b ;
3284 focus_menu_item#misc#set_sensitive b
3286 let _ = !focus_and_proveit_set_sensitive false in
3287 (* edit term menu *)
3288 let edit_term_menu = factory0#add_submenu "Edit Term" in
3289 let factory5 = new GMenu.factory edit_term_menu ~accel_group in
3290 let check_menu_item =
3291 factory5#add_item "Check Term" ~key:GdkKeysyms._C
3292 ~callback:(check scratch_window) in
3293 let _ = check_menu_item#misc#set_sensitive false in
3295 let settings_menu = factory0#add_submenu "Search" in
3296 let factory4 = new GMenu.factory settings_menu ~accel_group in
3298 factory4#add_item "Locate..." ~key:GdkKeysyms._T
3300 let searchPattern_menu_item =
3301 factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
3302 ~callback:completeSearchPattern in
3303 let _ = searchPattern_menu_item#misc#set_sensitive false in
3304 let show_menu_item =
3305 factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
3307 let insert_query_item =
3308 factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._U
3309 ~callback:insertQuery in
3311 let settings_menu = factory0#add_submenu "Settings" in
3312 let factory3 = new GMenu.factory settings_menu ~accel_group in
3314 factory3#add_item "Edit Aliases" ~key:GdkKeysyms._A
3315 ~callback:edit_aliases in
3316 let _ = factory3#add_separator () in
3318 factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
3319 ~callback:(function _ -> (settings_window ())#show ()) in
3321 let _ = window#add_accel_group accel_group in
3325 ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
3327 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
3328 let scrolled_window0 =
3329 GBin.scrolled_window ~border_width:10
3330 ~packing:(vbox#pack ~expand:true ~padding:5) () in
3331 let _ = scrolled_window0#add output#coerce in
3333 GBin.frame ~label:"Insert Term"
3334 ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
3335 let scrolled_window1 =
3336 GBin.scrolled_window ~border_width:5
3337 ~packing:frame#add () in
3339 new term_editor ~width:400 ~height:100 ~packing:scrolled_window1#add ()
3340 ~isnotempty_callback:
3342 check_menu_item#misc#set_sensitive b ;
3343 searchPattern_menu_item#misc#set_sensitive b) in
3345 GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
3347 vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
3349 GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
3353 ~source:"<html><body bgColor=\"white\"></body></html>"
3354 ~width:400 ~height: 100
3359 method outputhtml = outputhtml
3360 method inputt = inputt
3361 method output = (output : GMathViewAux.single_selection_math_view)
3362 method notebook = notebook
3363 method show = window#show
3365 notebook#set_empty_page ;
3366 export_to_postscript_menu_item#misc#set_sensitive false ;
3367 check_term := (check_term_in_scratch scratch_window) ;
3369 (* signal handlers here *)
3370 ignore(output#connect#selection_changed
3372 choose_selection output elem ;
3373 !focus_and_proveit_set_sensitive true
3375 ignore (output#connect#click (show_in_show_window_callback output)) ;
3376 let settings_window = new settings_window output scrolled_window0
3377 export_to_postscript_menu_item (choose_selection output) in
3378 set_settings_window settings_window ;
3379 set_outputhtml outputhtml ;
3380 ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
3381 Logger.log_callback :=
3382 (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
3387 let initialize_everything () =
3388 let module U = Unix in
3389 let output = GMathViewAux.single_selection_math_view ~width:350 ~height:280 () in
3390 let notebook = new notebook in
3391 let rendering_window' = new rendering_window output notebook in
3392 set_rendering_window rendering_window' ;
3393 mml_of_cic_term_ref := mml_of_cic_term ;
3394 rendering_window'#show () ;
3401 Mqint.set_database Mqint.postgres_db ;
3402 Mqint.init postgresqlconnectionstring ;
3404 ignore (GtkMain.Main.init ()) ;
3405 initialize_everything () ;
3406 if !usedb then Mqint.close ();