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