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