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