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