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