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