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