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