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