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