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