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