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