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