]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/gTopLevel.ml
- added HBugs support
[helm.git] / helm / gTopLevel / gTopLevel.ml
1 (* Copyright (C) 2000-2002, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 (******************************************************************************)
27 (*                                                                            *)
28 (*                               PROJECT HELM                                 *)
29 (*                                                                            *)
30 (*                Claudio Sacerdoti Coen <sacerdot@cs.unibo.it>               *)
31 (*                                 06/01/2002                                 *)
32 (*                                                                            *)
33 (*                                                                            *)
34 (******************************************************************************)
35
36 open Printf;;
37
38 (* DEBUGGING *)
39
40 let debug_print = 
41   let debug = true in
42   fun s -> prerr_endline (sprintf "DEBUG: %s" s)
43 ;;
44
45 (* GLOBAL CONSTANTS *)
46
47 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
48
49 let htmlheader =
50  "<html>" ^
51  " <body bgColor=\"white\">"
52 ;;
53
54 let htmlfooter =
55  " </body>" ^
56  "</html>"
57 ;;
58
59 let prooffile =
60  try
61   Sys.getenv "GTOPLEVEL_PROOFFILE"
62  with
63   Not_found -> "/public/currentproof"
64 ;;
65
66 let prooffiletype =
67  try
68   Sys.getenv "GTOPLEVEL_PROOFFILETYPE"
69  with
70   Not_found -> "/public/currentprooftype"
71 ;;
72
73 let postgresqlconnectionstring =
74  try
75   Sys.getenv "POSTGRESQL_CONNECTION_STRING"
76  with
77   Not_found -> "host=mowgli.cs.unibo.it dbname=helm_mowgli_new_schema user=helm"
78 ;;
79
80 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
81
82 let htmlheader_and_content = ref htmlheader;;
83
84 let check_term = ref (fun _ _ _ -> assert false);;
85
86 exception RenderingWindowsNotInitialized;;
87
88 let set_rendering_window,rendering_window =
89  let rendering_window_ref = ref None in
90   (function rw -> rendering_window_ref := Some rw),
91   (function () ->
92     match !rendering_window_ref with
93        None -> raise RenderingWindowsNotInitialized
94      | Some rw -> rw
95   )
96 ;;
97
98 exception SettingsWindowsNotInitialized;;
99
100 let set_settings_window,settings_window =
101  let settings_window_ref = ref None in
102   (function rw -> settings_window_ref := Some rw),
103   (function () ->
104     match !settings_window_ref with
105        None -> raise SettingsWindowsNotInitialized
106      | Some rw -> rw
107   )
108 ;;
109
110 exception OutputHtmlNotInitialized;;
111
112 let set_outputhtml,outputhtml =
113  let outputhtml_ref = ref None in
114   (function rw -> outputhtml_ref := Some rw),
115   (function () ->
116     match !outputhtml_ref with
117        None -> raise OutputHtmlNotInitialized
118      | Some outputhtml -> outputhtml
119   )
120 ;;
121
122 exception QedSetSensitiveNotInitialized;;
123 let qed_set_sensitive =
124  ref (function _ -> raise QedSetSensitiveNotInitialized)
125 ;;
126
127 exception SaveSetSensitiveNotInitialized;;
128 let save_set_sensitive =
129  ref (function _ -> raise SaveSetSensitiveNotInitialized)
130 ;;
131
132 (* COMMAND LINE OPTIONS *)
133
134 let usedb = ref true
135
136 let argspec =
137   [
138     "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
139   ]
140 in
141 Arg.parse argspec ignore ""
142
143 (* MISC FUNCTIONS *)
144
145 let term_of_cic_textual_parser_uri uri =
146  let module C = Cic in
147  let module CTP = CicTextualParser0 in
148   match uri with
149      CTP.ConUri uri -> C.Const (uri,[])
150    | CTP.VarUri uri -> C.Var (uri,[])
151    | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
152    | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
153 ;;
154
155 let string_of_cic_textual_parser_uri uri =
156  let module C = Cic in
157  let module CTP = CicTextualParser0 in
158   let uri' =
159    match uri with
160       CTP.ConUri uri -> UriManager.string_of_uri uri
161     | CTP.VarUri uri -> UriManager.string_of_uri uri
162     | CTP.IndTyUri (uri,tyno) ->
163        UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
164     | CTP.IndConUri (uri,tyno,consno) ->
165        UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
166         string_of_int consno
167   in
168    (* 4 = String.length "cic:" *)
169    String.sub uri' 4 (String.length uri' - 4)
170 ;;
171
172 let output_html outputhtml msg =
173  htmlheader_and_content := !htmlheader_and_content ^ msg ;
174  outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
175  outputhtml#set_topline (-1)
176 ;;
177
178 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
179
180 (* Check window *)
181
182 let check_window outputhtml uris =
183  let window =
184   GWindow.window
185    ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
186  let notebook =
187   GPack.notebook ~scrollable:true ~packing:window#add () in
188  window#show () ;
189  let render_terms =
190   List.map
191    (function uri ->
192      let scrolled_window =
193       GBin.scrolled_window ~border_width:10
194        ~packing:
195          (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
196        ()
197      in
198       lazy 
199        (let mmlwidget =
200          TermViewer.sequent_viewer
201           ~packing:scrolled_window#add ~width:400 ~height:280 () in
202         let expr =
203          let term =
204           term_of_cic_textual_parser_uri
205            (MQueryMisc.cic_textual_parser_uri_of_string uri)
206          in
207           (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
208         in
209          try
210           mmlwidget#load_sequent [] (111,[],expr)
211          with
212           e ->
213            output_html outputhtml
214             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
215        )
216    ) uris
217  in
218   ignore
219    (notebook#connect#switch_page
220      (function i -> Lazy.force (List.nth render_terms i)))
221 ;;
222
223 exception NoChoice;;
224
225 let
226  interactive_user_uri_choice ~(selection_mode:[`SINGLE|`EXTENDED]) ?(ok="Ok")
227   ?(enable_button_for_non_vars=false) ~title ~msg uris
228 =
229  let choices = ref [] in
230  let chosen = ref false in
231  let use_only_constants = ref false in
232  let window =
233   GWindow.dialog ~modal:true ~title ~width:600 () in
234  let lMessage =
235   GMisc.label ~text:msg
236    ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
237  let scrolled_window =
238   GBin.scrolled_window ~border_width:10
239    ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
240  let clist =
241   let expected_height = 18 * List.length uris in
242    let height = if expected_height > 400 then 400 else expected_height in
243     GList.clist ~columns:1 ~packing:scrolled_window#add
244      ~height ~selection_mode:(selection_mode :> Gtk.Tags.selection_mode) () in
245  let _ = List.map (function x -> clist#append [x]) uris in
246  let hbox2 =
247   GPack.hbox ~border_width:0
248    ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
249  let explain_label =
250   GMisc.label ~text:"None of the above. Try this one:"
251    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
252  let manual_input =
253   GEdit.entry ~editable:true
254    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
255  let hbox =
256   GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
257  let okb =
258   GButton.button ~label:ok
259    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
260  let _ = okb#misc#set_sensitive false in
261  let nonvarsb =
262   GButton.button
263    ~packing:
264     (function w ->
265       if enable_button_for_non_vars then
266        hbox#pack ~expand:false ~fill:false ~padding:5 w)
267    ~label:"Try constants only" () in
268  let checkb =
269   GButton.button ~label:"Check"
270    ~packing:(hbox#pack ~padding:5) () in
271  let _ = checkb#misc#set_sensitive false in
272  let cancelb =
273   GButton.button ~label:"Abort"
274    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
275  (* actions *)
276  let check_callback () =
277   assert (List.length !choices > 0) ;
278   check_window (outputhtml ()) !choices
279  in
280   ignore (window#connect#destroy GMain.Main.quit) ;
281   ignore (cancelb#connect#clicked window#destroy) ;
282   ignore
283    (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
284   ignore
285    (nonvarsb#connect#clicked
286      (function () ->
287        use_only_constants := true ;
288        chosen := true ;
289        window#destroy ()
290    )) ;
291   ignore (checkb#connect#clicked check_callback) ;
292   ignore
293    (clist#connect#select_row
294      (fun ~row ~column ~event ->
295        checkb#misc#set_sensitive true ;
296        okb#misc#set_sensitive true ;
297        choices := (List.nth uris row)::!choices)) ;
298   ignore
299    (clist#connect#unselect_row
300      (fun ~row ~column ~event ->
301        choices :=
302         List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
303   ignore
304    (manual_input#connect#changed
305      (fun _ ->
306        if manual_input#text = "" then
307         begin
308          choices := [] ;
309          checkb#misc#set_sensitive false ;
310          okb#misc#set_sensitive false ;
311          clist#misc#set_sensitive true
312         end
313        else
314         begin
315          choices := [manual_input#text] ;
316          clist#unselect_all () ;
317          checkb#misc#set_sensitive true ;
318          okb#misc#set_sensitive true ;
319          clist#misc#set_sensitive false
320         end));
321   window#set_position `CENTER ;
322   window#show () ;
323   GtkThread.main ();
324   if !chosen then
325    if !use_only_constants then
326     List.filter
327      (function uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
328      uris
329    else
330     if List.length !choices > 0 then !choices else raise NoChoice
331   else
332    raise NoChoice
333 ;;
334
335 let interactive_interpretation_choice interpretations =
336  let chosen = ref None in
337  let window =
338   GWindow.window
339    ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
340  let vbox = GPack.vbox ~packing:window#add () in
341  let lMessage =
342   GMisc.label
343    ~text:
344     ("Ambiguous input since there are many well-typed interpretations." ^
345      " Please, choose one of them.")
346    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
347  let notebook =
348   GPack.notebook ~scrollable:true
349    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
350  let _ =
351   List.map
352    (function interpretation ->
353      let clist =
354       let expected_height = 18 * List.length interpretation in
355        let height = if expected_height > 400 then 400 else expected_height in
356         GList.clist ~columns:2 ~packing:notebook#append_page ~height
357          ~titles:["id" ; "URI"] ()
358      in
359       ignore
360        (List.map
361          (function (id,uri) ->
362            let n = clist#append [id;uri] in
363             clist#set_row ~selectable:false n
364          ) interpretation
365        ) ;
366       clist#columns_autosize ()
367    ) interpretations in
368  let hbox =
369   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
370  let okb =
371   GButton.button ~label:"Ok"
372    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
373  let cancelb =
374   GButton.button ~label:"Abort"
375    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
376  (* actions *)
377  ignore (window#connect#destroy GMain.Main.quit) ;
378  ignore (cancelb#connect#clicked window#destroy) ;
379  ignore
380   (okb#connect#clicked
381     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
382  window#set_position `CENTER ;
383  window#show () ;
384  GtkThread.main ();
385  match !chosen with
386     None -> raise NoChoice
387   | Some n -> n
388 ;;
389
390
391 (* MISC FUNCTIONS *)
392
393 (* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
394 (* FG : THIS FUNCTION IS BECOMING A REAL NONSENSE                   *)
395 let get_last_query = 
396  let query = ref "" in
397   let out s = query := ! query ^ s in
398   MQueryGenerator.set_confirm_query
399    (function q -> 
400     query := ""; MQueryUtil.text_of_query out q ""; true);
401   function result ->
402    out (!query ^ " <h1>Result:</h1> "); MQueryUtil.text_of_result out result "<br>";
403    !query
404 ;;
405
406 let
407  save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
408 =
409  let name =
410   let struri = UriManager.string_of_uri uri in
411   let idx = (String.rindex struri '/') + 1 in
412    String.sub struri idx (String.length struri - idx)
413  in
414   let path = pathname ^ "/" ^ name in
415   let xml, bodyxml =
416    Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
417     annobj 
418   in
419   let xmlinnertypes =
420    Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
421     ~ask_dtd_to_the_getter:false
422   in
423    (* innertypes *)
424    let innertypesuri = UriManager.innertypesuri_of_uri uri in
425     Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
426     Getter.register innertypesuri
427      (Configuration.annotations_url ^
428        Str.replace_first (Str.regexp "^cic:") ""
429         (UriManager.string_of_uri innertypesuri) ^ ".xml"
430      ) ;
431     (* constant type / variable / mutual inductive types definition *)
432     Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
433     Getter.register uri
434      (Configuration.annotations_url ^
435        Str.replace_first (Str.regexp "^cic:") ""
436         (UriManager.string_of_uri uri) ^ ".xml"
437      ) ;
438     match bodyxml with
439        None -> ()
440      | Some bodyxml' ->
441         (* constant body *)
442         let bodyuri =
443          match UriManager.bodyuri_of_uri uri with
444             None -> assert false
445           | Some bodyuri -> bodyuri
446         in
447          Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
448          Getter.register bodyuri
449           (Configuration.annotations_url ^
450             Str.replace_first (Str.regexp "^cic:") ""
451              (UriManager.string_of_uri bodyuri) ^ ".xml"
452           )
453 ;;
454
455
456 (* CALLBACKS *)
457
458 (*
459 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
460  ~name:"/home/galata/miohelm/guruguru1" ~indent:true ()) ;
461 *)
462
463 exception OpenConjecturesStillThere;;
464 exception WrongProof;;
465
466 let pathname_of_annuri uristring =
467  Configuration.annotations_dir ^    
468   Str.replace_first (Str.regexp "^cic:") "" uristring
469 ;;
470
471 let make_dirs dirpath =
472  ignore (Unix.system ("mkdir -p " ^ dirpath))
473 ;;
474
475 let save_obj uri obj =
476  let
477   (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
478    ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
479  =
480   Cic2acic.acic_object_of_cic_object obj
481  in
482   (* let's save the theorem and register it to the getter *) 
483   let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
484    make_dirs pathname ;
485    save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
486     pathname
487 ;;
488
489 let qed () =
490  match !ProofEngine.proof with
491     None -> assert false
492   | Some (uri,[],bo,ty) ->
493      if
494       CicReduction.are_convertible []
495        (CicTypeChecker.type_of_aux' [] [] bo) ty
496      then
497       begin
498        (*CSC: Wrong: [] is just plainly wrong *)
499        let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
500        let (acic,ids_to_inner_types,ids_to_inner_sorts) =
501         (rendering_window ())#output#load_proof uri proof
502        in
503         !qed_set_sensitive false ;
504         (* let's save the theorem and register it to the getter *) 
505         let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
506          make_dirs pathname ;
507          save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
508           pathname
509       end
510      else
511       raise WrongProof
512   | _ -> raise OpenConjecturesStillThere
513 ;;
514
515   (** save an unfinished proof on the filesystem *)
516 let save_unfinished_proof () =
517  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
518  let (xml, bodyxml) = ProofEngine.get_current_status_as_xml () in
519  Xml.pp ~quiet:true xml (Some prooffiletype) ;
520  output_html outputhtml
521   ("<h1 color=\"Green\">Current proof type saved to " ^
522    prooffiletype ^ "</h1>") ;
523  Xml.pp ~quiet:true bodyxml (Some prooffile) ;
524  output_html outputhtml
525   ("<h1 color=\"Green\">Current proof body saved to " ^
526    prooffile ^ "</h1>")
527 ;;
528
529 (* Used to typecheck the loaded proofs *)
530 let typecheck_loaded_proof metasenv bo ty =
531  let module T = CicTypeChecker in
532   ignore (
533    List.fold_left
534     (fun metasenv ((_,context,ty) as conj) ->
535       ignore (T.type_of_aux' metasenv context ty) ;
536       metasenv @ [conj]
537     ) [] metasenv) ;
538   ignore (T.type_of_aux' metasenv [] ty) ;
539   ignore (T.type_of_aux' metasenv [] bo)
540 ;;
541
542 let decompose_uris_choice_callback uris = 
543 (* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
544   let module U = UriManager in 
545    List.map 
546     (function uri ->
547       match MQueryMisc.cic_textual_parser_uri_of_string uri with
548          CicTextualParser0.IndTyUri (uri,typeno) -> (uri,typeno,[])
549        | _ -> assert false)
550     (interactive_user_uri_choice 
551       ~selection_mode:`EXTENDED ~ok:"Ok" ~enable_button_for_non_vars:false 
552       ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose" 
553       (List.map 
554         (function (uri,typeno,_) ->
555           U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1)
556         ) uris)
557     ) 
558 ;;
559
560 let mk_fresh_name_callback context name ~typ =
561  let fresh_name =
562   match ProofEngineHelpers.mk_fresh_name context name ~typ with
563      Cic.Name fresh_name -> fresh_name
564    | Cic.Anonymous -> assert false
565  in
566   match
567    GToolbox.input_string ~title:"Enter a fresh hypothesis name" ~text:fresh_name
568     ("Enter a fresh name for the hypothesis " ^
569       CicPp.pp typ
570        (List.map (function None -> None | Some (n,_) -> Some n) context))
571   with
572      Some fresh_name' -> Cic.Name fresh_name'
573    | None -> raise NoChoice
574 ;;
575
576 let refresh_proof (output : TermViewer.proof_viewer) =
577  try
578   let uri,currentproof =
579    match !ProofEngine.proof with
580       None -> assert false
581     | Some (uri,metasenv,bo,ty) ->
582        !qed_set_sensitive (List.length metasenv = 0) ;
583        (*CSC: Wrong: [] is just plainly wrong *)
584        uri,
585         (Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
586   in
587    ignore (output#load_proof uri currentproof)
588  with
589   e ->
590  match !ProofEngine.proof with
591     None -> assert false
592   | Some (uri,metasenv,bo,ty) ->
593 prerr_endline ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[]))) ; flush stderr ;
594    raise (InvokeTactics.RefreshProofException e)
595
596 let refresh_goals ?(empty_notebook=true) notebook =
597  try
598   match !ProofEngine.goal with
599      None ->
600       if empty_notebook then
601        begin 
602         notebook#remove_all_pages ~skip_switch_page_event:false ;
603         notebook#set_empty_page
604        end
605       else
606        notebook#proofw#unload
607    | Some metano ->
608       let metasenv =
609        match !ProofEngine.proof with
610           None -> assert false
611         | Some (_,metasenv,_,_) -> metasenv
612       in
613       let currentsequent =
614        List.find (function (m,_,_) -> m=metano) metasenv
615       in
616         let regenerate_notebook () = 
617          let skip_switch_page_event =
618           match metasenv with
619              (m,_,_)::_ when m = metano -> false
620            | _ -> true
621          in
622           notebook#remove_all_pages ~skip_switch_page_event ;
623           List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
624         in
625           if empty_notebook then
626            begin
627             regenerate_notebook () ;
628             notebook#set_current_page
629              ~may_skip_switch_page_event:false metano
630            end
631           else
632            begin
633             notebook#set_current_page
634              ~may_skip_switch_page_event:true metano ;
635             notebook#proofw#load_sequent metasenv currentsequent
636            end
637  with
638   e ->
639 let metano =
640   match !ProofEngine.goal with
641      None -> assert false
642    | Some m -> m
643 in
644 let metasenv =
645  match !ProofEngine.proof with
646     None -> assert false
647   | Some (_,metasenv,_,_) -> metasenv
648 in
649 try
650 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
651    prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
652       raise (InvokeTactics.RefreshSequentException e)
653 with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unknown."); raise (InvokeTactics.RefreshSequentException e)
654
655 let __notify_hbugs = ref None;;
656 module InvokeTacticsCallbacks =
657  struct
658   let sequent_viewer () = (rendering_window ())#notebook#proofw
659   let term_editor () = (rendering_window ())#inputt
660   let scratch_window () = (rendering_window ())#scratch_window
661
662   let refresh_proof () =
663    let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
664     refresh_proof output
665
666   let refresh_goals () =
667    let notebook = (rendering_window ())#notebook in
668     refresh_goals notebook
669
670   let decompose_uris_choice_callback = decompose_uris_choice_callback
671   let mk_fresh_name_callback = mk_fresh_name_callback
672   let output_html msg = output_html (outputhtml ()) msg
673   let notify_hbugs () =
674     match !__notify_hbugs with
675     | Some f -> f ()
676     | None -> assert false
677  end
678 ;;
679 module InvokeTactics' = InvokeTactics.Make (InvokeTacticsCallbacks);;
680 module Hbugs' = Hbugs.Make (InvokeTactics');;
681 __notify_hbugs := Some Hbugs'.notify;;
682
683   (** load an unfinished proof from filesystem *)
684 let load_unfinished_proof () =
685  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
686  let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
687  let notebook = (rendering_window ())#notebook in
688   try
689    match 
690     GToolbox.input_string ~title:"Load Unfinished Proof" ~text:"/dummy.con"
691      "Choose an URI:"
692    with
693       None -> raise NoChoice
694     | Some uri0 ->
695        let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
696         match CicParser.obj_of_xml prooffiletype (Some prooffile) with
697            Cic.CurrentProof (_,metasenv,bo,ty,_) ->
698             typecheck_loaded_proof metasenv bo ty ;
699             ProofEngine.proof :=
700              Some (uri, metasenv, bo, ty) ;
701             ProofEngine.goal :=
702              (match metasenv with
703                  [] -> None
704                | (metano,_,_)::_ -> Some metano
705              ) ;
706             refresh_proof output ;
707             refresh_goals notebook ;
708              output_html outputhtml
709               ("<h1 color=\"Green\">Current proof type loaded from " ^
710                 prooffiletype ^ "</h1>") ;
711              output_html outputhtml
712               ("<h1 color=\"Green\">Current proof body loaded from " ^
713                 prooffile ^ "</h1>") ;
714             !save_set_sensitive true;
715             Hbugs'.notify ()
716          | _ -> assert false
717   with
718      InvokeTactics.RefreshSequentException e ->
719       output_html outputhtml
720        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
721         "sequent: " ^ Printexc.to_string e ^ "</h1>")
722    | InvokeTactics.RefreshProofException e ->
723       output_html outputhtml
724        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
725         "proof: " ^ Printexc.to_string e ^ "</h1>")
726    | e ->
727       output_html outputhtml
728        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
729 ;;
730
731 let edit_aliases () =
732  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
733  let id_to_uris = inputt#id_to_uris in
734  let chosen = ref false in
735  let window =
736   GWindow.window
737    ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
738  let vbox =
739   GPack.vbox ~border_width:0 ~packing:window#add () in
740  let scrolled_window =
741   GBin.scrolled_window ~border_width:10
742    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
743  let input = GEdit.text ~editable:true ~width:400 ~height:100
744    ~packing:scrolled_window#add () in
745  let hbox =
746   GPack.hbox ~border_width:0
747    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
748  let okb =
749   GButton.button ~label:"Ok"
750    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
751  let cancelb =
752   GButton.button ~label:"Cancel"
753    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
754  ignore (window#connect#destroy GMain.Main.quit) ;
755  ignore (cancelb#connect#clicked window#destroy) ;
756  ignore
757   (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
758  let dom,resolve_id = !id_to_uris in
759   ignore
760    (input#insert_text ~pos:0
761     (String.concat "\n"
762       (List.map
763         (function v ->
764           let uri =
765            match resolve_id v with
766               None -> assert false
767             | Some uri -> uri
768           in
769            "alias " ^ v ^ " " ^
770              (string_of_cic_textual_parser_uri uri)
771         ) dom))) ;
772   window#show () ;
773   GtkThread.main ();
774   if !chosen then
775    let dom,resolve_id =
776     let inputtext = input#get_chars 0 input#length in
777     let regexpr =
778      let alfa = "[a-zA-Z_-]" in
779      let digit = "[0-9]" in
780      let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
781      let blanks = "\( \|\t\|\n\)+" in
782      let nonblanks = "[^ \t\n]+" in
783      let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
784       Str.regexp
785        ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
786     in
787      let rec aux n =
788       try
789        let n' = Str.search_forward regexpr inputtext n in
790         let id = Str.matched_group 2 inputtext in
791         let uri =
792          MQueryMisc.cic_textual_parser_uri_of_string
793           ("cic:" ^ (Str.matched_group 5 inputtext))
794         in
795          let dom,resolve_id = aux (n' + 1) in
796           if List.mem id dom then
797            dom,resolve_id
798           else
799            id::dom,
800             (function id' -> if id = id' then Some uri else resolve_id id')
801       with
802        Not_found -> TermEditor.empty_id_to_uris
803      in
804       aux 0
805    in
806     id_to_uris := (dom,resolve_id)
807 ;;
808
809 let proveit () =
810  let module L = LogicalOperations in
811  let module G = Gdome in
812  let notebook = (rendering_window ())#notebook in
813  let output = (rendering_window ())#output in
814  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
815   try
816    output#make_sequent_of_selected_term ;
817    refresh_proof output ;
818    refresh_goals notebook
819   with
820      InvokeTactics.RefreshSequentException e ->
821       output_html outputhtml
822        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
823         "sequent: " ^ Printexc.to_string e ^ "</h1>")
824    | InvokeTactics.RefreshProofException e ->
825       output_html outputhtml
826        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
827         "proof: " ^ Printexc.to_string e ^ "</h1>")
828    | e ->
829       output_html outputhtml
830        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
831 ;;
832
833 let focus () =
834  let module L = LogicalOperations in
835  let module G = Gdome in
836  let notebook = (rendering_window ())#notebook in
837  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
838  let output = (rendering_window ())#output in
839   try
840    output#focus_sequent_of_selected_term ;
841    refresh_goals notebook
842   with
843      InvokeTactics.RefreshSequentException e ->
844       output_html outputhtml
845        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
846         "sequent: " ^ Printexc.to_string e ^ "</h1>")
847    | InvokeTactics.RefreshProofException e ->
848       output_html outputhtml
849        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
850         "proof: " ^ Printexc.to_string e ^ "</h1>")
851    | e ->
852       output_html outputhtml
853        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
854 ;;
855
856 exception NoPrevGoal;;
857 exception NoNextGoal;;
858
859 let setgoal metano =
860  let module L = LogicalOperations in
861  let module G = Gdome in
862  let notebook = (rendering_window ())#notebook in
863  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
864   let metasenv =
865    match !ProofEngine.proof with
866       None -> assert false
867     | Some (_,metasenv,_,_) -> metasenv
868   in
869    try
870     refresh_goals ~empty_notebook:false notebook
871    with
872       InvokeTactics.RefreshSequentException e ->
873        output_html outputhtml
874         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
875          "sequent: " ^ Printexc.to_string e ^ "</h1>")
876     | e ->
877        output_html outputhtml
878         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
879 ;;
880
881 let
882  show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
883 =
884  let window =
885   GWindow.window ~width:800 ~border_width:2 () in
886  let scrolled_window =
887   GBin.scrolled_window ~border_width:10 ~packing:window#add () in
888  let mmlwidget =
889   GMathViewAux.single_selection_math_view
890     ~packing:scrolled_window#add ~width:600 ~height:400 ()
891  in
892  let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
893  let href = Gdome.domString "href" in
894   let show_in_show_window_obj uri obj =
895    let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
896     try
897      let
898       (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
899        ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
900      =
901       Cic2acic.acic_object_of_cic_object obj
902      in
903       let mml =
904        ApplyStylesheets.mml_of_cic_object
905         ~explode_all:false uri acic ids_to_inner_sorts ids_to_inner_types
906       in
907        window#set_title (UriManager.string_of_uri uri) ;
908        window#misc#hide () ; window#show () ;
909        mmlwidget#load_doc mml ;
910     with
911      e ->
912       output_html outputhtml
913        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
914   in
915   let show_in_show_window_uri uri =
916    let obj = CicEnvironment.get_obj uri in
917     show_in_show_window_obj uri obj
918   in
919    let show_in_show_window_callback mmlwidget (n : Gdome.element) _ =
920     if n#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
921      let uri =
922       (n#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
923      in 
924       show_in_show_window_uri (UriManager.uri_of_string uri)
925     else
926      ignore (mmlwidget#action_toggle n)
927    in
928     let _ =
929      mmlwidget#connect#click (show_in_show_window_callback mmlwidget)
930     in
931      show_in_show_window_obj, show_in_show_window_uri,
932       show_in_show_window_callback
933 ;;
934
935 exception NoObjectsLocated;;
936
937 let user_uri_choice ~title ~msg uris =
938  let uri =
939   match uris with
940      [] -> raise NoObjectsLocated
941    | [uri] -> uri
942    | uris ->
943       match
944        interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
945       with
946          [uri] -> uri
947        | _ -> assert false
948  in
949   String.sub uri 4 (String.length uri - 4)
950 ;;
951
952 let locate_callback id =
953  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
954  let result = MQueryGenerator.locate id in
955  let uris =
956   List.map
957    (function uri,_ ->
958      MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format' uri)
959    result in
960  let html =
961   (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>")
962  in
963   output_html outputhtml html ;
964   user_uri_choice ~title:"Ambiguous input."
965    ~msg:
966      ("Ambiguous input \"" ^ id ^
967       "\". Please, choose one interpetation:")
968    uris
969 ;;
970
971
972 let input_or_locate_uri ~title =
973  let uri = ref None in
974  let window =
975   GWindow.window
976    ~width:400 ~modal:true ~title ~border_width:2 () in
977  let vbox = GPack.vbox ~packing:window#add () in
978  let hbox1 =
979   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
980  let _ =
981   GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
982  let manual_input =
983   GEdit.entry ~editable:true
984    ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
985  let checkb =
986   GButton.button ~label:"Check"
987    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
988  let _ = checkb#misc#set_sensitive false in
989  let hbox2 =
990   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
991  let _ =
992   GMisc.label ~text:"You can also enter an indentifier to locate:"
993    ~packing:(hbox2#pack ~padding:5) () in
994  let locate_input =
995   GEdit.entry ~editable:true
996    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
997  let locateb =
998   GButton.button ~label:"Locate"
999    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1000  let _ = locateb#misc#set_sensitive false in
1001  let hbox3 =
1002   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1003  let okb =
1004   GButton.button ~label:"Ok"
1005    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
1006  let _ = okb#misc#set_sensitive false in
1007  let cancelb =
1008   GButton.button ~label:"Cancel"
1009    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
1010  in
1011   ignore (window#connect#destroy GMain.Main.quit) ;
1012   ignore
1013    (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
1014   let check_callback () =
1015    let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1016    let uri = "cic:" ^ manual_input#text in
1017     try
1018       ignore (Getter.resolve (UriManager.uri_of_string uri)) ;
1019       output_html outputhtml "<h1 color=\"Green\">OK</h1>" ;
1020       true
1021     with
1022        Getter.Unresolved ->
1023         output_html outputhtml
1024          ("<h1 color=\"Red\">URI " ^ uri ^
1025           " does not correspond to any object.</h1>") ;
1026         false
1027      | UriManager.IllFormedUri _ ->
1028         output_html outputhtml
1029          ("<h1 color=\"Red\">URI " ^ uri ^ " is not well-formed.</h1>") ;
1030         false
1031      | e ->
1032         output_html outputhtml
1033          ("<h1 color=\"Red\">" ^ Printexc.to_string e ^ "</h1>") ;
1034         false
1035   in
1036   ignore
1037    (okb#connect#clicked
1038      (function () ->
1039        if check_callback () then
1040         begin
1041          uri := Some manual_input#text ;
1042          window#destroy ()
1043         end
1044    )) ;
1045   ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1046   ignore
1047    (manual_input#connect#changed
1048      (fun _ ->
1049        if manual_input#text = "" then
1050         begin
1051          checkb#misc#set_sensitive false ;
1052          okb#misc#set_sensitive false
1053         end
1054        else
1055         begin
1056          checkb#misc#set_sensitive true ;
1057          okb#misc#set_sensitive true
1058         end));
1059   ignore
1060    (locate_input#connect#changed
1061      (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1062   ignore
1063    (locateb#connect#clicked
1064      (function () ->
1065        let id = locate_input#text in
1066         manual_input#set_text (locate_callback id) ;
1067         locate_input#delete_text 0 (String.length id)
1068    )) ;
1069   window#show () ;
1070   GtkThread.main ();
1071   match !uri with
1072      None -> raise NoChoice
1073    | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1074 ;;
1075
1076 exception AmbiguousInput;;
1077
1078 (* A WIDGET TO ENTER CIC TERMS *)
1079
1080 module Callbacks =
1081  struct
1082   let output_html msg = output_html (outputhtml ()) msg;;
1083   let interactive_user_uri_choice =
1084    fun ~selection_mode ?ok ?enable_button_for_non_vars ~title ~msg ~id ->
1085     interactive_user_uri_choice ~selection_mode ?ok
1086      ?enable_button_for_non_vars ~title ~msg;;
1087   let interactive_interpretation_choice = interactive_interpretation_choice;;
1088   let input_or_locate_uri = input_or_locate_uri;;
1089  end
1090 ;;
1091
1092 module Disambiguate' = Disambiguate.Make(Callbacks);;
1093
1094 module TermEditor' = TermEditor.Make(Callbacks);;
1095
1096 (* OTHER FUNCTIONS *)
1097
1098 let locate () =
1099  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1100  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1101    try
1102     match
1103      GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1104     with
1105        None -> raise NoChoice
1106      | Some input ->
1107         let uri = locate_callback input in
1108          inputt#set_term uri
1109    with
1110     e ->
1111      output_html outputhtml
1112       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1113 ;;
1114
1115
1116 exception UriAlreadyInUse;;
1117 exception NotAUriToAConstant;;
1118
1119 let new_inductive () =
1120  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1121  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1122  let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1123  let notebook = (rendering_window ())#notebook in
1124
1125  let chosen = ref false in
1126  let inductive = ref true in
1127  let paramsno = ref 0 in
1128  let get_uri = ref (function _ -> assert false) in
1129  let get_base_uri = ref (function _ -> assert false) in
1130  let get_names = ref (function _ -> assert false) in
1131  let get_types_and_cons = ref (function _ -> assert false) in
1132  let get_context_and_subst = ref (function _ -> assert false) in 
1133  let window =
1134   GWindow.window
1135    ~width:600 ~modal:true ~position:`CENTER
1136    ~title:"New Block of Mutual (Co)Inductive Definitions"
1137    ~border_width:2 () in
1138  let vbox = GPack.vbox ~packing:window#add () in
1139  let hbox =
1140   GPack.hbox ~border_width:0
1141    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1142  let _ =
1143   GMisc.label ~text:"Enter the URI for the new block:"
1144    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1145  let uri_entry =
1146   GEdit.entry ~editable:true
1147    ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1148  let hbox0 =
1149   GPack.hbox ~border_width:0
1150    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1151  let _ =
1152   GMisc.label
1153    ~text:
1154      "Enter the number of left parameters in every arity and constructor type:"
1155    ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1156  let paramsno_entry =
1157   GEdit.entry ~editable:true ~text:"0"
1158    ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1159  let hbox1 =
1160   GPack.hbox ~border_width:0
1161    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1162  let _ =
1163   GMisc.label ~text:"Are the definitions inductive or coinductive?"
1164    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1165  let inductiveb =
1166   GButton.radio_button ~label:"Inductive"
1167    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1168  let coinductiveb =
1169   GButton.radio_button ~label:"Coinductive"
1170    ~group:inductiveb#group
1171    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1172  let hbox2 =
1173   GPack.hbox ~border_width:0
1174    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1175  let _ =
1176   GMisc.label ~text:"Enter the list of the names of the types:"
1177    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1178  let names_entry =
1179   GEdit.entry ~editable:true
1180    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1181  let hboxn =
1182   GPack.hbox ~border_width:0
1183    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1184  let okb =
1185   GButton.button ~label:"> Next"
1186    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1187  let _ = okb#misc#set_sensitive true in
1188  let cancelb =
1189   GButton.button ~label:"Abort"
1190    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1191  ignore (window#connect#destroy GMain.Main.quit) ;
1192  ignore (cancelb#connect#clicked window#destroy) ;
1193  (* First phase *)
1194  let rec phase1 () =
1195   ignore
1196    (okb#connect#clicked
1197      (function () ->
1198        try
1199         let uristr = "cic:" ^ uri_entry#text in
1200         let namesstr = names_entry#text in
1201         let paramsno' = int_of_string (paramsno_entry#text) in
1202          match Str.split (Str.regexp " +") namesstr with
1203             [] -> assert false
1204           | (he::tl) as names ->
1205              let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1206               begin
1207                try
1208                 ignore (Getter.resolve uri) ;
1209                 raise UriAlreadyInUse
1210                with
1211                 Getter.Unresolved ->
1212                  get_uri := (function () -> uri) ; 
1213                  get_names := (function () -> names) ;
1214                  inductive := inductiveb#active ;
1215                  paramsno := paramsno' ;
1216                  phase2 ()
1217               end
1218        with
1219         e ->
1220          output_html outputhtml
1221           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1222      ))
1223  (* Second phase *)
1224  and phase2 () =
1225   let type_widgets =
1226    List.map
1227     (function name ->
1228       let frame =
1229        GBin.frame ~label:name
1230         ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1231       let vbox = GPack.vbox ~packing:frame#add () in
1232       let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1233       let _ =
1234        GMisc.label ~text:("Enter its type:")
1235         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1236       let scrolled_window =
1237        GBin.scrolled_window ~border_width:5
1238         ~packing:(vbox#pack ~expand:true ~padding:0) () in
1239       let newinputt =
1240        TermEditor'.term_editor
1241         ~width:400 ~height:20 ~packing:scrolled_window#add 
1242         ~share_id_to_uris_with:inputt ()
1243         ~isnotempty_callback:
1244          (function b ->
1245            (*non_empty_type := b ;*)
1246            okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1247       in
1248       let hbox =
1249        GPack.hbox ~border_width:0
1250         ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1251       let _ =
1252        GMisc.label ~text:("Enter the list of its constructors:")
1253         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1254       let cons_names_entry =
1255        GEdit.entry ~editable:true
1256         ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1257       (newinputt,cons_names_entry)
1258     ) (!get_names ())
1259   in
1260    vbox#remove hboxn#coerce ;
1261    let hboxn =
1262     GPack.hbox ~border_width:0
1263      ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1264    let okb =
1265     GButton.button ~label:"> Next"
1266      ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1267    let cancelb =
1268     GButton.button ~label:"Abort"
1269      ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1270    ignore (cancelb#connect#clicked window#destroy) ;
1271    ignore
1272     (okb#connect#clicked
1273       (function () ->
1274         try
1275          let names = !get_names () in
1276          let types_and_cons =
1277           List.map2
1278            (fun name (newinputt,cons_names_entry) ->
1279              let consnamesstr = cons_names_entry#text in
1280              let cons_names = Str.split (Str.regexp " +") consnamesstr in
1281              let metasenv,expr =
1282               newinputt#get_metasenv_and_term ~context:[] ~metasenv:[]
1283              in
1284               match metasenv with
1285                  [] -> expr,cons_names
1286                | _ -> raise AmbiguousInput
1287            ) names type_widgets
1288          in
1289           let uri = !get_uri () in
1290           let _ =
1291            (* Let's see if so far the definition is well-typed *)
1292            let params = [] in
1293            let paramsno = 0 in
1294            (* To test if the arities of the inductive types are well *)
1295            (* typed, we check the inductive block definition where   *)
1296            (* no constructor is given to each type.                  *)
1297            let tys =
1298             List.map2
1299              (fun name (ty,cons) -> (name, !inductive, ty, []))
1300              names types_and_cons
1301            in
1302             CicTypeChecker.typecheck_mutual_inductive_defs uri
1303              (tys,params,paramsno)
1304           in
1305            get_context_and_subst :=
1306             (function () ->
1307               let i = ref 0 in
1308                List.fold_left2
1309                 (fun (context,subst) name (ty,_) ->
1310                   let res =
1311                    (Some (Cic.Name name, Cic.Decl ty))::context,
1312                     (Cic.MutInd (uri,!i,[]))::subst
1313                   in
1314                    incr i ; res
1315                 ) ([],[]) names types_and_cons) ;
1316            let types_and_cons' =
1317             List.map2
1318              (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1319              names types_and_cons
1320            in
1321             get_types_and_cons := (function () -> types_and_cons') ;
1322             chosen := true ;
1323             window#destroy ()
1324         with
1325          e ->
1326           output_html outputhtml
1327            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1328       ))
1329  (* Third phase *)
1330  and phase3 name cons =
1331   let get_cons_types = ref (function () -> assert false) in
1332   let window2 =
1333    GWindow.window
1334     ~width:600 ~modal:true ~position:`CENTER
1335     ~title:(name ^ " Constructors")
1336     ~border_width:2 () in
1337   let vbox = GPack.vbox ~packing:window2#add () in
1338   let cons_type_widgets =
1339    List.map
1340     (function consname ->
1341       let hbox =
1342        GPack.hbox ~border_width:0
1343         ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1344       let _ =
1345        GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1346         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1347       let scrolled_window =
1348        GBin.scrolled_window ~border_width:5
1349         ~packing:(vbox#pack ~expand:true ~padding:0) () in
1350       let newinputt =
1351        TermEditor'.term_editor
1352         ~width:400 ~height:20 ~packing:scrolled_window#add
1353         ~share_id_to_uris_with:inputt ()
1354         ~isnotempty_callback:
1355          (function b ->
1356            (* (*non_empty_type := b ;*)
1357            okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1358       in
1359        newinputt
1360     ) cons in
1361   let hboxn =
1362    GPack.hbox ~border_width:0
1363     ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1364   let okb =
1365    GButton.button ~label:"> Next"
1366     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1367   let _ = okb#misc#set_sensitive true in
1368   let cancelb =
1369    GButton.button ~label:"Abort"
1370     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1371   ignore (window2#connect#destroy GMain.Main.quit) ;
1372   ignore (cancelb#connect#clicked window2#destroy) ;
1373   ignore
1374    (okb#connect#clicked
1375      (function () ->
1376        try
1377         chosen := true ;
1378         let context,subst= !get_context_and_subst () in
1379         let cons_types =
1380          List.map2
1381           (fun name inputt ->
1382             let metasenv,expr =
1383              inputt#get_metasenv_and_term ~context ~metasenv:[]
1384             in
1385              match metasenv with
1386                 [] ->
1387                  let undebrujined_expr =
1388                   List.fold_left
1389                    (fun expr t -> CicSubstitution.subst t expr) expr subst
1390                  in
1391                   name, undebrujined_expr
1392               | _ -> raise AmbiguousInput
1393           ) cons cons_type_widgets
1394         in
1395          get_cons_types := (function () -> cons_types) ;
1396          window2#destroy ()
1397        with
1398         e ->
1399          output_html outputhtml
1400           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1401      )) ;
1402   window2#show () ;
1403   GtkThread.main ();
1404   let okb_pressed = !chosen in
1405    chosen := false ;
1406    if (not okb_pressed) then
1407     begin
1408      window#destroy () ;
1409      assert false (* The control never reaches this point *)
1410     end
1411    else
1412     (!get_cons_types ())
1413  in
1414   phase1 () ;
1415   (* No more phases left or Abort pressed *) 
1416   window#show () ;
1417   GtkThread.main ();
1418   window#destroy () ;
1419   if !chosen then
1420    try
1421     let uri = !get_uri () in
1422 (*CSC: Da finire *)
1423     let params = [] in
1424     let tys = !get_types_and_cons () in
1425      let obj = Cic.InductiveDefinition tys params !paramsno in
1426       begin
1427        try
1428         prerr_endline (CicPp.ppobj obj) ;
1429         CicTypeChecker.typecheck_mutual_inductive_defs uri
1430          (tys,params,!paramsno) ;
1431         with
1432          e ->
1433           prerr_endline "Offending mutual (co)inductive type declaration:" ;
1434           prerr_endline (CicPp.ppobj obj) ;
1435       end ;
1436       (* We already know that obj is well-typed. We need to add it to the  *)
1437       (* environment in order to compute the inner-types without having to *)
1438       (* debrujin it or having to modify lots of other functions to avoid  *)
1439       (* asking the environment for the MUTINDs we are defining now.       *)
1440       CicEnvironment.put_inductive_definition uri obj ;
1441       save_obj uri obj ;
1442       show_in_show_window_obj uri obj
1443    with
1444     e ->
1445      output_html outputhtml
1446       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1447 ;;
1448
1449 let new_proof () =
1450  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1451  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1452  let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1453  let notebook = (rendering_window ())#notebook in
1454
1455  let chosen = ref false in
1456  let get_metasenv_and_term = ref (function _ -> assert false) in
1457  let get_uri = ref (function _ -> assert false) in
1458  let non_empty_type = ref false in
1459  let window =
1460   GWindow.window
1461    ~width:600 ~modal:true ~title:"New Proof or Definition"
1462    ~border_width:2 () in
1463  let vbox = GPack.vbox ~packing:window#add () in
1464  let hbox =
1465   GPack.hbox ~border_width:0
1466    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1467  let _ =
1468   GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1469    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1470  let uri_entry =
1471   GEdit.entry ~editable:true
1472    ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1473  let hbox1 =
1474   GPack.hbox ~border_width:0
1475    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1476  let _ =
1477   GMisc.label ~text:"Enter the theorem or definition type:"
1478    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1479  let scrolled_window =
1480   GBin.scrolled_window ~border_width:5
1481    ~packing:(vbox#pack ~expand:true ~padding:0) () in
1482  (* the content of the scrolled_window is moved below (see comment) *)
1483  let hbox =
1484   GPack.hbox ~border_width:0
1485    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1486  let okb =
1487   GButton.button ~label:"Ok"
1488    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1489  let _ = okb#misc#set_sensitive false in
1490  let cancelb =
1491   GButton.button ~label:"Cancel"
1492    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1493  (* moved here to have visibility of the ok button *)
1494  let newinputt =
1495   TermEditor'.term_editor ~width:400 ~height:100 ~packing:scrolled_window#add
1496    ~share_id_to_uris_with:inputt ()
1497    ~isnotempty_callback:
1498     (function b ->
1499       non_empty_type := b ;
1500       okb#misc#set_sensitive (b && uri_entry#text <> ""))
1501  in
1502  let _ =
1503   newinputt#set_term inputt#get_as_string ;
1504   inputt#reset in
1505  let _ =
1506   uri_entry#connect#changed
1507    (function () ->
1508      okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1509  in
1510  ignore (window#connect#destroy GMain.Main.quit) ;
1511  ignore (cancelb#connect#clicked window#destroy) ;
1512  ignore
1513   (okb#connect#clicked
1514     (function () ->
1515       chosen := true ;
1516       try
1517        let metasenv,parsed = newinputt#get_metasenv_and_term [] [] in
1518        let uristr = "cic:" ^ uri_entry#text in
1519        let uri = UriManager.uri_of_string uristr in
1520         if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1521          raise NotAUriToAConstant
1522         else
1523          begin
1524           try
1525            ignore (Getter.resolve uri) ;
1526            raise UriAlreadyInUse
1527           with
1528            Getter.Unresolved ->
1529             get_metasenv_and_term := (function () -> metasenv,parsed) ;
1530             get_uri := (function () -> uri) ; 
1531             window#destroy ()
1532          end
1533       with
1534        e ->
1535         output_html outputhtml
1536          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1537   )) ;
1538  window#show () ;
1539  GtkThread.main ();
1540  if !chosen then
1541   try
1542    let metasenv,expr = !get_metasenv_and_term () in
1543     let _  = CicTypeChecker.type_of_aux' metasenv [] expr in
1544      ProofEngine.proof :=
1545       Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
1546      ProofEngine.goal := Some 1 ;
1547      refresh_goals notebook ;
1548      refresh_proof output ;
1549      !save_set_sensitive true ;
1550      inputt#reset ;
1551      ProofEngine.intros ~mk_fresh_name_callback () ;
1552      Hbugs'.notify ();
1553      refresh_goals notebook ;
1554      refresh_proof output
1555   with
1556      InvokeTactics.RefreshSequentException e ->
1557       output_html outputhtml
1558        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1559         "sequent: " ^ Printexc.to_string e ^ "</h1>")
1560    | InvokeTactics.RefreshProofException e ->
1561       output_html outputhtml
1562        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1563         "proof: " ^ Printexc.to_string e ^ "</h1>")
1564    | e ->
1565       output_html outputhtml
1566        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1567 ;;
1568
1569 let check_term_in_scratch scratch_window metasenv context expr = 
1570  try
1571   let ty = CicTypeChecker.type_of_aux' metasenv context expr in
1572   let expr = Cic.Cast (expr,ty) in
1573    scratch_window#show () ;
1574    scratch_window#set_term expr ;
1575    scratch_window#set_context context ;
1576    scratch_window#set_metasenv metasenv ;
1577    scratch_window#sequent_viewer#load_sequent metasenv (111,context,expr)
1578  with
1579   e ->
1580    print_endline ("? " ^ CicPp.ppterm expr) ;
1581    raise e
1582 ;;
1583
1584 let check scratch_window () =
1585  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1586  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1587   let metasenv =
1588    match !ProofEngine.proof with
1589       None -> []
1590     | Some (_,metasenv,_,_) -> metasenv
1591   in
1592   let context =
1593    match !ProofEngine.goal with
1594       None -> []
1595     | Some metano ->
1596        let (_,canonical_context,_) =
1597         List.find (function (m,_,_) -> m=metano) metasenv
1598        in
1599         canonical_context
1600   in
1601    try
1602     let metasenv',expr = inputt#get_metasenv_and_term context metasenv in
1603      check_term_in_scratch scratch_window metasenv' context expr
1604    with
1605     e ->
1606      output_html outputhtml
1607       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1608 ;;
1609
1610 let show () =
1611  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1612   try
1613    show_in_show_window_uri (input_or_locate_uri ~title:"Show")
1614   with
1615    e ->
1616     output_html outputhtml
1617      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1618 ;;
1619
1620 exception NotADefinition;;
1621
1622 let open_ () =
1623  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1624  let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
1625  let notebook = (rendering_window ())#notebook in
1626    try
1627     let uri = input_or_locate_uri ~title:"Open" in
1628      CicTypeChecker.typecheck uri ;
1629      let metasenv,bo,ty =
1630       match CicEnvironment.get_cooked_obj uri with
1631          Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
1632        | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
1633        | Cic.Constant _
1634        | Cic.Variable _
1635        | Cic.InductiveDefinition _ -> raise NotADefinition
1636      in
1637       ProofEngine.proof :=
1638        Some (uri, metasenv, bo, ty) ;
1639       ProofEngine.goal := None ;
1640       refresh_goals notebook ;
1641       refresh_proof output
1642    with
1643       InvokeTactics.RefreshSequentException e ->
1644        output_html outputhtml
1645         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1646          "sequent: " ^ Printexc.to_string e ^ "</h1>")
1647     | InvokeTactics.RefreshProofException e ->
1648        output_html outputhtml
1649         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1650          "proof: " ^ Printexc.to_string e ^ "</h1>")
1651     | e ->
1652        output_html outputhtml
1653         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1654 ;;
1655
1656 let show_query_results results =
1657  let window =
1658   GWindow.window
1659    ~modal:false ~title:"Query results." ~border_width:2 () in
1660  let vbox = GPack.vbox ~packing:window#add () in
1661  let hbox =
1662   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1663  let lMessage =
1664   GMisc.label
1665    ~text:"Click on a URI to show that object"
1666    ~packing:hbox#add () in
1667  let scrolled_window =
1668   GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1669    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1670  let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
1671   ignore
1672    (List.map
1673      (function (uri,_) ->
1674        let n =
1675         clist#append [uri]
1676        in
1677         clist#set_row ~selectable:false n
1678      ) results
1679    ) ;
1680   clist#columns_autosize () ;
1681   ignore
1682    (clist#connect#select_row
1683      (fun ~row ~column ~event ->
1684        let (uristr,_) = List.nth results row in
1685         match
1686          MQueryMisc.cic_textual_parser_uri_of_string
1687           (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
1688             uristr)
1689         with
1690            CicTextualParser0.ConUri uri
1691          | CicTextualParser0.VarUri uri
1692          | CicTextualParser0.IndTyUri (uri,_)
1693          | CicTextualParser0.IndConUri (uri,_,_) ->
1694             show_in_show_window_uri uri
1695      )
1696    ) ;
1697   window#show ()
1698 ;;
1699
1700 let refine_constraints (must_obj,must_rel,must_sort) =
1701  let chosen = ref false in
1702  let use_only = ref false in
1703  let window =
1704   GWindow.window
1705    ~modal:true ~title:"Constraints refinement."
1706    ~width:800 ~border_width:2 () in
1707  let vbox = GPack.vbox ~packing:window#add () in
1708  let hbox =
1709   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1710  let lMessage =
1711   GMisc.label
1712    ~text: "\"Only\" constraints can be enforced or not."
1713    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1714  let onlyb =
1715   GButton.toggle_button ~label:"Enforce \"only\" constraints"
1716    ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1717  in
1718   ignore
1719    (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
1720  (* Notebook for the constraints choice *)
1721  let notebook =
1722   GPack.notebook ~scrollable:true
1723    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1724  (* Rel constraints *)
1725  let label =
1726   GMisc.label
1727    ~text: "Constraints on Rels" () in
1728  let vbox' =
1729   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1730    () in
1731  let hbox =
1732   GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1733  let lMessage =
1734   GMisc.label
1735    ~text: "You can now specify the constraints on Rels."
1736    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1737  let expected_height = 25 * (List.length must_rel + 2) in
1738  let height = if expected_height > 400 then 400 else expected_height in
1739  let scrolled_window =
1740   GBin.scrolled_window ~border_width:10 ~height ~width:600
1741    ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1742  let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1743  let rel_constraints =
1744   List.map
1745    (function (position,depth) ->
1746      let hbox =
1747       GPack.hbox
1748        ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1749      let lMessage =
1750       GMisc.label
1751        ~text:position
1752        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1753      match depth with
1754         None -> position, ref None
1755       | Some depth' ->
1756          let mutable_ref = ref (Some depth') in
1757          let depthb =
1758           GButton.toggle_button
1759            ~label:("depth = " ^ string_of_int depth') ~active:true
1760            ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1761          in
1762           ignore
1763            (depthb#connect#toggled
1764              (function () ->
1765                let sel_depth = if depthb#active then Some depth' else None in
1766                 mutable_ref := sel_depth
1767             )) ;
1768           position, mutable_ref
1769    ) must_rel in
1770  (* Sort constraints *)
1771  let label =
1772   GMisc.label
1773    ~text: "Constraints on Sorts" () in
1774  let vbox' =
1775   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1776    () in
1777  let hbox =
1778   GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1779  let lMessage =
1780   GMisc.label
1781    ~text: "You can now specify the constraints on Sorts."
1782    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1783  let expected_height = 25 * (List.length must_sort + 2) in
1784  let height = if expected_height > 400 then 400 else expected_height in
1785  let scrolled_window =
1786   GBin.scrolled_window ~border_width:10 ~height ~width:600
1787    ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1788  let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1789  let sort_constraints =
1790   List.map
1791    (function (position,depth,sort) ->
1792      let hbox =
1793       GPack.hbox
1794        ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1795      let lMessage =
1796       GMisc.label
1797        ~text:(sort ^ " " ^ position)
1798        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1799      match depth with
1800         None -> position, ref None, sort
1801       | Some depth' ->
1802          let mutable_ref = ref (Some depth') in
1803          let depthb =
1804           GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
1805            ~active:true
1806            ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1807          in
1808           ignore
1809            (depthb#connect#toggled
1810              (function () ->
1811                let sel_depth = if depthb#active then Some depth' else None in
1812                 mutable_ref := sel_depth
1813             )) ;
1814           position, mutable_ref, sort
1815    ) must_sort in
1816  (* Obj constraints *)
1817  let label =
1818   GMisc.label
1819    ~text: "Constraints on constants" () in
1820  let vbox' =
1821   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
1822    () in
1823  let hbox =
1824   GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
1825  let lMessage =
1826   GMisc.label
1827    ~text: "You can now specify the constraints on constants."
1828    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1829  let expected_height = 25 * (List.length must_obj + 2) in
1830  let height = if expected_height > 400 then 400 else expected_height in
1831  let scrolled_window =
1832   GBin.scrolled_window ~border_width:10 ~height ~width:600
1833    ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
1834  let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
1835  let obj_constraints =
1836   List.map
1837    (function (uri,position,depth) ->
1838      let hbox =
1839       GPack.hbox
1840        ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
1841      let lMessage =
1842       GMisc.label
1843        ~text:(uri ^ " " ^ position)
1844        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1845      match depth with
1846         None -> uri, position, ref None
1847       | Some depth' ->
1848          let mutable_ref = ref (Some depth') in
1849          let depthb =
1850           GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
1851            ~active:true
1852            ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1853          in
1854           ignore
1855            (depthb#connect#toggled
1856              (function () ->
1857                let sel_depth = if depthb#active then Some depth' else None in
1858                 mutable_ref := sel_depth
1859             )) ;
1860           uri, position, mutable_ref
1861    ) must_obj in
1862  (* Confirm/abort buttons *)
1863  let hbox =
1864   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1865  let okb =
1866   GButton.button ~label:"Ok"
1867    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1868  let cancelb =
1869   GButton.button ~label:"Abort"
1870    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
1871  in
1872   ignore (window#connect#destroy GMain.Main.quit) ;
1873   ignore (cancelb#connect#clicked window#destroy) ;
1874   ignore
1875    (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
1876   window#set_position `CENTER ;
1877   window#show () ;
1878   GtkThread.main ();
1879   if !chosen then
1880    let chosen_must_rel =
1881     List.map
1882      (function (position,ref_depth) -> position,!ref_depth) rel_constraints in
1883    let chosen_must_sort =
1884     List.map
1885      (function (position,ref_depth,sort) -> position,!ref_depth,sort)
1886      sort_constraints
1887    in
1888    let chosen_must_obj =
1889     List.map
1890      (function (uri,position,ref_depth) -> uri,position,!ref_depth)
1891      obj_constraints
1892    in
1893     (chosen_must_obj,chosen_must_rel,chosen_must_sort),
1894      (if !use_only then
1895 (*CSC: ???????????????????????? I assume that must and only are the same... *)
1896        Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
1897       else
1898        None,None,None
1899      )
1900   else
1901    raise NoChoice
1902 ;;
1903
1904 let completeSearchPattern () =
1905  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
1906  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1907   try
1908    let metasenv,expr = inputt#get_metasenv_and_term ~context:[] ~metasenv:[] in
1909    let must = MQueryLevels2.get_constraints expr in
1910    let must',only = refine_constraints must in
1911    let results = MQueryGenerator.searchPattern must' only in 
1912     show_query_results results
1913   with
1914    e ->
1915     output_html outputhtml
1916      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1917 ;;
1918
1919 let insertQuery () =
1920  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1921   try
1922    let chosen = ref None in
1923    let window =
1924     GWindow.window
1925      ~modal:true ~title:"Insert Query (Experts Only)" ~border_width:2 () in
1926    let vbox = GPack.vbox ~packing:window#add () in
1927    let label =
1928     GMisc.label ~text:"Insert Query. For Experts Only."
1929      ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1930    let scrolled_window =
1931     GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
1932      ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1933    let input = GEdit.text ~editable:true
1934     ~packing:scrolled_window#add () in
1935    let hbox =
1936     GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1937    let okb =
1938     GButton.button ~label:"Ok"
1939      ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1940    let loadb =
1941     GButton.button ~label:"Load from file..."
1942      ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1943    let cancelb =
1944     GButton.button ~label:"Abort"
1945      ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1946    ignore (window#connect#destroy GMain.Main.quit) ;
1947    ignore (cancelb#connect#clicked window#destroy) ;
1948    ignore
1949     (okb#connect#clicked
1950       (function () ->
1951         chosen := Some (input#get_chars 0 input#length) ; window#destroy ())) ;
1952    ignore
1953     (loadb#connect#clicked
1954       (function () ->
1955         match
1956          GToolbox.select_file ~title:"Select Query File" ()
1957         with
1958            None -> ()
1959          | Some filename ->
1960             let inch = open_in filename in
1961              let rec read_file () =
1962               try
1963                let line = input_line inch in
1964                 line ^ "\n" ^ read_file ()
1965               with
1966                End_of_file -> ""
1967              in
1968               let text = read_file () in
1969                input#delete_text 0 input#length ;
1970                ignore (input#insert_text text ~pos:0))) ;
1971    window#set_position `CENTER ;
1972    window#show () ;
1973    GtkThread.main ();
1974    match !chosen with
1975       None -> ()
1976     | Some q ->
1977        let results =
1978         Mqint.execute (MQueryUtil.query_of_text (Lexing.from_string q))
1979        in
1980         show_query_results results
1981   with
1982    e ->
1983     output_html outputhtml
1984      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1985 ;;
1986
1987 let choose_must list_of_must only =
1988  let chosen = ref None in
1989  let user_constraints = ref [] in
1990  let window =
1991   GWindow.window
1992    ~modal:true ~title:"Query refinement." ~border_width:2 () in
1993  let vbox = GPack.vbox ~packing:window#add () in
1994  let hbox =
1995   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1996  let lMessage =
1997   GMisc.label
1998    ~text:
1999     ("You can now specify the genericity of the query. " ^
2000      "The more generic the slower.")
2001    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2002  let hbox =
2003   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2004  let lMessage =
2005   GMisc.label
2006    ~text:
2007     "Suggestion: start with faster queries before moving to more generic ones."
2008    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2009  let notebook =
2010   GPack.notebook ~scrollable:true
2011    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2012  let _ =
2013   let page = ref 0 in
2014   let last = List.length list_of_must in
2015   List.map
2016    (function must ->
2017      incr page ;
2018      let label =
2019       GMisc.label ~text:
2020        (if !page = 1 then "More generic" else
2021          if !page = last then "More precise" else "          ") () in
2022      let expected_height = 25 * (List.length must + 2) in
2023      let height = if expected_height > 400 then 400 else expected_height in
2024      let scrolled_window =
2025       GBin.scrolled_window ~border_width:10 ~height ~width:600
2026        ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2027      let clist =
2028         GList.clist ~columns:2 ~packing:scrolled_window#add
2029          ~titles:["URI" ; "Position"] ()
2030      in
2031       ignore
2032        (List.map
2033          (function (uri,position) ->
2034            let n =
2035             clist#append 
2036              [uri; if position then "MainConclusion" else "Conclusion"]
2037            in
2038             clist#set_row ~selectable:false n
2039          ) must
2040        ) ;
2041       clist#columns_autosize ()
2042    ) list_of_must in
2043  let _ =
2044   let label = GMisc.label ~text:"User provided" () in
2045   let vbox =
2046    GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2047   let hbox =
2048    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2049   let lMessage =
2050    GMisc.label
2051    ~text:"Select the constraints that must be satisfied and press OK."
2052    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2053   let expected_height = 25 * (List.length only + 2) in
2054   let height = if expected_height > 400 then 400 else expected_height in
2055   let scrolled_window =
2056    GBin.scrolled_window ~border_width:10 ~height ~width:600
2057     ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2058   let clist =
2059    GList.clist ~columns:2 ~packing:scrolled_window#add
2060     ~selection_mode:`EXTENDED
2061     ~titles:["URI" ; "Position"] ()
2062   in
2063    ignore
2064     (List.map
2065       (function (uri,position) ->
2066         let n =
2067          clist#append 
2068           [uri; if position then "MainConclusion" else "Conclusion"]
2069         in
2070          clist#set_row ~selectable:true n
2071       ) only
2072     ) ;
2073    clist#columns_autosize () ;
2074    ignore
2075     (clist#connect#select_row
2076       (fun ~row ~column ~event ->
2077         user_constraints := (List.nth only row)::!user_constraints)) ;
2078    ignore
2079     (clist#connect#unselect_row
2080       (fun ~row ~column ~event ->
2081         user_constraints :=
2082          List.filter
2083           (function uri -> uri != (List.nth only row)) !user_constraints)) ;
2084  in
2085  let hbox =
2086   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2087  let okb =
2088   GButton.button ~label:"Ok"
2089    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2090  let cancelb =
2091   GButton.button ~label:"Abort"
2092    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2093  (* actions *)
2094  ignore (window#connect#destroy GMain.Main.quit) ;
2095  ignore (cancelb#connect#clicked window#destroy) ;
2096  ignore
2097   (okb#connect#clicked
2098     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2099  window#set_position `CENTER ;
2100  window#show () ;
2101  GtkThread.main ();
2102  match !chosen with
2103     None -> raise NoChoice
2104   | Some n ->
2105      if n = List.length list_of_must then
2106       (* user provided constraints *)
2107       !user_constraints
2108      else
2109       List.nth list_of_must n
2110 ;;
2111
2112 let searchPattern () =
2113  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
2114  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2115   try
2116     let proof =
2117      match !ProofEngine.proof with
2118         None -> assert false
2119       | Some proof -> proof
2120     in
2121      match !ProofEngine.goal with
2122       | None -> ()
2123       | Some metano ->
2124          let uris' =
2125            TacticChaser.searchPattern
2126             ~output_html:(output_html outputhtml) ~choose_must ()
2127             ~status:(proof, metano)
2128          in
2129          let uri' =
2130           user_uri_choice ~title:"Ambiguous input."
2131           ~msg: "Many lemmas can be successfully applied. Please, choose one:"
2132            uris'
2133          in
2134           inputt#set_term uri' ;
2135           InvokeTactics'.apply ()
2136   with
2137    e -> 
2138     output_html outputhtml 
2139      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2140 ;;
2141       
2142 let choose_selection mmlwidget (element : Gdome.element option) =
2143  let module G = Gdome in
2144   let rec aux element =
2145    if element#hasAttributeNS
2146        ~namespaceURI:Misc.helmns
2147        ~localName:(G.domString "xref")
2148    then
2149      mmlwidget#set_selection (Some element)
2150    else
2151     try
2152       match element#get_parentNode with
2153          None -> assert false
2154        (*CSC: OCAML DIVERGES!
2155        | Some p -> aux (new G.element_of_node p)
2156        *)
2157        | Some p -> aux (new Gdome.element_of_node p)
2158     with
2159        GdomeInit.DOMCastException _ ->
2160         prerr_endline
2161          "******* trying to select above the document root ********"
2162   in
2163    match element with
2164      Some x -> aux x
2165    | None   -> mmlwidget#set_selection None
2166 ;;
2167
2168 (* STUFF TO BUILD THE GTK INTERFACE *)
2169
2170 (* Stuff for the widget settings *)
2171
2172 let export_to_postscript output =
2173  let lastdir = ref (Unix.getcwd ()) in
2174   function () ->
2175    match
2176     GToolbox.select_file ~title:"Export to PostScript"
2177      ~dir:lastdir ~filename:"screenshot.ps" ()
2178    with
2179       None -> ()
2180     | Some filename ->
2181        (output :> GMathView.math_view)#export_to_postscript
2182          ~filename:filename ();
2183 ;;
2184
2185 let activate_t1 output button_set_anti_aliasing
2186  button_set_transparency export_to_postscript_menu_item
2187  button_t1 ()
2188 =
2189  let is_set = button_t1#active in
2190   output#set_font_manager_type
2191    ~fm_type:(if is_set then `font_manager_t1 else `font_manager_gtk) ;
2192   if is_set then
2193    begin
2194     button_set_anti_aliasing#misc#set_sensitive true ;
2195     button_set_transparency#misc#set_sensitive true ;
2196     export_to_postscript_menu_item#misc#set_sensitive true ;
2197    end
2198   else
2199    begin
2200     button_set_anti_aliasing#misc#set_sensitive false ;
2201     button_set_transparency#misc#set_sensitive false ;
2202     export_to_postscript_menu_item#misc#set_sensitive false ;
2203    end
2204 ;;
2205
2206 let set_anti_aliasing output button_set_anti_aliasing () =
2207  output#set_anti_aliasing button_set_anti_aliasing#active
2208 ;;
2209
2210 let set_transparency output button_set_transparency () =
2211  output#set_transparency button_set_transparency#active
2212 ;;
2213
2214 let changefont output font_size_spinb () =
2215  output#set_font_size font_size_spinb#value_as_int
2216 ;;
2217
2218 let set_log_verbosity output log_verbosity_spinb () =
2219  output#set_log_verbosity log_verbosity_spinb#value_as_int
2220 ;;
2221
2222 class settings_window output sw
2223  export_to_postscript_menu_item selection_changed_callback
2224 =
2225  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2226  let vbox =
2227   GPack.vbox ~packing:settings_window#add () in
2228  let table =
2229   GPack.table
2230    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2231    ~border_width:5 ~packing:vbox#add () in
2232  let button_t1 =
2233   GButton.toggle_button ~label:"activate t1 fonts"
2234    ~packing:(table#attach ~left:0 ~top:0) () in
2235  let button_set_anti_aliasing =
2236   GButton.toggle_button ~label:"set_anti_aliasing"
2237    ~packing:(table#attach ~left:0 ~top:1) () in
2238  let button_set_transparency =
2239   GButton.toggle_button ~label:"set_transparency"
2240    ~packing:(table#attach ~left:2 ~top:1) () in
2241  let table =
2242   GPack.table
2243    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2244    ~border_width:5 ~packing:vbox#add () in
2245  let font_size_label =
2246   GMisc.label ~text:"font size:"
2247    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2248  let font_size_spinb =
2249   let sadj =
2250    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2251   in
2252    GEdit.spin_button 
2253     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2254  let log_verbosity_label =
2255   GMisc.label ~text:"log verbosity:"
2256    ~packing:(table#attach ~left:0 ~top:1) () in
2257  let log_verbosity_spinb =
2258   let sadj =
2259    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2260   in
2261    GEdit.spin_button 
2262     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2263  let hbox =
2264   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2265  let closeb =
2266   GButton.button ~label:"Close"
2267    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2268 object(self)
2269  method show = settings_window#show
2270  initializer
2271   button_set_anti_aliasing#misc#set_sensitive false ;
2272   button_set_transparency#misc#set_sensitive false ;
2273   (* Signals connection *)
2274   ignore(button_t1#connect#clicked
2275    (activate_t1 output button_set_anti_aliasing
2276     button_set_transparency export_to_postscript_menu_item button_t1)) ;
2277   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2278   ignore(button_set_anti_aliasing#connect#toggled
2279    (set_anti_aliasing output button_set_anti_aliasing));
2280   ignore(button_set_transparency#connect#toggled
2281    (set_transparency output button_set_transparency)) ;
2282   ignore(log_verbosity_spinb#connect#changed
2283    (set_log_verbosity output log_verbosity_spinb)) ;
2284   ignore(closeb#connect#clicked settings_window#misc#hide)
2285 end;;
2286
2287 (* Scratch window *)
2288
2289 class scratch_window =
2290  let window =
2291   GWindow.window
2292     ~title:"MathML viewer"
2293     ~border_width:2 () in
2294  let vbox =
2295   GPack.vbox ~packing:window#add () in
2296  let hbox =
2297   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2298  let whdb =
2299   GButton.button ~label:"Whd"
2300    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2301  let reduceb =
2302   GButton.button ~label:"Reduce"
2303    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2304  let simplb =
2305   GButton.button ~label:"Simpl"
2306    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2307  let scrolled_window =
2308   GBin.scrolled_window ~border_width:10
2309    ~packing:(vbox#pack ~expand:true ~padding:5) () in
2310  let sequent_viewer =
2311   TermViewer.sequent_viewer
2312    ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
2313 object(self)
2314  val mutable term = Cic.Rel 1                 (* dummy value *)
2315  val mutable context = ([] : Cic.context)     (* dummy value *)
2316  val mutable metasenv = ([] : Cic.metasenv)   (* dummy value *)
2317  method sequent_viewer = sequent_viewer
2318  method show () = window#misc#hide () ; window#show ()
2319  method term = term
2320  method set_term t = term <- t
2321  method context = context
2322  method set_context t = context <- t
2323  method metasenv = metasenv
2324  method set_metasenv t = metasenv <- t
2325  initializer
2326   ignore
2327    (sequent_viewer#connect#selection_changed (choose_selection sequent_viewer));
2328   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
2329   ignore(whdb#connect#clicked InvokeTactics'.whd_in_scratch) ;
2330   ignore(reduceb#connect#clicked InvokeTactics'.reduce_in_scratch) ;
2331   ignore(simplb#connect#clicked InvokeTactics'.simpl_in_scratch)
2332 end;;
2333
2334 let open_contextual_menu_for_selected_terms mmlwidget infos =
2335  let button = GdkEvent.Button.button infos in 
2336  let terms_selected = List.length mmlwidget#get_selections > 0 in
2337   if button = 3 then
2338    begin
2339     let time = GdkEvent.Button.time infos in
2340     let menu = GMenu.menu () in
2341     let f = new GMenu.factory menu in
2342     let whd_menu_item =
2343      f#add_item "Whd" ~key:GdkKeysyms._W ~callback:InvokeTactics'.whd in
2344     let reduce_menu_item =
2345      f#add_item "Reduce" ~key:GdkKeysyms._R ~callback:InvokeTactics'.reduce in
2346     let simpl_menu_item =
2347      f#add_item "Simpl" ~key:GdkKeysyms._S ~callback:InvokeTactics'.simpl in
2348     let _ = f#add_separator () in
2349     let generalize_menu_item =
2350      f#add_item "Generalize"
2351       ~key:GdkKeysyms._G ~callback:InvokeTactics'.generalize in
2352     let _ = f#add_separator () in
2353     let clear_menu_item =
2354      f#add_item "Clear" ~key:GdkKeysyms._C ~callback:InvokeTactics'.clear in
2355     let clearbody_menu_item =
2356      f#add_item "ClearBody"
2357       ~key:GdkKeysyms._B ~callback:InvokeTactics'.clearbody
2358     in
2359      whd_menu_item#misc#set_sensitive terms_selected ; 
2360      reduce_menu_item#misc#set_sensitive terms_selected ; 
2361      simpl_menu_item#misc#set_sensitive terms_selected ;
2362      generalize_menu_item#misc#set_sensitive terms_selected ;
2363      clear_menu_item#misc#set_sensitive terms_selected ;
2364      clearbody_menu_item#misc#set_sensitive terms_selected ;
2365      menu#popup ~button ~time
2366    end ;
2367   true
2368 ;;
2369
2370 class page () =
2371  let vbox1 = GPack.vbox () in
2372 object(self)
2373  val mutable proofw_ref = None
2374  val mutable compute_ref = None
2375  method proofw =
2376   Lazy.force self#compute ;
2377   match proofw_ref with
2378      None -> assert false
2379    | Some proofw -> proofw
2380  method content = vbox1
2381  method compute =
2382   match compute_ref with
2383      None -> assert false
2384    | Some compute -> compute
2385  initializer
2386   compute_ref <-
2387    Some (lazy (
2388    let scrolled_window1 =
2389     GBin.scrolled_window ~border_width:10
2390      ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2391    let proofw =
2392     TermViewer.sequent_viewer ~width:400 ~height:275
2393      ~packing:(scrolled_window1#add) () in
2394    let _ = proofw_ref <- Some proofw in
2395    let hbox3 =
2396     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2397    let ringb =
2398     GButton.button ~label:"Ring"
2399      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2400    let fourierb =
2401     GButton.button ~label:"Fourier"
2402      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2403    let reflexivityb =
2404     GButton.button ~label:"Reflexivity"
2405      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2406    let symmetryb =
2407     GButton.button ~label:"Symmetry"
2408      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2409    let assumptionb =
2410     GButton.button ~label:"Assumption"
2411      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2412    let contradictionb =
2413     GButton.button ~label:"Contradiction"
2414      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2415    let hbox4 =
2416     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2417    let existsb =
2418     GButton.button ~label:"Exists"
2419      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2420    let splitb =
2421     GButton.button ~label:"Split"
2422      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2423    let leftb =
2424     GButton.button ~label:"Left"
2425      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2426    let rightb =
2427     GButton.button ~label:"Right"
2428      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2429    let searchpatternb =
2430     GButton.button ~label:"SearchPattern_Apply"
2431      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
2432    let hbox5 =
2433     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2434    let exactb =
2435     GButton.button ~label:"Exact"
2436      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2437    let introsb =
2438     GButton.button ~label:"Intros"
2439      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2440    let applyb =
2441     GButton.button ~label:"Apply"
2442      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2443    let elimintrossimplb =
2444     GButton.button ~label:"ElimIntrosSimpl"
2445      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2446    let elimtypeb =
2447     GButton.button ~label:"ElimType"
2448      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2449    let foldwhdb =
2450     GButton.button ~label:"Fold_whd"
2451      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2452    let foldreduceb =
2453     GButton.button ~label:"Fold_reduce"
2454      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2455    let hbox6 =
2456     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2457    let foldsimplb =
2458     GButton.button ~label:"Fold_simpl"
2459      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2460    let cutb =
2461     GButton.button ~label:"Cut"
2462      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2463    let changeb =
2464     GButton.button ~label:"Change"
2465      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2466    let letinb =
2467     GButton.button ~label:"Let ... In"
2468      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2469    let rewritesimplb =
2470     GButton.button ~label:"RewriteSimpl ->"
2471      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2472    let rewritebacksimplb =
2473     GButton.button ~label:"RewriteSimpl <-"
2474      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
2475    let hbox7 =
2476     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
2477    let absurdb =
2478     GButton.button ~label:"Absurd"
2479      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2480    let decomposeb =
2481     GButton.button ~label:"Decompose"
2482      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2483    let transitivityb =
2484     GButton.button ~label:"Transitivity"
2485      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2486    let replaceb =
2487     GButton.button ~label:"Replace"
2488      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2489    let injectionb =
2490     GButton.button ~label:"Injection"
2491      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2492    let discriminateb =
2493     GButton.button ~label:"Discriminate"
2494      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2495 (* Zack: spostare in una toolbar
2496    let generalizeb =
2497     GButton.button ~label:"Generalize"
2498      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
2499    let clearbodyb =
2500     GButton.button ~label:"ClearBody"
2501      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2502    let clearb =
2503     GButton.button ~label:"Clear"
2504      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
2505    let whdb =
2506     GButton.button ~label:"Whd"
2507      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2508    let reduceb =
2509     GButton.button ~label:"Reduce"
2510      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2511    let simplb =
2512     GButton.button ~label:"Simpl"
2513      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
2514 *)
2515
2516    ignore(exactb#connect#clicked InvokeTactics'.exact) ;
2517    ignore(applyb#connect#clicked InvokeTactics'.apply) ;
2518    ignore(elimintrossimplb#connect#clicked InvokeTactics'.elimintrossimpl) ;
2519    ignore(elimtypeb#connect#clicked InvokeTactics'.elimtype) ;
2520    ignore(foldwhdb#connect#clicked InvokeTactics'.fold_whd) ;
2521    ignore(foldreduceb#connect#clicked InvokeTactics'.fold_reduce) ;
2522    ignore(foldsimplb#connect#clicked InvokeTactics'.fold_simpl) ;
2523    ignore(cutb#connect#clicked InvokeTactics'.cut) ;
2524    ignore(changeb#connect#clicked InvokeTactics'.change) ;
2525    ignore(letinb#connect#clicked InvokeTactics'.letin) ;
2526    ignore(ringb#connect#clicked InvokeTactics'.ring) ;
2527    ignore(fourierb#connect#clicked InvokeTactics'.fourier) ;
2528    ignore(rewritesimplb#connect#clicked InvokeTactics'.rewritesimpl) ;
2529    ignore(rewritebacksimplb#connect#clicked InvokeTactics'.rewritebacksimpl) ;
2530    ignore(replaceb#connect#clicked InvokeTactics'.replace) ;
2531    ignore(reflexivityb#connect#clicked InvokeTactics'.reflexivity) ;
2532    ignore(symmetryb#connect#clicked InvokeTactics'.symmetry) ;
2533    ignore(transitivityb#connect#clicked InvokeTactics'.transitivity) ;
2534    ignore(existsb#connect#clicked InvokeTactics'.exists) ;
2535    ignore(splitb#connect#clicked InvokeTactics'.split) ;
2536    ignore(leftb#connect#clicked InvokeTactics'.left) ;
2537    ignore(rightb#connect#clicked InvokeTactics'.right) ;
2538    ignore(assumptionb#connect#clicked InvokeTactics'.assumption) ;
2539    ignore(absurdb#connect#clicked InvokeTactics'.absurd) ;
2540    ignore(contradictionb#connect#clicked InvokeTactics'.contradiction) ;
2541    ignore(introsb#connect#clicked InvokeTactics'.intros) ;
2542    ignore(decomposeb#connect#clicked InvokeTactics'.decompose) ;
2543    ignore(searchpatternb#connect#clicked searchPattern) ;
2544    ignore(injectionb#connect#clicked InvokeTactics'.injection) ;
2545    ignore(discriminateb#connect#clicked InvokeTactics'.discriminate) ;
2546 (* Zack: spostare in una toolbar
2547    ignore(whdb#connect#clicked whd) ;
2548    ignore(reduceb#connect#clicked reduce) ;
2549    ignore(simplb#connect#clicked simpl) ;
2550    ignore(clearbodyb#connect#clicked clearbody) ;
2551    ignore(clearb#connect#clicked clear) ;
2552    ignore(generalizeb#connect#clicked generalize) ;
2553 *)
2554    ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
2555    ignore
2556      ((new GObj.event_ops proofw#as_widget)#connect#button_press
2557         (open_contextual_menu_for_selected_terms proofw)) ;
2558   ))
2559 end
2560 ;;
2561
2562 class empty_page =
2563  let vbox1 = GPack.vbox () in
2564  let scrolled_window1 =
2565   GBin.scrolled_window ~border_width:10
2566    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
2567  let proofw =
2568   TermViewer.sequent_viewer ~width:400 ~height:275
2569    ~packing:(scrolled_window1#add) () in
2570 object(self)
2571  method proofw = (assert false : TermViewer.sequent_viewer)
2572  method content = vbox1
2573  method compute = (assert false : unit)
2574 end
2575 ;;
2576
2577 let empty_page = new empty_page;;
2578
2579 class notebook =
2580 object(self)
2581  val notebook = GPack.notebook ()
2582  val pages = ref []
2583  val mutable skip_switch_page_event = false 
2584  val mutable empty = true
2585  method notebook = notebook
2586  method add_page n =
2587   let new_page = new page () in
2588    empty <- false ;
2589    pages := !pages @ [n,lazy (setgoal n),new_page] ;
2590    notebook#append_page
2591     ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
2592     new_page#content#coerce
2593  method remove_all_pages ~skip_switch_page_event:skip =
2594   if empty then
2595    notebook#remove_page 0 (* let's remove the empty page *)
2596   else
2597    List.iter (function _ -> notebook#remove_page 0) !pages ;
2598   pages := [] ;
2599   skip_switch_page_event <- skip
2600  method set_current_page ~may_skip_switch_page_event n =
2601   let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
2602    let new_page = notebook#page_num page#content#coerce in
2603     if may_skip_switch_page_event && new_page <> notebook#current_page then
2604      skip_switch_page_event <- true ;
2605     notebook#goto_page new_page
2606  method set_empty_page =
2607   empty <- true ;
2608   pages := [] ;
2609   notebook#append_page
2610    ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
2611    empty_page#content#coerce
2612  method proofw =
2613   let (_,_,page) = List.nth !pages notebook#current_page in
2614    page#proofw
2615  initializer
2616   ignore
2617    (notebook#connect#switch_page
2618     (function i ->
2619       let skip = skip_switch_page_event in
2620        skip_switch_page_event <- false ;
2621        if not skip then
2622         try
2623          let (metano,setgoal,page) = List.nth !pages i in
2624           ProofEngine.goal := Some metano ;
2625           Lazy.force (page#compute) ;
2626           Lazy.force setgoal
2627         with _ -> ()
2628     ))
2629 end
2630 ;;
2631
2632 (* Main window *)
2633
2634 class rendering_window output (notebook : notebook) =
2635  let scratch_window = new scratch_window in
2636  let window =
2637   GWindow.window
2638    ~title:"gTopLevel - Helm's Proof Assistant"
2639    ~border_width:0 ~allow_shrink:false () in
2640  let vbox_for_menu = GPack.vbox ~packing:window#add () in
2641  (* menus *)
2642  let handle_box = GBin.handle_box ~border_width:2
2643   ~packing:(vbox_for_menu#pack ~padding:0) () in
2644  let menubar = GMenu.menu_bar ~packing:handle_box#add () in
2645  let factory0 = new GMenu.factory menubar in
2646  let accel_group = factory0#accel_group in
2647  (* file menu *)
2648  let file_menu = factory0#add_submenu "File" in
2649  let factory1 = new GMenu.factory file_menu ~accel_group in
2650  let export_to_postscript_menu_item =
2651   begin
2652    let _ =
2653     factory1#add_item "New Block of (Co)Inductive Definitions..."
2654      ~key:GdkKeysyms._B ~callback:new_inductive
2655    in
2656    let _ =
2657     factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
2658      ~callback:new_proof
2659    in
2660    let reopen_menu_item =
2661     factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
2662      ~callback:open_
2663    in
2664    let qed_menu_item =
2665     factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
2666    ignore (factory1#add_separator ()) ;
2667    ignore
2668     (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
2669       ~callback:load_unfinished_proof) ;
2670    let save_menu_item =
2671     factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S
2672       ~callback:save_unfinished_proof
2673    in
2674    ignore
2675     (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
2676    ignore (!save_set_sensitive false);
2677    ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
2678    ignore (!qed_set_sensitive false);
2679    ignore (factory1#add_separator ()) ;
2680    let export_to_postscript_menu_item =
2681     factory1#add_item "Export to PostScript..."
2682      ~callback:(export_to_postscript output) in
2683    ignore (factory1#add_separator ()) ;
2684    ignore
2685     (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) ;
2686    export_to_postscript_menu_item
2687   end in
2688  (* edit menu *)
2689  let edit_menu = factory0#add_submenu "Edit Current Proof" in
2690  let factory2 = new GMenu.factory edit_menu ~accel_group in
2691  let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
2692  let proveit_menu_item =
2693   factory2#add_item "Prove It" ~key:GdkKeysyms._I
2694    ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
2695  in
2696  let focus_menu_item =
2697   factory2#add_item "Focus" ~key:GdkKeysyms._F
2698    ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
2699  in
2700  let _ =
2701   focus_and_proveit_set_sensitive :=
2702    function b ->
2703     proveit_menu_item#misc#set_sensitive b ;
2704     focus_menu_item#misc#set_sensitive b
2705  in
2706  let _ = !focus_and_proveit_set_sensitive false in
2707  (* edit term menu *)
2708  let edit_term_menu = factory0#add_submenu "Edit Term" in
2709  let factory5 = new GMenu.factory edit_term_menu ~accel_group in
2710  let check_menu_item =
2711   factory5#add_item "Check Term" ~key:GdkKeysyms._C
2712    ~callback:(check scratch_window) in
2713  let _ = check_menu_item#misc#set_sensitive false in
2714  (* search menu *)
2715  let search_menu = factory0#add_submenu "Search" in
2716  let factory4 = new GMenu.factory search_menu ~accel_group in
2717  let _ =
2718   factory4#add_item "Locate..." ~key:GdkKeysyms._T
2719    ~callback:locate in
2720  let searchPattern_menu_item =
2721   factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
2722    ~callback:completeSearchPattern in
2723  let _ = searchPattern_menu_item#misc#set_sensitive false in
2724  let show_menu_item =
2725   factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
2726  in
2727  let insert_query_item =
2728   factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._U
2729    ~callback:insertQuery in
2730  (* hbugs menu *)
2731  let hbugs_menu = factory0#add_submenu "HBugs" in
2732  let factory6 = new GMenu.factory hbugs_menu ~accel_group in
2733  let toggle_hbugs_menu_item =
2734   factory6#add_check_item
2735     ~active:false ~key:GdkKeysyms._F5 ~callback:Hbugs'.toggle "HBugs enabled"
2736  in
2737  (* settings menu *)
2738  let settings_menu = factory0#add_submenu "Settings" in
2739  let factory3 = new GMenu.factory settings_menu ~accel_group in
2740  let _ =
2741   factory3#add_item "Edit Aliases" ~key:GdkKeysyms._A
2742    ~callback:edit_aliases in
2743  let _ = factory3#add_separator () in
2744  let _ =
2745   factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
2746    ~callback:(function _ -> (settings_window ())#show ()) in
2747  (* accel group *)
2748  let _ = window#add_accel_group accel_group in
2749  (* end of menus *)
2750  let hbox0 =
2751   GPack.hbox
2752    ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
2753  let vbox =
2754   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2755  let scrolled_window0 =
2756   GBin.scrolled_window ~border_width:10
2757    ~packing:(vbox#pack ~expand:true ~padding:5) () in
2758  let _ = scrolled_window0#add output#coerce in
2759  let frame =
2760   GBin.frame ~label:"Insert Term"
2761    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2762  let scrolled_window1 =
2763   GBin.scrolled_window ~border_width:5
2764    ~packing:frame#add () in
2765  let inputt =
2766   TermEditor'.term_editor
2767    ~width:400 ~height:100 ~packing:scrolled_window1#add ()
2768    ~isnotempty_callback:
2769     (function b ->
2770       check_menu_item#misc#set_sensitive b ;
2771       searchPattern_menu_item#misc#set_sensitive b) in
2772  let vboxl =
2773   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
2774  let _ =
2775   vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
2776  let frame =
2777   GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
2778  in
2779  let outputhtml =
2780   GHtml.xmhtml
2781    ~source:"<html><body bgColor=\"white\"></body></html>"
2782    ~width:400 ~height: 100
2783    ~border_width:20
2784    ~packing:frame#add
2785    ~show:true () in
2786 object
2787  method outputhtml = outputhtml
2788  method inputt = inputt
2789  method output = (output : TermViewer.proof_viewer)
2790  method scratch_window = scratch_window
2791  method notebook = notebook
2792  method show = window#show
2793  initializer
2794   notebook#set_empty_page ;
2795   export_to_postscript_menu_item#misc#set_sensitive false ;
2796   check_term := (check_term_in_scratch scratch_window) ;
2797
2798   (* signal handlers here *)
2799   ignore(output#connect#selection_changed
2800    (function elem ->
2801      choose_selection output elem ;
2802      !focus_and_proveit_set_sensitive true
2803    )) ;
2804   ignore (output#connect#click (show_in_show_window_callback output)) ;
2805   let settings_window = new settings_window output scrolled_window0
2806    export_to_postscript_menu_item (choose_selection output) in
2807   set_settings_window settings_window ;
2808   set_outputhtml outputhtml ;
2809   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
2810   Logger.log_callback :=
2811    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
2812 end;;
2813
2814 (* MAIN *)
2815
2816 let initialize_everything () =
2817  let module U = Unix in
2818   let output = TermViewer.proof_viewer ~width:350 ~height:280 () in
2819   let notebook = new notebook in
2820    let rendering_window' = new rendering_window output notebook in
2821     set_rendering_window rendering_window' ;
2822     rendering_window'#show () ;
2823 (*     Hbugs'.toggle true; *)
2824     GtkThread.main ()
2825 ;;
2826
2827 let main () =
2828  if !usedb then
2829   begin
2830    Mqint.set_database Mqint.postgres_db ;
2831    Mqint.init postgresqlconnectionstring ;
2832   end ;
2833  ignore (GtkMain.Main.init ()) ;
2834  initialize_everything () ;
2835  if !usedb then Mqint.close ();
2836  prerr_endline "FOO";
2837  Hbugs'.quit ()
2838 ;;
2839
2840 try
2841   Sys.catch_break true;
2842   main ();
2843 with Sys.Break -> ()  (* exit nicely, invoking at_exit functions *)
2844