]> matita.cs.unibo.it Git - helm.git/blob - helm/matita/matitaMathView.ml
refactored gui handling code so that MatitaMathView is linked before MatitaGui
[helm.git] / helm / matita / matitaMathView.ml
1 (* Copyright (C) 2004-2005, 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 open Printf
27
28 open MatitaTypes
29
30 let add_trailing_slash =
31   let rex = Pcre.regexp "/$" in
32   fun s ->
33     if Pcre.pmatch ~rex s then s
34     else s ^ "/"
35
36 let strip_blanks =
37   let rex = Pcre.regexp "^\\s*([^\\s]*)\\s*$" in
38   fun s ->
39     (Pcre.extract ~rex s).(1)
40
41 (** inherit from this class if you want to access current script *)
42 class scriptAccessor =
43 object (self)
44   method private script = MatitaScript.instance ()
45 end
46
47 let cicBrowsers = ref []
48 let gui_instance = ref None
49 let set_gui gui = gui_instance := Some gui
50 let get_gui () =
51   match !gui_instance with
52   | None -> assert false
53   | Some gui -> gui
54
55 let default_font_size () =
56   Helm_registry.get_opt_default Helm_registry.int
57     ~default:BuildTimeConf.default_font_size "matita.font_size"
58 let current_font_size = ref ~-1
59 let increase_font_size () = incr current_font_size
60 let decrease_font_size () = decr current_font_size
61 let reset_font_size () = current_font_size := default_font_size ()
62
63   (* is there any lablgtk2 constant corresponding to the left mouse button??? *)
64 let left_button = 1
65
66 let near (x1, y1) (x2, y2) =
67   let distance = sqrt (((x2 -. x1) ** 2.) +. ((y2 -. y1) ** 2.)) in
68   (distance < 4.)
69
70 let href_ds = Gdome.domString "href"
71 let xref_ds = Gdome.domString "xref"
72
73 class clickableMathView obj =
74   let text_width = 80 in
75   object (self)
76     inherit GMathViewAux.multi_selection_math_view obj
77
78     val mutable href_callback: (string -> unit) option = None
79     method set_href_callback f = href_callback <- f
80
81     val mutable _cic_info = None
82     method private set_cic_info info = _cic_info <- info
83     method private cic_info =
84       match _cic_info with
85       | Some info -> info
86       | None -> assert false
87
88     initializer
89       self#set_font_size !current_font_size;
90       ignore (self#connect#selection_changed self#choose_selection);
91       ignore (self#event#connect#button_press self#button_press);
92       ignore (self#event#connect#button_release self#button_release);
93 (*       ignore (self#connect#click (fun (gdome_elt, _, _, _) ->
94         match gdome_elt with
95         | Some elt  |+ element is an hyperlink, use href_callback on it +|
96           when elt#hasAttributeNS ~namespaceURI:DomMisc.xlink_ns ~localName:href ->
97             (match href_callback with
98             | None -> ()
99             | Some f ->
100                 let uri =
101                   elt#getAttributeNS ~namespaceURI:DomMisc.xlink_ns ~localName:href
102                 in
103                 f (uri#to_string))
104         | Some elt -> ignore (self#action_toggle elt)
105         | None -> ())) *)
106
107     val mutable button_press_x = -1.
108     val mutable button_press_y = -1.
109     val mutable selection_changed = false
110
111     method private button_press gdk_button =
112       if GdkEvent.Button.button gdk_button = left_button then begin
113         button_press_x <- GdkEvent.Button.x gdk_button;
114         button_press_y <- GdkEvent.Button.y gdk_button;
115         selection_changed <- false
116       end;
117       false
118
119     method private button_release gdk_button =
120       if GdkEvent.Button.button gdk_button = left_button then begin
121         let button_release_x = GdkEvent.Button.x gdk_button in
122         let button_release_y = GdkEvent.Button.y gdk_button in
123         (if near (button_press_x, button_press_y)
124           (button_release_x, button_release_y)
125           && not selection_changed
126         then
127           let x = int_of_float button_press_x in
128           let y = int_of_float button_press_y in
129           (match self#get_element_at x y with
130           | None -> ()
131           | Some elt ->
132               let namespaceURI = DomMisc.xlink_ns in
133               let localName = href_ds in
134               if elt#hasAttributeNS ~namespaceURI ~localName then
135                 self#invoke_href_callback
136                   (elt#getAttributeNS ~namespaceURI ~localName)#to_string
137                   gdk_button
138               else
139                 ignore (self#action_toggle elt)));
140       end;
141       false
142
143     method private invoke_href_callback href_value gdk_button =
144       let button = GdkEvent.Button.button gdk_button in
145       if button = left_button then
146         let time = GdkEvent.Button.time gdk_button in
147         match href_callback with
148         | None -> ()
149         | Some f ->
150             (match MatitaMisc.split href_value with
151             | [ uri ] ->  f uri
152             | uris ->
153                 let menu = GMenu.menu () in
154                 List.iter
155                   (fun uri ->
156                     let menu_item =
157                       GMenu.menu_item ~label:uri ~packing:menu#append ()
158                     in
159                     ignore (menu_item#connect#activate (fun () -> f uri)))
160                   uris;
161                 menu#popup ~button ~time)
162
163     method private choose_selection gdome_elt =
164       let rec aux elt =
165         if (elt#getAttributeNS ~namespaceURI:DomMisc.helm_ns
166               ~localName:xref_ds)#to_string <> ""
167 (*         if elt#hasAttributeNS ~namespaceURI:DomMisc.helm_ns ~localName:xref_ds
168           && (elt#getAttributeNS ~namespaceURI:DomMisc.helm_ns
169               ~localName:xref_ds)#to_string <> "" *)
170         then
171           self#set_selection (Some elt)
172         else
173           try
174             (match elt#get_parentNode with
175             | None -> assert false
176             | Some p -> aux (new Gdome.element_of_node p))
177           with GdomeInit.DOMCastException _ -> ()
178 (*             debug_print "trying to select above the document root" *)
179       in
180       (match gdome_elt with
181       | Some elt -> aux elt
182       | None   -> self#set_selection None);
183       selection_changed <- true
184
185     method update_font_size = 
186       self#set_font_size !current_font_size
187
188     method private get_term_by_id context id =
189       let ids_to_terms, ids_to_hypotheses = self#cic_info in
190       try
191         `Term (Hashtbl.find ids_to_terms id)
192       with Not_found ->
193         try
194           let hyp = Hashtbl.find ids_to_hypotheses id in
195           let context' = MatitaMisc.list_tl_at hyp context in
196           `Hyp context'
197         with Not_found -> assert false
198       
199     method string_of_selected_terms =
200       let get_id (node: Gdome.element) =
201         let xref_attr =
202           node#getAttributeNS ~namespaceURI:DomMisc.helm_ns ~localName:xref_ds
203         in
204         xref_attr#to_string
205       in
206       let script = MatitaScript.instance () in
207       let metasenv = script#proofMetasenv in
208       let context = script#proofContext in
209       let conclusion = script#proofConclusion in
210       let cic_terms =
211         List.map
212           (fun node -> self#get_term_by_id context (get_id node))
213           self#get_selections
214       in
215 (* TODO: code for patterns
216       let conclusion = (MatitaScript.instance ())#proofConclusion in
217       let conclusion_pattern =
218         ProofEngineHelpers.pattern_of ~term:conclusion cic_terms
219       in
220 *)
221       let dummy_goal = ~-1 in
222       let cic_sequent =
223         match cic_terms with
224         | [] -> assert false
225         | `Term t :: _ ->
226             let context' =
227               ProofEngineHelpers.locate_in_conjecture t
228                 (dummy_goal, context, conclusion)
229             in
230             dummy_goal, context', t
231         | `Hyp context :: _ -> dummy_goal, context, Cic.Rel 1
232       in
233 (* TODO: code for patterns
234       (* TODO context shouldn't be empty *)
235       let cic_sequent = ~-1, [], conclusion_pattern in
236 *)
237       let acic_sequent, _, _, ids_to_inner_sorts, _ =
238         Cic2acic.asequent_of_sequent metasenv cic_sequent
239       in
240       let _, _, _, annterm = acic_sequent in
241       let ast, ids_to_uris =
242         CicNotationRew.ast_of_acic ids_to_inner_sorts annterm
243       in
244       let pped_ast = CicNotationRew.pp_ast ast in
245       let markup = CicNotationPres.render ids_to_uris pped_ast in
246       BoxPp.render_to_string text_width markup
247
248   end
249
250 let clickableMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity =
251   GtkBase.Widget.size_params
252     ~cont:(OgtkMathViewProps.pack_return (fun p ->
253       OgtkMathViewProps.set_params
254         (new clickableMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
255         ~font_size:None ~log_verbosity:None))
256     []
257
258 class sequentViewer obj =
259 object (self)
260   inherit clickableMathView obj
261
262   method load_sequent metasenv metano =
263     let sequent = CicUtil.lookup_meta metano metasenv in
264     let (mathml, (_, (ids_to_terms, _, ids_to_hypotheses,_ ))) =
265       ApplyTransformation.mml_of_cic_sequent metasenv sequent
266     in
267     self#set_cic_info (Some (ids_to_terms, ids_to_hypotheses));
268     let name = "sequent_viewer.xml" in
269     prerr_endline ("load_sequent: dumping MathML to ./" ^ name);
270     ignore (DomMisc.domImpl#saveDocumentToFile ~name ~doc:mathml ());
271     self#load_root ~root:mathml#get_documentElement
272  end
273
274 class sequentsViewer ~(notebook:GPack.notebook)
275   ~(sequentViewer:sequentViewer) ()
276 =
277   object (self)
278     inherit scriptAccessor
279
280     val mutable pages = 0
281     val mutable switch_page_callback = None
282     val mutable page2goal = []  (* associative list: page no -> goal no *)
283     val mutable goal2page = []  (* the other way round *)
284     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
285     val mutable _metasenv = []
286     val mutable scrolledWin: GBin.scrolled_window option = None
287       (* scrolled window to which the sequentViewer is currently attached *)
288
289     method private tab_label metano =
290       (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
291
292     method reset =
293       (match scrolledWin with
294       | Some w ->
295           (* removing page from the notebook will destroy all contained widget,
296           * we do not want the sequentViewer to be destroyed as well *)
297           w#remove sequentViewer#coerce;
298           scrolledWin <- None
299       | None -> ());
300       for i = 1 to pages do notebook#remove_page 0 done;
301       pages <- 0;
302       page2goal <- [];
303       goal2page <- [];
304       goal2win <- [];
305       _metasenv <- [];
306       self#script#setGoal ~-1;
307       (match switch_page_callback with
308       | Some id ->
309           GtkSignal.disconnect notebook#as_widget id;
310           switch_page_callback <- None
311       | None -> ())
312
313     method load_sequents (status: ProofEngineTypes.status) =
314       let ((_, metasenv, _, _), goal) = status in
315       let sequents_no = List.length metasenv in
316       _metasenv <- metasenv;
317       pages <- sequents_no;
318       self#script#setGoal goal;
319       let parentref = ref None in
320       let win metano =
321         let w =
322           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC
323             ~shadow_type:`IN ~show:true ()
324         in
325         let reparent () =
326           scrolledWin <- Some w;
327           match sequentViewer#misc#parent with
328           | None -> w#add sequentViewer#coerce; parentref := Some w
329           | Some parent ->
330              let parent =
331               match !parentref with None -> assert false | Some p -> p in
332              parent#remove sequentViewer#coerce;
333              w#add sequentViewer#coerce;
334              parentref := Some w;
335         in
336         goal2win <- (metano, reparent) :: goal2win;
337         w#coerce
338       in
339       let page = ref 0 in
340       List.iter
341         (fun (metano, _, _) ->
342           page2goal <- (!page, metano) :: page2goal;
343           goal2page <- (metano, !page) :: goal2page;
344           incr page;
345           notebook#append_page ~tab_label:(self#tab_label metano) (win metano))
346         metasenv;
347       switch_page_callback <-
348         Some (notebook#connect#switch_page ~callback:(fun page ->
349           let goal =
350             try
351               List.assoc page page2goal
352             with Not_found -> assert false
353           in
354           self#script#setGoal goal;
355           self#render_page ~page ~goal))
356
357     method private render_page ~page ~goal =
358       sequentViewer#load_sequent _metasenv goal;
359       try
360         List.assoc goal goal2win ();
361         sequentViewer#set_selection None
362       with Not_found -> assert false
363
364     method goto_sequent goal =
365       let page =
366         try
367           List.assoc goal goal2page
368         with Not_found -> assert false
369       in
370       notebook#goto_page page;
371       self#render_page page goal
372
373   end
374
375  (** constructors *)
376
377 type 'widget constructor =
378   ?hadjustment:GData.adjustment ->
379   ?vadjustment:GData.adjustment ->
380   ?font_size:int ->
381   ?log_verbosity:int ->
382   ?width:int ->
383   ?height:int ->
384   ?packing:(GObj.widget -> unit) ->
385   ?show:bool ->
386   unit ->
387     'widget
388
389 let sequentViewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
390   GtkBase.Widget.size_params
391     ~cont:(OgtkMathViewProps.pack_return (fun p ->
392       OgtkMathViewProps.set_params
393         (new sequentViewer (GtkMathViewProps.MathView_GMetaDOM.create p))
394         ~font_size ~log_verbosity))
395     []
396
397 let blank_uri = BuildTimeConf.blank_uri
398 let current_proof_uri = BuildTimeConf.current_proof_uri
399
400 type term_source =
401   [ `Ast of DisambiguateTypes.term
402   | `Cic of Cic.term * Cic.metasenv
403   | `String of string
404   ]
405
406 class type cicBrowser =
407 object
408   method load: MatitaTypes.mathViewer_entry -> unit
409   (* method loadList: string list -> MatitaTypes.mathViewer_entry-> unit *)
410   method loadInput: string -> unit
411 end
412
413 let reloadable = function
414   | `About `Current_proof
415   | `Dir _ ->
416       true
417   | _ -> false
418
419 class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history)
420   ()
421 =
422   let term_RE = Pcre.regexp "^term:(.*)" in
423   let whelp_RE = Pcre.regexp "^\\s*whelp" in
424   let uri_RE =
425     Pcre.regexp
426       "^cic:/([^/]+/)*[^/]+\\.(con|ind|var)(#xpointer\\(\\d+(/\\d+)+\\))?$"
427   in
428   let dir_RE = Pcre.regexp "^cic:((/([^/]+/)*[^/]+(/)?)|/|)$" in
429   let whelp_query_RE = Pcre.regexp "^\\s*whelp\\s+([^\\s]+)\\s+(.*)$" in
430   let trailing_slash_RE = Pcre.regexp "/$" in
431   let has_xpointer_RE = Pcre.regexp "#xpointer\\(\\d+/\\d+(/\\d+)?\\)$" in
432   let is_whelp txt = Pcre.pmatch ~rex:whelp_RE txt in
433   let is_uri txt = Pcre.pmatch ~rex:uri_RE txt in
434   let is_dir txt = Pcre.pmatch ~rex:dir_RE txt in
435   let gui = get_gui () in
436   let (win: MatitaGuiTypes.browserWin) = gui#newBrowserWin () in
437   let queries = ["Locate";"Hint";"Match";"Elim";"Instance"] in
438   let combo,_ = GEdit.combo_box_text ~strings:queries () in
439   let activate_combo_query input q =
440     let q' = String.lowercase q in
441     let rec aux i = function
442       | [] -> failwith ("Whelp query '" ^ q ^ "' not found")
443       | h::_ when String.lowercase h = q' -> i
444       | _::tl -> aux (i+1) tl
445     in
446     combo#set_active (aux 0 queries);
447     win#queryInputText#set_text input
448   in
449   let set_whelp_query txt =
450     let query, arg = 
451       try
452         let q = Pcre.extract ~rex:whelp_query_RE txt in
453         q.(1), q.(2)
454       with Invalid_argument _ -> failwith "Malformed Whelp query"
455     in
456     activate_combo_query arg query
457   in
458   let toplevel = win#toplevel in
459   let mathView = sequentViewer ~packing:win#scrolledBrowser#add () in
460   let fail message = 
461     MatitaGtkMisc.report_error ~title:"Cic browser" ~message 
462       ~parent:toplevel ()  
463   in
464   let tags =
465     [ "dir", GdkPixbuf.from_file (MatitaMisc.image_path "matita-folder.png");
466       "obj", GdkPixbuf.from_file (MatitaMisc.image_path "matita-object.png") ]
467   in
468   let handle_error f =
469     try
470       f ()
471     with exn -> fail (MatitaExcPp.to_string exn)
472   in
473   let handle_error' f = (fun () -> handle_error (fun () -> f ())) in
474   object (self)
475     inherit scriptAccessor
476     
477     (* Whelp bar queries *)
478
479     initializer
480       activate_combo_query "" "locate";
481       win#whelpBarComboVbox#add combo#coerce;
482       let start_query () = 
483         let query = String.lowercase (List.nth queries combo#active) in
484         let input = win#queryInputText#text in
485         let statement = "whelp " ^ query ^ " " ^ input ^ "." in
486         (MatitaScript.instance ())#advance ~statement ()
487       in
488       ignore(win#queryInputText#connect#activate ~callback:start_query);
489       ignore(combo#connect#changed ~callback:start_query);
490       win#whelpBarImage#set_file (MatitaMisc.image_path "whelp.png");
491       win#mathOrListNotebook#set_show_tabs false;
492
493       win#browserForwardButton#misc#set_sensitive false;
494       win#browserBackButton#misc#set_sensitive false;
495       ignore (win#browserUri#entry#connect#activate (handle_error' (fun () ->
496         self#loadInput win#browserUri#entry#text)));
497       ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
498         self#load (`About `Current_proof))));
499       ignore (win#browserRefreshButton#connect#clicked
500         (handle_error' self#refresh));
501       ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
502       ignore (win#browserForwardButton#connect#clicked
503         (handle_error' self#forward));
504       ignore (win#toplevel#event#connect#delete (fun _ ->
505         let my_id = Oo.id self in
506         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
507         if !cicBrowsers = [] &&
508           Helm_registry.get "matita.mode" = "cicbrowser"
509         then
510           GMain.quit ();
511         false));
512       ignore(win#whelpResultTreeview#connect#row_activated 
513         ~callback:(fun _ _ ->
514           handle_error (fun () -> self#loadInput (self#_getSelectedUri ()))));
515       mathView#set_href_callback (Some (fun uri ->
516         handle_error (fun () ->
517           self#load (`Uri (UriManager.uri_of_string uri)))));
518       self#_load (`About `Blank);
519       toplevel#show ()
520
521     val mutable current_entry = `About `Blank 
522     val mutable current_infos = None
523     val mutable current_mathml = None
524
525     val model =
526       new MatitaGtkMisc.taggedStringListModel tags win#whelpResultTreeview
527
528     val mutable lastDir = ""  (* last loaded "directory" *)
529
530     method private _getSelectedUri () =
531       match model#easy_selection () with
532       | [sel] when is_uri sel -> sel  (* absolute URI selected *)
533 (*       | [sel] -> win#browserUri#entry#text ^ sel  |+ relative URI selected +| *)
534       | [sel] -> lastDir ^ sel
535       | _ -> assert false
536
537     (** history RATIONALE 
538      *
539      * All operations about history are done using _historyFoo.
540      * Only toplevel functions (ATM load and loadInput) call _historyAdd.
541      *)
542           
543     method private _historyAdd item = 
544       history#add item;
545       win#browserBackButton#misc#set_sensitive true;
546       win#browserForwardButton#misc#set_sensitive false
547
548     method private _historyPrev () =
549       let item = history#previous in
550       if history#is_begin then win#browserBackButton#misc#set_sensitive false;
551       win#browserForwardButton#misc#set_sensitive true;
552       item
553     
554     method private _historyNext () =
555       let item = history#next in
556       if history#is_end then win#browserForwardButton#misc#set_sensitive false;
557       win#browserBackButton#misc#set_sensitive true;
558       item
559
560     (** notebook RATIONALE 
561      * 
562      * Use only these functions to switch between the tabs
563      *)
564     method private _showList = win#mathOrListNotebook#goto_page 1
565     method private _showMath = win#mathOrListNotebook#goto_page 0
566     
567     method private back () =
568       try
569         self#_load (self#_historyPrev ())
570       with MatitaMisc.History_failure -> ()
571
572     method private forward () =
573       try
574         self#_load (self#_historyNext ())
575       with MatitaMisc.History_failure -> ()
576
577       (* loads a uri which can be a cic uri or an about:* uri
578       * @param uri string *)
579     method private _load entry =
580       try
581         if entry <> current_entry || reloadable entry then begin
582           (match entry with
583           | `About `Current_proof -> self#home ()
584           | `About `Blank -> self#blank ()
585           | `About `Us -> () (* TODO implement easter egg here :-] *)
586           | `Check term -> self#_loadCheck term
587           | `Cic (term, metasenv) -> self#_loadTermCic term metasenv
588           | `Dir dir -> self#_loadDir dir
589           | `Uri uri -> self#_loadUriManagerUri uri
590           | `Whelp (query, results) -> 
591               set_whelp_query query;
592               self#_loadList (List.map (fun r -> "obj",
593                 UriManager.string_of_uri r) results));
594           self#setEntry entry
595         end
596       with exn -> fail (MatitaExcPp.to_string exn)
597
598     method private blank () =
599       self#_showMath;
600       mathView#load_root (MatitaMisc.empty_mathml ())#get_documentElement
601
602     method private _loadCheck term =
603       failwith "not implemented _loadCheck";
604       self#_showMath
605
606     method private home () =
607       self#_showMath;
608       match self#script#status.proof_status with
609       | Proof  (uri, metasenv, bo, ty) ->
610           let name = UriManager.name_of_uri (MatitaMisc.unopt uri) in
611           let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
612           self#_loadObj obj
613       | Incomplete_proof ((uri, metasenv, bo, ty), _) -> 
614           let name = UriManager.name_of_uri (MatitaMisc.unopt uri) in
615           let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
616           self#_loadObj obj
617       | _ -> self#blank ()
618
619       (** loads a cic uri from the environment
620       * @param uri UriManager.uri *)
621     method private _loadUriManagerUri uri =
622       let uri = UriManager.strip_xpointer uri in
623       let (obj, _) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
624       self#_loadObj obj
625       
626     method private _loadDir dir = 
627       let content = Http_getter.ls dir in
628       let l =
629         List.fast_sort
630           Pervasives.compare
631           (List.map
632             (function 
633               | Http_getter_types.Ls_section s -> "dir", s
634               | Http_getter_types.Ls_object o -> "obj", o.Http_getter_types.uri)
635             content)
636       in
637       lastDir <- dir;
638       self#_loadList l
639
640     method private setEntry entry =
641       win#browserUri#entry#set_text (string_of_entry entry);
642       current_entry <- entry
643
644     method private _loadObj obj =
645       self#_showMath; 
646       (* this must be _before_ loading the document, since 
647        * if the widget is not mapped (hidden by the notebook)
648        * the document is not rendered *)
649       let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *)
650       let (mathml, (_,((ids_to_terms, ids_to_father_ids, ids_to_conjectures,
651            ids_to_hypotheses, ids_to_inner_sorts, ids_to_inner_types) as info)))
652       =
653         ApplyTransformation.mml_of_cic_object obj
654       in
655       current_infos <- Some info;
656       (match current_mathml with
657       | Some current_mathml when use_diff ->
658           mathView#freeze;
659           XmlDiff.update_dom ~from:current_mathml mathml;
660           mathView#thaw
661       |  _ ->
662           let name = "cic_browser.xml" in
663           prerr_endline ("cic_browser: dumping MathML to ./" ^ name);
664           ignore (DomMisc.domImpl#saveDocumentToFile ~name ~doc:mathml ());
665           mathView#load_root ~root:mathml#get_documentElement;
666           current_mathml <- Some mathml);
667
668     method private _loadTermCic term metasenv =
669       let context = self#script#proofContext in
670       let dummyno = CicMkImplicit.new_meta metasenv [] in
671       let sequent = (dummyno, context, term) in
672       mathView#load_sequent (sequent :: metasenv) dummyno;
673       self#_showMath
674
675     method private _loadList l =
676       model#list_store#clear ();
677       List.iter (fun (tag, s) -> model#easy_append ~tag s) l;
678       self#_showList
679     
680     (** { public methods, all must call _load!! } *)
681       
682     method load entry =
683       handle_error (fun () -> self#_load entry; self#_historyAdd entry)
684
685     (**  this is what the browser does when you enter a string an hit enter *)
686     method loadInput txt =
687       let txt = strip_blanks txt in
688       let fix_uri txt =
689         UriManager.string_of_uri
690           (UriManager.strip_xpointer (UriManager.uri_of_string txt))
691       in
692       if is_whelp txt then begin
693         set_whelp_query txt;  
694         (MatitaScript.instance ())#advance ~statement:(txt ^ ".") ()
695       end else begin
696         let entry =
697           match txt with
698           | txt when is_uri txt -> `Uri (UriManager.uri_of_string (fix_uri txt))
699           | txt when is_dir txt -> `Dir (add_trailing_slash txt)
700           | txt ->
701               (try
702                 entry_of_string txt
703               with Invalid_argument _ ->
704                 command_error (sprintf "unsupported uri: %s" txt))
705         in
706         self#_load entry;
707         self#_historyAdd entry
708       end
709
710       (** {2 methods accessing underlying GtkMathView} *)
711
712     method updateFontSize = mathView#set_font_size !current_font_size
713
714       (** {2 methods used by constructor only} *)
715
716     method win = win
717     method history = history
718     method currentEntry = current_entry
719     method refresh () =
720       if reloadable current_entry then self#_load current_entry
721
722   end
723   
724 let sequentsViewer ~(notebook:GPack.notebook)
725   ~(sequentViewer:sequentViewer) ()
726 =
727   new sequentsViewer ~notebook ~sequentViewer ()
728
729 let cicBrowser () =
730   let size = BuildTimeConf.browser_history_size in
731   let rec aux history =
732     let browser = new cicBrowser_impl ~history () in
733     let win = browser#win in
734     ignore (win#browserNewButton#connect#clicked (fun () ->
735       let history =
736         new MatitaMisc.browser_history ~memento:history#save size
737           (`About `Blank)
738       in
739       let newBrowser = aux history in
740       newBrowser#load browser#currentEntry));
741 (*
742       (* attempt (failed) to close windows on CTRL-W ... *)
743     MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
744       GdkKeysyms._W (fun () -> win#toplevel#destroy ());
745 *)
746     cicBrowsers := browser :: !cicBrowsers;
747     (browser :> cicBrowser)
748   in
749   let history = new MatitaMisc.browser_history size (`About `Blank) in
750   aux history
751
752 let default_sequentViewer () = sequentViewer ~show:true ()
753 let sequentViewer_instance = MatitaMisc.singleton default_sequentViewer
754
755 let default_sequentsViewer () =
756   let gui = get_gui () in
757   let sequentViewer = sequentViewer_instance () in
758   sequentsViewer ~notebook:gui#main#sequentsNotebook ~sequentViewer ()
759 let sequentsViewer_instance = MatitaMisc.singleton default_sequentsViewer
760
761 let mathViewer () = 
762   object(self)
763     method private get_browser reuse = 
764       if reuse then
765         (match !cicBrowsers with
766         | [] -> cicBrowser ()
767         | b :: _ -> (b :> cicBrowser))
768       else
769         (cicBrowser ())
770           
771     method show_entry ?(reuse=false) t = (self#get_browser reuse)#load t
772       
773     method show_uri_list ?(reuse=false) ~entry l =
774       (self#get_browser reuse)#load entry
775   end
776
777 let refresh_all_browsers () = List.iter (fun b -> b#refresh ()) !cicBrowsers
778
779 let update_font_sizes () =
780   List.iter (fun b -> b#updateFontSize) !cicBrowsers;
781   (sequentViewer_instance ())#update_font_size
782