]> matita.cs.unibo.it Git - helm.git/blob - matita/matita/matitaMathView.ml
ef7780f0c88a8b3993a2c6628007ed1e1d63d5b0
[helm.git] / matita / 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 (* $Id$ *)
27
28 open Printf
29
30 open GrafiteTypes
31 open MatitaGtkMisc
32 open MatitaGuiTypes
33 open CicMathView
34
35 module Stack = Continuationals.Stack
36
37 let cicBrowsers = ref []
38
39 let tab_label meta_markup =
40   let rec aux =
41     function
42     | `Closed m -> sprintf "<s>%s</s>" (aux m)
43     | `Current m -> sprintf "<b>%s</b>" (aux m)
44     | `Shift (pos, m) -> sprintf "|<sub>%d</sub>: %s" pos (aux m)
45     | `Meta n -> sprintf "?%d" n
46   in
47   let markup = aux meta_markup in
48   (GMisc.label ~markup ~show:true ())#coerce
49
50 let goal_of_switch = function Stack.Open g | Stack.Closed g -> g
51
52 class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () =
53   object (self)
54     method cicMathView = cicMathView  (** clickableMathView accessor *)
55
56     val mutable pages = 0
57     val mutable switch_page_callback = None
58     val mutable page2goal = []  (* associative list: page no -> goal no *)
59     val mutable goal2page = []  (* the other way round *)
60     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
61     val mutable _metasenv = [],[]
62     val mutable scrolledWin: GBin.scrolled_window option = None
63       (* scrolled window to which the sequentViewer is currently attached *)
64     val logo = (GMisc.image
65       ~file:(MatitaMisc.image_path "matita_medium.png") ()
66       :> GObj.widget)
67             
68     val logo_with_qed = (GMisc.image
69       ~file:(MatitaMisc.image_path "matita_small.png") ()
70       :> GObj.widget)
71
72     method load_logo =
73      notebook#set_show_tabs false;
74      ignore(notebook#append_page logo)
75
76     method load_logo_with_qed =
77      notebook#set_show_tabs false;
78      ignore(notebook#append_page logo_with_qed)
79
80     method reset =
81       cicMathView#remove_selections;
82       (match scrolledWin with
83       | Some w ->
84           (* removing page from the notebook will destroy all contained widget,
85           * we do not want the cicMathView to be destroyed as well *)
86           w#remove cicMathView#coerce;
87           scrolledWin <- None
88       | None -> ());
89       (match switch_page_callback with
90       | Some id ->
91           GtkSignal.disconnect notebook#as_widget id;
92           switch_page_callback <- None
93       | None -> ());
94       for i = 0 to pages do notebook#remove_page 0 done; 
95       notebook#set_show_tabs true;
96       pages <- 0;
97       page2goal <- [];
98       goal2page <- [];
99       goal2win <- [];
100       _metasenv <- [],[]
101
102     method nload_sequents : 'status. #GrafiteTypes.status as 'status -> unit
103     = fun (status : #GrafiteTypes.status) ->
104      let _,_,metasenv,subst,_ = status#obj in
105       _metasenv <- metasenv,subst;
106       pages <- 0;
107       let win goal_switch =
108         let w =
109           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`ALWAYS
110             ~shadow_type:`IN ~show:true () in
111         let reparent () =
112           scrolledWin <- Some w;
113           (match cicMathView#misc#parent with
114             | None -> ()
115             | Some parent ->
116                let parent =
117                 match cicMathView#misc#parent with
118                    None -> assert false
119                  | Some p -> GContainer.cast_container p
120                in
121                 parent#remove cicMathView#coerce);
122           w#add cicMathView#coerce
123         in
124         goal2win <- (goal_switch, reparent) :: goal2win;
125         w#coerce
126       in
127       assert (
128         let stack_goals = Stack.open_goals status#stack in
129         let proof_goals = List.map fst metasenv in
130         if
131           HExtlib.list_uniq (List.sort Pervasives.compare stack_goals)
132           <> List.sort Pervasives.compare proof_goals
133         then begin
134           prerr_endline ("STACK GOALS = " ^ String.concat " " (List.map string_of_int stack_goals));
135           prerr_endline ("PROOF GOALS = " ^ String.concat " " (List.map string_of_int proof_goals));
136           false
137         end
138         else true
139       );
140       let render_switch =
141         function Stack.Open i ->`Meta i | Stack.Closed i ->`Closed (`Meta i)
142       in
143       let page = ref 0 in
144       let added_goals = ref [] in
145         (* goals can be duplicated on the tack due to focus, but we should avoid
146          * multiple labels in the user interface *)
147       let add_tab markup goal_switch =
148         let goal = Stack.goal_of_switch goal_switch in
149         if not (List.mem goal !added_goals) then begin
150           ignore(notebook#append_page 
151             ~tab_label:(tab_label markup) (win goal_switch));
152           page2goal <- (!page, goal_switch) :: page2goal;
153           goal2page <- (goal_switch, !page) :: goal2page;
154           incr page;
155           pages <- pages + 1;
156           added_goals := goal :: !added_goals
157         end
158       in
159       let add_switch _ _ (_, sw) = add_tab (render_switch sw) sw in
160       Stack.iter  (** populate notebook with tabs *)
161         ~env:(fun depth tag (pos, sw) ->
162           let markup =
163             match depth, pos with
164             | 0, 0 -> `Current (render_switch sw)
165             | 0, _ -> `Shift (pos, `Current (render_switch sw))
166             | 1, pos when Stack.head_tag status#stack = `BranchTag ->
167                 `Shift (pos, render_switch sw)
168             | _ -> render_switch sw
169           in
170           add_tab markup sw)
171         ~cont:add_switch ~todo:add_switch
172         status#stack;
173       switch_page_callback <-
174         Some (notebook#connect#switch_page ~callback:(fun page ->
175           let goal_switch =
176             try List.assoc page page2goal with Not_found -> assert false
177           in
178           self#render_page status ~page ~goal_switch))
179
180     method private render_page:
181      'status. #ApplyTransformation.status as 'status -> page:int ->
182        goal_switch:Stack.switch -> unit
183      = fun status ~page ~goal_switch ->
184       (match goal_switch with
185       | Stack.Open goal ->
186          let menv,subst = _metasenv in
187           cicMathView#nload_sequent status menv subst goal
188       | Stack.Closed goal ->
189           let root = Lazy.force closed_goal_mathml in
190           cicMathView#load_root ~root);
191       (try
192         cicMathView#set_selection None;
193         List.assoc goal_switch goal2win ();
194         (match cicMathView#misc#parent with
195            None -> assert false
196          | Some p ->
197             (* The text widget dinamycally inserts the text in a separate
198                thread. We need to wait for it to terminate before we can
199                move the scrollbar to the end *)
200             while Glib.Main.pending()do ignore(Glib.Main.iteration false); done;
201             let w =
202              new GBin.scrolled_window
203               (Gobject.try_cast p#as_widget "GtkScrolledWindow") in
204             (* The double change upper/lower is to trigger the emission of
205                changed :-( *)
206             w#hadjustment#set_value w#hadjustment#upper;
207             w#hadjustment#set_value w#hadjustment#lower;
208             w#vadjustment#set_value w#vadjustment#lower;
209             w#vadjustment#set_value
210              (w#vadjustment#upper -. w#vadjustment#page_size));
211       with Not_found -> assert false)
212
213     method goto_sequent: 'status. #ApplyTransformation.status as 'status -> int -> unit
214      = fun status goal ->
215       let goal_switch, page =
216         try
217           List.find
218             (function Stack.Open g, _ | Stack.Closed g, _ -> g = goal)
219             goal2page
220         with Not_found -> assert false
221       in
222       notebook#goto_page page;
223       self#render_page status ~page ~goal_switch
224   end
225
226 let blank_uri = BuildTimeConf.blank_uri
227 let current_proof_uri = BuildTimeConf.current_proof_uri
228
229 type term_source =
230   [ `Ast of NotationPt.term
231   | `NCic of NCic.term * NCic.context * NCic.metasenv * NCic.substitution
232   | `String of string
233   ]
234
235 class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history)
236   ()
237 =
238   let uri_RE =
239     Pcre.regexp
240       "^cic:/([^/]+/)*[^/]+\\.(con|ind|var)(#xpointer\\(\\d+(/\\d+)+\\))?$"
241   in
242   let dir_RE = Pcre.regexp "^cic:((/([^/]+/)*[^/]+(/)?)|/|)$" in
243   let is_uri txt = Pcre.pmatch ~rex:uri_RE txt in
244   let is_dir txt = Pcre.pmatch ~rex:dir_RE txt in
245   let _gui = MatitaMisc.get_gui () in
246   let win = new MatitaGeneratedGui.browserWin () in
247   let _ = win#browserUri#misc#grab_focus () in
248   let gviz = LablGraphviz.graphviz ~packing:win#graphScrolledWin#add () in
249   let searchText = 
250     GSourceView3.source_view ~auto_indent:false ~editable:false ()
251   in
252   let _ =
253      win#scrolledwinContent#add (searchText :> GObj.widget);
254      let callback () = 
255        let text = win#entrySearch#text in
256        let highlight start end_ =
257          searchText#source_buffer#move_mark `INSERT ~where:start;
258          searchText#source_buffer#move_mark `SEL_BOUND ~where:end_;
259          searchText#scroll_mark_onscreen `INSERT
260        in
261        let iter = searchText#source_buffer#get_iter `SEL_BOUND in
262        match iter#forward_search text with
263        | None -> 
264            (match searchText#source_buffer#start_iter#forward_search text with
265            | None -> ()
266            | Some (start,end_) -> highlight start end_)
267        | Some (start,end_) -> highlight start end_
268      in
269      ignore(win#entrySearch#connect#activate ~callback);
270      ignore(win#buttonSearch#connect#clicked ~callback);
271   in
272   let toplevel = win#toplevel in
273   let mathView = cicMathView ~packing:win#scrolledBrowser#add () in
274   let fail message = 
275     MatitaGtkMisc.report_error ~title:"Cic browser" ~message 
276       ~parent:toplevel ()  
277   in
278   let tags =
279     [ "dir", GdkPixbuf.from_file (MatitaMisc.image_path "matita-folder.png");
280       "obj", GdkPixbuf.from_file (MatitaMisc.image_path "matita-object.png") ]
281   in
282   let b = (not (Helm_registry.get_bool "matita.debug")) in
283   let handle_error f =
284     try
285       f ()
286     with exn ->
287       if b then
288         fail (snd (MatitaExcPp.to_string exn))
289       else raise exn
290   in
291   let handle_error' f = (fun () -> handle_error (fun () -> f ())) in
292   let load_easter_egg = lazy (
293     win#browserImage#set_file (MatitaMisc.image_path "meegg.png"))
294   in
295   let load_hints () =
296       let module Pp = GraphvizPp.Dot in
297       let filename, oc = Filename.open_temp_file "matita" ".dot" in
298       let fmt = Format.formatter_of_out_channel oc in
299       let status = (get_matita_script_current ())#status in
300       Pp.header 
301         ~name:"Hints"
302         ~graph_type:"graph"
303         ~graph_attrs:["overlap", "false"]
304         ~node_attrs:["fontsize", "9"; "width", ".4"; 
305             "height", ".4"; "shape", "box"]
306         ~edge_attrs:["fontsize", "10"; "len", "2"] fmt;
307       NCicUnifHint.generate_dot_file status fmt;
308       Pp.trailer fmt;
309       Pp.raw "@." fmt;
310       close_out oc;
311       gviz#load_graph_from_file ~gviz_cmd:"neato -Tpng" filename;
312       (*HExtlib.safe_remove filename*)
313   in
314   let load_coerchgraph tred () = 
315       let module Pp = GraphvizPp.Dot in
316       let filename, oc = Filename.open_temp_file "matita" ".dot" in
317       let fmt = Format.formatter_of_out_channel oc in
318       Pp.header 
319         ~name:"Coercions"
320         ~node_attrs:["fontsize", "9"; "width", ".4"; "height", ".4"]
321         ~edge_attrs:["fontsize", "10"] fmt;
322       let status = (get_matita_script_current ())#status in
323       NCicCoercion.generate_dot_file status fmt;
324       Pp.trailer fmt;
325       Pp.raw "@." fmt;
326       close_out oc;
327       if tred then
328         gviz#load_graph_from_file 
329           (* gvpack can no longer read the output of -Txdot :-( *)
330           (*~gviz_cmd:"dot -Txdot | tred |gvpack -gv | dot" filename*)
331           ~gviz_cmd:"dot -Txdot | tred | dot" filename
332       else
333         gviz#load_graph_from_file 
334           (* gvpack can no longer read the output of -Txdot :-( *)
335           (*~gviz_cmd:"dot -Txdot | gvpack -gv | dot" filename;*)
336           ~gviz_cmd:"dot -Txdot | dot" filename;
337       HExtlib.safe_remove filename
338   in
339   object (self)
340     val mutable gviz_uri =
341       let uri = NUri.uri_of_string "cic:/dummy/dec.con" in
342       NReference.reference_of_spec uri NReference.Decl;
343
344     val dep_contextual_menu = GMenu.menu ()
345
346     initializer
347       win#mathOrListNotebook#set_show_tabs false;
348       win#browserForwardButton#misc#set_sensitive false;
349       win#browserBackButton#misc#set_sensitive false;
350       ignore (win#browserUri#connect#activate (handle_error' (fun () ->
351         self#loadInput win#browserUri#text)));
352       ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
353         self#load (`About `Current_proof))));
354       ignore (win#browserRefreshButton#connect#clicked
355         (handle_error' (self#refresh ~force:true)));
356       ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
357       ignore (win#browserForwardButton#connect#clicked
358         (handle_error' self#forward));
359       ignore (win#toplevel#event#connect#delete (fun _ ->
360         let my_id = Oo.id self in
361         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
362         false));
363       ignore(win#whelpResultTreeview#connect#row_activated 
364         ~callback:(fun _ _ ->
365           handle_error (fun () -> self#loadInput (self#_getSelectedUri ()))));
366       mathView#set_href_callback (Some (fun uri ->
367         handle_error (fun () ->
368          let uri = `NRef (NReference.reference_of_string uri) in
369           self#load uri)));
370       gviz#connect_href (fun button_ev attrs ->
371         let time = GdkEvent.Button.time button_ev in
372         let uri = List.assoc "href" attrs in
373         gviz_uri <- NReference.reference_of_string uri;
374         match GdkEvent.Button.button button_ev with
375         | button when button = MatitaMisc.left_button -> self#load (`NRef gviz_uri)
376         | button when button = MatitaMisc.right_button ->
377             dep_contextual_menu#popup ~button ~time
378         | _ -> ());
379       connect_menu_item win#browserCloseMenuItem (fun () ->
380         let my_id = Oo.id self in
381         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
382         win#toplevel#misc#hide(); win#toplevel#destroy ());
383       connect_menu_item win#browserUrlMenuItem (fun () ->
384         win#browserUri#misc#grab_focus ());
385
386       self#_load (`About `Blank);
387       toplevel#show ()
388
389     val mutable current_entry = `About `Blank 
390
391       (** @return None if no object uri can be built from the current entry *)
392     method private currentCicUri =
393       match current_entry with
394       | `NRef uri -> Some uri
395       | _ -> None
396
397     val model =
398       new MatitaGtkMisc.taggedStringListModel tags win#whelpResultTreeview
399
400     val mutable lastDir = ""  (* last loaded "directory" *)
401
402     method mathView = mathView
403
404     method private _getSelectedUri () =
405       match model#easy_selection () with
406       | [sel] when is_uri sel -> sel  (* absolute URI selected *)
407 (*       | [sel] -> win#browserUri#entry#text ^ sel  |+ relative URI selected +| *)
408       | [sel] -> lastDir ^ sel
409       | _ -> assert false
410
411     (** history RATIONALE 
412      *
413      * All operations about history are done using _historyFoo.
414      * Only toplevel functions (ATM load and loadInput) call _historyAdd.
415      *)
416           
417     method private _historyAdd item = 
418       history#add item;
419       win#browserBackButton#misc#set_sensitive true;
420       win#browserForwardButton#misc#set_sensitive false
421
422     method private _historyPrev () =
423       let item = history#previous in
424       if history#is_begin then win#browserBackButton#misc#set_sensitive false;
425       win#browserForwardButton#misc#set_sensitive true;
426       item
427     
428     method private _historyNext () =
429       let item = history#next in
430       if history#is_end then win#browserForwardButton#misc#set_sensitive false;
431       win#browserBackButton#misc#set_sensitive true;
432       item
433
434     (** notebook RATIONALE 
435      * 
436      * Use only these functions to switch between the tabs
437      *)
438     method private _showMath = win#mathOrListNotebook#goto_page   0
439     method private _showList = win#mathOrListNotebook#goto_page   1
440     method private _showEgg  = win#mathOrListNotebook#goto_page   2
441     method private _showGviz = win#mathOrListNotebook#goto_page   3
442     method private _showSearch = win#mathOrListNotebook#goto_page 4
443
444     method private back () =
445       try
446         self#_load (self#_historyPrev ())
447       with MatitaMisc.History_failure -> ()
448
449     method private forward () =
450       try
451         self#_load (self#_historyNext ())
452       with MatitaMisc.History_failure -> ()
453
454       (* loads a uri which can be a cic uri or an about:* uri
455       * @param uri string *)
456     method private _load ?(force=false) entry =
457       handle_error (fun () ->
458        if entry <> current_entry || entry = `About `Current_proof || entry =
459          `About `Coercions || entry = `About `CoercionsFull || force then
460         begin
461           (match entry with
462           | `About `Current_proof -> self#home ()
463           | `About `Blank -> self#blank ()
464           | `About `Us -> self#egg ()
465           | `About `CoercionsFull -> self#coerchgraph false ()
466           | `About `Coercions -> self#coerchgraph true ()
467           | `About `Hints -> self#hints ()
468           | `About `TeX -> self#tex ()
469           | `About `Grammar -> self#grammar () 
470           | `Check term -> self#_loadCheck term
471           | `NCic (term, ctx, metasenv, subst) -> 
472                self#_loadTermNCic term metasenv subst ctx
473           | `Dir dir -> self#_loadDir dir
474           | `NRef nref -> self#_loadNReference nref);
475           self#setEntry entry
476         end)
477
478     method private blank () =
479       self#_showMath;
480       mathView#load_root (Lazy.force empty_mathml)
481
482     method private _loadCheck term =
483       failwith "not implemented _loadCheck";
484 (*       self#_showMath *)
485
486     method private egg () =
487       self#_showEgg;
488       Lazy.force load_easter_egg
489
490     method private redraw_gviz ?center_on () =
491       if Sys.command "which dot" = 0 then
492        let tmpfile, oc = Filename.open_temp_file "matita" ".dot" in
493        (* MATITA 1.0 let fmt = Format.formatter_of_out_channel oc in
494        MetadataDeps.DepGraph.render fmt gviz_graph;*)
495        close_out oc;
496        gviz#load_graph_from_file ~gviz_cmd:"tred | dot" tmpfile;
497        (match center_on with
498        | None -> ()
499        | Some uri -> gviz#center_on_href (NReference.string_of_reference uri));
500        HExtlib.safe_remove tmpfile
501       else
502        MatitaGtkMisc.report_error ~title:"graphviz error"
503         ~message:("Graphviz is not installed but is necessary to render "^
504          "the graph of dependencies amoung objects. Please install it.")
505         ~parent:win#toplevel ()
506
507     method private dependencies direction uri () =
508       assert false (* MATITA 1.0
509       let dbd = LibraryDb.instance () in
510       let graph =
511         match direction with
512         | `Fwd -> MetadataDeps.DepGraph.direct_deps ~dbd uri
513         | `Back -> MetadataDeps.DepGraph.inverse_deps ~dbd uri in
514       gviz_graph <- graph;  (** XXX check this for memory consuption *)
515       self#redraw_gviz ~center_on:uri ();
516       self#_showGviz *)
517
518     method private coerchgraph tred () =
519       load_coerchgraph tred ();
520       self#_showGviz
521
522     method private hints () =
523       load_hints ();
524       self#_showGviz
525
526     method private tex () =
527       let b = Buffer.create 1000 in
528       Printf.bprintf b "UTF-8 equivalence classes (rotate with ALT-L):\n\n";
529       List.iter 
530         (fun l ->
531            List.iter (fun sym ->
532              Printf.bprintf b "  %s" (Glib.Utf8.from_unichar sym) 
533            ) l;
534            Printf.bprintf b "\n";
535         )
536         (List.sort 
537           (fun l1 l2 -> compare (List.hd l1) (List.hd l2))
538           (Virtuals.get_all_eqclass ()));
539       Printf.bprintf b "\n\nVirtual keys (trigger with ALT-L):\n\n";
540       List.iter 
541         (fun tag, items -> 
542            Printf.bprintf b "  %s:\n" tag;
543            List.iter 
544              (fun names, symbol ->
545                 Printf.bprintf b "  \t%s\t%s\n" 
546                   (Glib.Utf8.from_unichar symbol)
547                   (String.concat ", " names))
548              (List.sort 
549                (fun (_,a) (_,b) -> compare a b)
550                items);
551            Printf.bprintf b "\n")
552         (List.sort 
553           (fun (a,_) (b,_) -> compare a b)
554           (Virtuals.get_all_virtuals ()));
555       self#_loadText (Buffer.contents b)
556
557     method private _loadText text =
558       searchText#source_buffer#set_text text;
559       win#entrySearch#misc#grab_focus ();
560       self#_showSearch
561
562     method private grammar () =
563       self#_loadText
564        (Print_grammar.ebnf_of_term (get_matita_script_current ())#status);
565
566     method private home () =
567       self#_showMath;
568       let status = (get_matita_script_current ())#status in
569        match status#ng_mode with
570           `ProofMode -> self#_loadNObj status status#obj
571         | _ -> self#blank ()
572
573     method private _loadNReference (NReference.Ref (uri,_)) =
574       let status = (get_matita_script_current ())#status in
575       let obj = NCicEnvironment.get_checked_obj status uri in
576       self#_loadNObj status obj
577
578     method private _loadDir dir = 
579       let content = Http_getter.ls ~local:false dir in
580       let l =
581         List.fast_sort
582           Pervasives.compare
583           (List.map
584             (function 
585               | Http_getter_types.Ls_section s -> "dir", s
586               | Http_getter_types.Ls_object o -> "obj", o.Http_getter_types.uri)
587             content)
588       in
589       lastDir <- dir;
590       self#_loadList l
591
592     method private setEntry entry =
593       win#browserUri#set_text (MatitaTypes.string_of_entry entry);
594       current_entry <- entry
595
596     method private _loadNObj status obj =
597       (* showMath must be done _before_ loading the document, since if the
598        * widget is not mapped (hidden by the notebook) the document is not
599        * rendered *)
600       self#_showMath;
601       mathView#load_nobject status obj
602
603     method private _loadTermNCic term m s c =
604       let d = 0 in
605       let m = (0,([],c,term))::m in
606       let status = (get_matita_script_current ())#status in
607       mathView#nload_sequent status m s d;
608       self#_showMath
609
610     method private _loadList l =
611       model#list_store#clear ();
612       List.iter (fun (tag, s) -> model#easy_append ~tag s) l;
613       self#_showList
614
615     (** { public methods, all must call _load!! } *)
616       
617     method load entry =
618       handle_error (fun () -> self#_load entry; self#_historyAdd entry)
619
620     (**  this is what the browser does when you enter a string an hit enter *)
621     method loadInput txt =
622       let txt = HExtlib.trim_blanks txt in
623       (* (* ZACK: what the heck? *)
624       let fix_uri txt =
625         UriManager.string_of_uri
626           (UriManager.strip_xpointer (UriManager.uri_of_string txt))
627       in
628       *)
629         let entry =
630           match txt with
631           | txt when is_uri txt ->
632               `NRef (NReference.reference_of_string ((*fix_uri*) txt))
633           | txt when is_dir txt -> `Dir (MatitaMisc.normalize_dir txt)
634           | txt ->
635              (try
636                MatitaTypes.entry_of_string txt
637               with Invalid_argument _ ->
638                raise
639                 (GrafiteTypes.Command_error(sprintf "unsupported uri: %s" txt)))
640         in
641         self#_load entry;
642         self#_historyAdd entry
643
644       (** {2 methods used by constructor only} *)
645
646     method win = win
647     method history = history
648     method currentEntry = current_entry
649     method refresh ~force () = self#_load ~force current_entry
650
651   end
652   
653 let sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) ():
654   MatitaGuiTypes.sequentsViewer
655 =
656   (new sequentsViewer ~notebook ~cicMathView ():> MatitaGuiTypes.sequentsViewer)
657
658 let new_cicBrowser () =
659   let size = BuildTimeConf.browser_history_size in
660   let rec aux history =
661     let browser = new cicBrowser_impl ~history () in
662     let win = browser#win in
663     ignore (win#browserNewButton#connect#clicked (fun () ->
664       let history =
665         new MatitaMisc.browser_history ~memento:history#save size
666           (`About `Blank)
667       in
668       let newBrowser = aux history in
669       newBrowser#load browser#currentEntry));
670 (*
671       (* attempt (failed) to close windows on CTRL-W ... *)
672     MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
673       GdkKeysyms._W (fun () -> win#toplevel#destroy ());
674 *)
675     cicBrowsers := browser :: !cicBrowsers;
676     browser
677   in
678   let history = new MatitaMisc.browser_history size (`About `Blank) in
679   aux history
680
681 (** @param reuse if set reused last opened cic browser otherwise 
682 *  opens a new one. default is false *)
683 let cicBrowser ?(reuse=false) t =
684  let browser =
685   if reuse then
686    (match !cicBrowsers with [] -> new_cicBrowser () | b :: _ -> b)
687   else
688    new_cicBrowser ()
689  in
690   match t with
691      None -> ()
692    | Some t -> browser#load t
693 ;;
694
695 let default_cicMathView () =
696  let res = cicMathView ~show:true () in
697   res#set_href_callback
698     (Some (fun uri ->
699       let uri = `NRef (NReference.reference_of_string uri) in
700        cicBrowser (Some uri)));
701   res
702
703 let cicMathView_instance =
704  MatitaMisc.singleton default_cicMathView
705
706 let default_sequentsViewer notebook =
707   let cicMathView = cicMathView_instance () in
708   sequentsViewer ~notebook ~cicMathView ()
709
710 let sequentsViewer_instance =
711  let already_used = ref false in
712   fun notebook ->
713    if !already_used then assert false
714    else
715     (already_used := true;
716      default_sequentsViewer notebook)
717
718 let refresh_all_browsers () =
719   List.iter (fun b -> b#refresh ~force:false ()) !cicBrowsers
720
721 let get_math_views () =
722   (cicMathView_instance ()) :: (List.map (fun b -> b#mathView) !cicBrowsers)
723
724 let find_selection_owner () =
725   let rec aux =
726     function
727     | [] -> raise Not_found
728     | mv :: tl ->
729         (match mv#get_selections with
730         | [] -> aux tl
731         | sel :: _ -> mv)
732   in
733   aux (get_math_views ())
734
735 let has_selection () =
736   try ignore (find_selection_owner ()); true
737   with Not_found -> false
738
739 let math_view_clipboard = ref None (* associative list target -> string *)
740 let has_clipboard () = !math_view_clipboard <> None
741 let empty_clipboard () = math_view_clipboard := None
742
743 let copy_selection () =
744   try
745     math_view_clipboard :=
746       Some ((find_selection_owner ())#strings_of_selection)
747   with Not_found -> failwith "no selection"
748
749 let paste_clipboard paste_kind =
750   match !math_view_clipboard with
751   | None -> failwith "empty clipboard"
752   | Some cb ->
753       (try List.assoc paste_kind cb with Not_found -> assert false)
754