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