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