]> matita.cs.unibo.it Git - helm.git/blob - helm/matita/matitaMathView.ml
better dependencies among modules and symlinking of several matitatools to a single...
[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 open MatitaGtkMisc
30
31 module Stack = Continuationals.Stack
32
33 (** inherit from this class if you want to access current script *)
34 class scriptAccessor =
35 object (self)
36   method private script = MatitaScript.current ()
37 end
38
39 let cicBrowsers = ref []
40 let gui_instance = ref None
41 let set_gui gui = gui_instance := Some gui
42 let get_gui () =
43   match !gui_instance with
44   | None -> assert false
45   | Some gui -> gui
46
47 let default_font_size () =
48   Helm_registry.get_opt_default Helm_registry.int
49     ~default:BuildTimeConf.default_font_size "matita.font_size"
50 let current_font_size = ref ~-1
51 let increase_font_size () = incr current_font_size
52 let decrease_font_size () = decr current_font_size
53 let reset_font_size () = current_font_size := default_font_size ()
54
55   (* is there any lablgtk2 constant corresponding to the various mouse
56    * buttons??? *)
57 let left_button = 1
58 let middle_button = 2
59 let right_button = 3
60
61 let near (x1, y1) (x2, y2) =
62   let distance = sqrt (((x2 -. x1) ** 2.) +. ((y2 -. y1) ** 2.)) in
63   (distance < 4.)
64
65 let xlink_ns = Gdome.domString "http://www.w3.org/1999/xlink"
66 let helm_ns = Gdome.domString "http://www.cs.unibo.it/helm"
67 let href_ds = Gdome.domString "href"
68 let xref_ds = Gdome.domString "xref"
69
70 let domImpl = Gdome.domImplementation ()
71
72   (** Gdome.element of a MathML document whose rendering should be blank. Used
73   * by cicBrowser to render "about:blank" document *)
74 let empty_mathml = lazy (
75   domImpl#createDocument ~namespaceURI:(Some DomMisc.mathml_ns)
76     ~qualifiedName:(Gdome.domString "math") ~doctype:None)
77
78 let empty_boxml = lazy (
79   domImpl#createDocument ~namespaceURI:(Some DomMisc.boxml_ns) 
80     ~qualifiedName:(Gdome.domString "box") ~doctype:None)
81
82   (** shown for goals closed by side effects *)
83 let closed_goal_mathml = lazy (
84   domImpl#createDocumentFromURI ~uri:BuildTimeConf.closed_xml ())
85
86 (* ids_to_terms should not be passed here, is just for debugging *)
87 let find_root_id annobj id ids_to_father_ids ids_to_terms ids_to_inner_types =
88   let find_parent id ids =
89     let rec aux id =
90 (*       (prerr_endline (sprintf "id %s = %s" id
91         (try
92           CicPp.ppterm (Hashtbl.find ids_to_terms id)
93         with Not_found -> "NONE"))); *)
94       if List.mem id ids then Some id
95       else
96         (match
97           (try Hashtbl.find ids_to_father_ids id with Not_found -> None)
98         with
99         | None -> None
100         | Some id' -> aux id')
101     in
102     aux id
103   in
104   let return_father id ids =
105     match find_parent id ids with
106     | None -> assert false
107     | Some parent_id -> parent_id
108   in
109   let mk_ids terms = List.map CicUtil.id_of_annterm terms in
110   let inner_types =
111    Hashtbl.fold
112     (fun _ types acc ->
113       match types.Cic2acic.annexpected with
114          None -> types.Cic2acic.annsynthesized :: acc
115        | Some ty -> ty :: types.Cic2acic.annsynthesized :: acc
116     ) ids_to_inner_types [] in
117   match annobj with
118   | Cic.AConstant (_, _, _, Some bo, ty, _, _)
119   | Cic.AVariable (_, _, Some bo, ty, _, _)
120   | Cic.ACurrentProof (_, _, _, _, bo, ty, _, _) ->
121       return_father id (mk_ids (ty :: bo :: inner_types))
122   | Cic.AConstant (_, _, _, None, ty, _, _)
123   | Cic.AVariable (_, _, None, ty, _, _) ->
124       return_father id (mk_ids (ty::inner_types))
125   | Cic.AInductiveDefinition _ ->
126       assert false  (* TODO *)
127
128   (** @return string content of a dom node having a single text child node, e.g.
129    * <m:mi xlink:href="...">bool</m:mi> *)
130 let string_of_dom_node node =
131   match node#get_firstChild with
132   | None -> ""
133   | Some node ->
134       (try
135         let text = new Gdome.text_of_node node in
136         text#get_data#to_string
137       with GdomeInit.DOMCastException _ -> "")
138
139 class clickableMathView obj =
140 let text_width = 80 in
141 object (self)
142   inherit GMathViewAux.multi_selection_math_view obj
143
144   val mutable href_callback: (string -> unit) option = None
145   method set_href_callback f = href_callback <- f
146
147   val mutable _cic_info = None
148   method private set_cic_info info = _cic_info <- info
149   method private cic_info = _cic_info
150
151   initializer
152     self#set_font_size !current_font_size;
153     ignore (self#connect#selection_changed self#choose_selection_cb);
154     ignore (self#event#connect#button_press self#button_press_cb);
155     ignore (self#event#connect#button_release self#button_release_cb);
156     ignore (self#event#connect#selection_clear self#selection_clear_cb);
157     ignore (self#coerce#misc#connect#selection_get self#selection_get_cb)
158
159   val mutable button_press_x = -1.
160   val mutable button_press_y = -1.
161   val mutable selection_changed = false
162
163   method private selection_get_cb ctxt ~info ~time =
164     (match self#get_selections with
165     | [] -> ()
166     | node :: _ -> ctxt#return (self#string_of_node node))
167
168   method private selection_clear_cb sel_event =
169     self#remove_selections;
170     false
171
172   method private button_press_cb gdk_button =
173     let button = GdkEvent.Button.button gdk_button in
174     if  button = left_button then begin
175       button_press_x <- GdkEvent.Button.x gdk_button;
176       button_press_y <- GdkEvent.Button.y gdk_button;
177       selection_changed <- false
178     end else if button = right_button then
179       self#popup_contextual_menu (GdkEvent.Button.time gdk_button);
180     false
181
182   method private popup_contextual_menu time =
183     match self#string_of_selection with
184     | None -> ()
185     | Some s ->
186         let clipboard = GData.clipboard Gdk.Atom.clipboard in
187         let menu = GMenu.menu () in
188         let copy_menu_item =
189           GMenu.image_menu_item
190             ~label:"_Copy" ~stock:`COPY ~packing:menu#append ()
191         in
192         connect_menu_item copy_menu_item (fun () -> clipboard#set_text s);
193         menu#popup ~button:right_button ~time
194
195   method private button_release_cb gdk_button =
196     let clipboard = GData.clipboard Gdk.Atom.primary in
197     if GdkEvent.Button.button gdk_button = left_button then begin
198       let button_release_x = GdkEvent.Button.x gdk_button in
199       let button_release_y = GdkEvent.Button.y gdk_button in
200       if selection_changed then
201         ()
202       else  (* selection _not_ changed *)
203         if near (button_press_x, button_press_y)
204           (button_release_x, button_release_y)
205         then
206           let x = int_of_float button_press_x in
207           let y = int_of_float button_press_y in
208           (match self#get_element_at x y with
209           | None -> ()
210           | Some elt ->
211               let localName = href_ds in
212               if elt#hasAttributeNS ~namespaceURI:xlink_ns ~localName then
213                 self#invoke_href_callback
214                   (elt#getAttributeNS ~namespaceURI:xlink_ns
215                     ~localName)#to_string
216                   gdk_button
217               else
218                 ignore (self#action_toggle elt));
219     end;
220     false
221
222   method private invoke_href_callback href_value gdk_button =
223     let button = GdkEvent.Button.button gdk_button in
224     if button = left_button then
225       let time = GdkEvent.Button.time gdk_button in
226       match href_callback with
227       | None -> ()
228       | Some f ->
229           (match HExtlib.split href_value with
230           | [ uri ] ->  f uri
231           | uris ->
232               let menu = GMenu.menu () in
233               List.iter
234                 (fun uri ->
235                   let menu_item =
236                     GMenu.menu_item ~label:uri ~packing:menu#append ()
237                   in
238                   connect_menu_item menu_item (fun () -> f uri))
239                 uris;
240               menu#popup ~button ~time)
241
242   method private choose_selection_cb gdome_elt =
243     let (gui: MatitaGuiTypes.gui) = get_gui () in
244     let clipboard = GData.clipboard Gdk.Atom.primary in
245     let set_selection elt =
246       self#set_selection (Some elt);
247       self#coerce#misc#add_selection_target
248         ~target:(Gdk.Atom.name Gdk.Atom.string) Gdk.Atom.primary;
249       ignore (self#coerce#misc#grab_selection Gdk.Atom.primary)
250     in
251     let rec aux elt =
252       if (elt#getAttributeNS ~namespaceURI:helm_ns
253             ~localName:xref_ds)#to_string <> ""
254       then
255         set_selection elt
256       else
257         try
258           (match elt#get_parentNode with
259           | None -> assert false
260           | Some p -> aux (new Gdome.element_of_node p))
261         with GdomeInit.DOMCastException _ -> ()
262     in
263     (match gdome_elt with
264     | Some elt when (elt#getAttributeNS ~namespaceURI:xlink_ns
265         ~localName:href_ds)#to_string <> "" ->
266           set_selection elt
267     | Some elt -> aux elt
268     | None -> self#set_selection None);
269     selection_changed <- true
270
271   method update_font_size = self#set_font_size !current_font_size
272
273   method private get_term_by_id context cic_info id =
274     let ids_to_terms, ids_to_hypotheses, _, _, _ = cic_info in
275     try
276       `Term (Hashtbl.find ids_to_terms id)
277     with Not_found ->
278       try
279         let hyp = Hashtbl.find ids_to_hypotheses id in
280         let context' = MatitaMisc.list_tl_at hyp context in
281         `Hyp context'
282       with Not_found -> assert false
283     
284   method private find_obj_conclusion id =
285     match self#cic_info with
286     | None
287     | Some (_, _, _, _, None) -> assert false
288     | Some (ids_to_terms, _, ids_to_father_ids, ids_to_inner_types, Some annobj) ->
289         let id =
290          find_root_id annobj id ids_to_father_ids ids_to_terms ids_to_inner_types
291         in
292          (try Hashtbl.find ids_to_terms id with Not_found -> assert false)
293
294   method private string_of_node node =
295     if node#hasAttributeNS ~namespaceURI:helm_ns ~localName:xref_ds
296     then self#string_of_id_node node
297     else string_of_dom_node node
298
299   method private string_of_id_node node =
300     let get_id (node: Gdome.element) =
301       let xref_attr =
302         node#getAttributeNS ~namespaceURI:helm_ns ~localName:xref_ds
303       in
304       List.hd (HExtlib.split ~sep:' ' xref_attr#to_string)
305     in
306     let id = get_id node in
307     let script = MatitaScript.current () in
308     let metasenv = script#proofMetasenv in
309     let context = script#proofContext in
310     let metasenv, context, conclusion =
311       if script#onGoingProof () then
312         script#proofMetasenv, script#proofContext, script#proofConclusion
313       else
314         [], [],
315         let t = self#find_obj_conclusion id in
316         MatitaLog.debug (CicPp.ppterm t);
317         t
318     in
319 (* TODO: code for patterns
320     let conclusion = (MatitaScript.instance ())#proofConclusion in
321     let conclusion_pattern =
322       ProofEngineHelpers.pattern_of ~term:conclusion cic_terms
323     in
324 *)
325     let string_of_cic_sequent cic_sequent =
326       let acic_sequent, _, _, ids_to_inner_sorts, _ =
327         Cic2acic.asequent_of_sequent metasenv cic_sequent
328       in
329       let _, _, _, annterm = acic_sequent in
330       let ast, ids_to_uris =
331         CicNotationRew.ast_of_acic ids_to_inner_sorts annterm
332       in
333       let pped_ast = CicNotationRew.pp_ast ast in
334       let markup = CicNotationPres.render ids_to_uris pped_ast in
335       BoxPp.render_to_string text_width markup
336     in
337     let cic_info =
338       match self#cic_info with Some info -> info | None -> assert false
339     in
340     let cic_sequent =
341       match self#get_term_by_id context cic_info id with
342       | `Term t ->
343           let context' =
344             match
345               ProofEngineHelpers.locate_in_conjecture t
346                 (~-1, context, conclusion)
347             with
348               [context,_] -> context
349             | _ -> assert false (* since it uses physical equality *)
350           in
351           ~-1, context', t
352       | `Hyp context -> ~-1, context, Cic.Rel 1
353     in
354     string_of_cic_sequent cic_sequent
355
356   method string_of_selections =
357     List.map self#string_of_node (List.rev self#get_selections)
358
359   method string_of_selection =
360     match self#get_selections with
361     | [] -> None
362     | node :: _ -> Some (self#string_of_node node)
363
364 end
365
366 let clickableMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity =
367   GtkBase.Widget.size_params
368     ~cont:(OgtkMathViewProps.pack_return (fun p ->
369       OgtkMathViewProps.set_params
370         (new clickableMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
371         ~font_size:None ~log_verbosity:None))
372     []
373
374 class cicMathView obj =
375 object (self)
376   inherit clickableMathView obj
377
378   val mutable current_mathml = None
379
380   method load_sequent metasenv metano =
381     let sequent = CicUtil.lookup_meta metano metasenv in
382     let (mathml, (_, (ids_to_terms, ids_to_father_ids, ids_to_hypotheses,_ ))) =
383       ApplyTransformation.mml_of_cic_sequent metasenv sequent
384     in
385     self#set_cic_info
386       (Some (ids_to_terms, ids_to_hypotheses, ids_to_father_ids,
387         Hashtbl.create 1, None));
388     let name = "sequent_viewer.xml" in
389     MatitaLog.debug ("load_sequent: dumping MathML to ./" ^ name);
390     ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ());
391     self#load_root ~root:mathml#get_documentElement
392
393   method load_object obj =
394     let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *)
395     let (mathml,
396       (annobj, (ids_to_terms, ids_to_father_ids, _, ids_to_hypotheses, _, ids_to_inner_types)))
397     =
398       ApplyTransformation.mml_of_cic_object obj
399     in
400     self#set_cic_info
401       (Some (ids_to_terms, ids_to_hypotheses, ids_to_father_ids, ids_to_inner_types, Some annobj));
402     (match current_mathml with
403     | Some current_mathml when use_diff ->
404         self#freeze;
405         XmlDiff.update_dom ~from:current_mathml mathml;
406         self#thaw
407     |  _ ->
408         let name = "cic_browser.xml" in
409         MatitaLog.debug ("cic_browser: dumping MathML to ./" ^ name);
410         ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ());
411         self#load_root ~root:mathml#get_documentElement;
412         current_mathml <- Some mathml);
413 end
414
415 let tab_label meta_markup =
416   let rec aux =
417     function
418     | `Current m -> sprintf "<b>%s</b>" (aux m)
419     | `Closed m -> sprintf "<s>%s</s>" (aux m)
420     | `Shift (pos, m) -> sprintf "|<sub>%d</sub>: %s" pos (aux m)
421     | `Meta n -> sprintf "?%d" n
422   in
423   let markup = aux meta_markup in
424   (GMisc.label ~markup ~show:true ())#coerce
425
426 let goal_of_switch = function Stack.Open g | Stack.Closed g -> g
427
428 class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () =
429   object (self)
430     inherit scriptAccessor
431
432     val mutable pages = 0
433     val mutable switch_page_callback = None
434     val mutable page2goal = []  (* associative list: page no -> goal no *)
435     val mutable goal2page = []  (* the other way round *)
436     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
437     val mutable _metasenv = []
438     val mutable scrolledWin: GBin.scrolled_window option = None
439       (* scrolled window to which the sequentViewer is currently attached *)
440     val logo = (GMisc.image
441       ~file:(MatitaMisc.image_path "matita_medium.png") ()
442       :> GObj.widget)
443             
444     val logo_with_qed = (GMisc.image
445       ~file:(MatitaMisc.image_path "matita_small.png") ()
446       :> GObj.widget)
447
448     method load_logo =
449      notebook#set_show_tabs false;
450      notebook#append_page logo
451
452     method load_logo_with_qed =
453      notebook#set_show_tabs false;
454      notebook#append_page logo_with_qed
455
456     method reset =
457       (match scrolledWin with
458       | Some w ->
459           (* removing page from the notebook will destroy all contained widget,
460           * we do not want the cicMathView to be destroyed as well *)
461           w#remove cicMathView#coerce;
462           scrolledWin <- None
463       | None -> ());
464       (match switch_page_callback with
465       | Some id ->
466           GtkSignal.disconnect notebook#as_widget id;
467           switch_page_callback <- None
468       | None -> ());
469       for i = 0 to pages do notebook#remove_page 0 done; 
470       notebook#set_show_tabs true;
471       pages <- 0;
472       page2goal <- [];
473       goal2page <- [];
474       goal2win <- [];
475       _metasenv <- []; 
476       self#script#setGoal ~-1;
477
478     method load_sequents { proof = (_,metasenv,_,_) as proof; stack = stack } =
479       let sequents_no = List.length metasenv in
480       _metasenv <- metasenv;
481       pages <- 0;
482       let win goal_switch =
483         let w =
484           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`ALWAYS
485             ~shadow_type:`IN ~show:true ()
486         in
487         let reparent () =
488           scrolledWin <- Some w;
489           match cicMathView#misc#parent with
490           | None -> w#add cicMathView#coerce
491           | Some parent ->
492              let parent =
493               match cicMathView#misc#parent with
494                  None -> assert false
495                | Some p -> GContainer.cast_container p
496              in
497               parent#remove cicMathView#coerce;
498               w#add cicMathView#coerce
499         in
500         goal2win <- (goal_switch, reparent) :: goal2win;
501         w#coerce
502       in
503       assert (
504         let stack_goals = Stack.open_goals stack in
505         let proof_goals = ProofEngineTypes.goals_of_proof proof in
506         if
507           HExtlib.list_uniq (List.sort Pervasives.compare stack_goals)
508           <> List.sort Pervasives.compare proof_goals
509         then begin
510           prerr_endline ("STACK GOALS = " ^ String.concat " " (List.map string_of_int stack_goals));
511           prerr_endline ("PROOF GOALS = " ^ String.concat " " (List.map string_of_int proof_goals));
512           false
513         end
514         else true
515       );
516       let render_switch =
517         function Stack.Open i ->`Meta i | Stack.Closed i ->`Closed (`Meta i)
518       in
519       let page = ref 0 in
520       let added_goals = ref [] in
521         (* goals can be duplicated on the tack due to focus, but we should avoid
522          * multiple labels in the user interface *)
523       let add_tab markup goal_switch =
524         let goal = Stack.goal_of_switch goal_switch in
525         if not (List.mem goal !added_goals) then begin
526           notebook#append_page ~tab_label:(tab_label markup) (win goal_switch);
527           page2goal <- (!page, goal_switch) :: page2goal;
528           goal2page <- (goal_switch, !page) :: goal2page;
529           incr page;
530           pages <- pages + 1;
531           added_goals := goal :: !added_goals
532         end
533       in
534       let add_switch _ _ (_, sw) = add_tab (render_switch sw) sw in
535       Stack.iter  (** populate notebook with tabs *)
536         ~env:(fun depth tag (pos, sw) ->
537           let markup =
538             match depth, pos with
539             | 0, _ -> `Current (render_switch sw)
540             | 1, pos when Stack.head_tag stack = `BranchTag ->
541                 `Shift (pos, render_switch sw)
542             | _ -> render_switch sw
543           in
544           add_tab markup sw)
545         ~cont:add_switch ~todo:add_switch
546         stack;
547       switch_page_callback <-
548         Some (notebook#connect#switch_page ~callback:(fun page ->
549           let goal_switch =
550             try List.assoc page page2goal with Not_found -> assert false
551           in
552           self#script#setGoal (goal_of_switch goal_switch);
553           self#render_page ~page ~goal_switch))
554
555     method private render_page ~page ~goal_switch =
556       (match goal_switch with
557       | Stack.Open goal -> cicMathView#load_sequent _metasenv goal
558       | Stack.Closed goal ->
559           let doc = Lazy.force closed_goal_mathml in
560           cicMathView#load_root ~root:doc#get_documentElement);
561       (try
562         cicMathView#set_selection None;
563         List.assoc goal_switch goal2win ()
564       with Not_found -> assert false)
565
566     method goto_sequent goal =
567       let goal_switch, page =
568         try
569           List.find
570             (function Stack.Open g, _ | Stack.Closed g, _ -> g = goal)
571             goal2page
572         with Not_found -> assert false
573       in
574       notebook#goto_page page;
575       self#render_page page goal_switch
576
577   end
578
579  (** constructors *)
580
581 type 'widget constructor =
582   ?hadjustment:GData.adjustment ->
583   ?vadjustment:GData.adjustment ->
584   ?font_size:int ->
585   ?log_verbosity:int ->
586   ?width:int ->
587   ?height:int ->
588   ?packing:(GObj.widget -> unit) ->
589   ?show:bool ->
590   unit ->
591     'widget
592
593 let cicMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity =
594   GtkBase.Widget.size_params
595     ~cont:(OgtkMathViewProps.pack_return (fun p ->
596       OgtkMathViewProps.set_params
597         (new cicMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
598         ~font_size ~log_verbosity))
599     []
600
601 let blank_uri = BuildTimeConf.blank_uri
602 let current_proof_uri = BuildTimeConf.current_proof_uri
603
604 type term_source =
605   [ `Ast of DisambiguateTypes.term
606   | `Cic of Cic.term * Cic.metasenv
607   | `String of string
608   ]
609
610 class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history)
611   ()
612 =
613   let term_RE = Pcre.regexp "^term:(.*)" in
614   let whelp_RE = Pcre.regexp "^\\s*whelp" in
615   let uri_RE =
616     Pcre.regexp
617       "^cic:/([^/]+/)*[^/]+\\.(con|ind|var)(#xpointer\\(\\d+(/\\d+)+\\))?$"
618   in
619   let dir_RE = Pcre.regexp "^cic:((/([^/]+/)*[^/]+(/)?)|/|)$" in
620   let whelp_query_RE = Pcre.regexp "^\\s*whelp\\s+([^\\s]+)\\s+(.*)$" in
621   let trailing_slash_RE = Pcre.regexp "/$" in
622   let has_xpointer_RE = Pcre.regexp "#xpointer\\(\\d+/\\d+(/\\d+)?\\)$" in
623   let is_whelp txt = Pcre.pmatch ~rex:whelp_RE txt in
624   let is_uri txt = Pcre.pmatch ~rex:uri_RE txt in
625   let is_dir txt = Pcre.pmatch ~rex:dir_RE txt in
626   let gui = get_gui () in
627   let (win: MatitaGuiTypes.browserWin) = gui#newBrowserWin () in
628   let queries = ["Locate";"Hint";"Match";"Elim";"Instance"] in
629   let combo,_ = GEdit.combo_box_text ~strings:queries () in
630   let activate_combo_query input q =
631     let q' = String.lowercase q in
632     let rec aux i = function
633       | [] -> failwith ("Whelp query '" ^ q ^ "' not found")
634       | h::_ when String.lowercase h = q' -> i
635       | _::tl -> aux (i+1) tl
636     in
637     combo#set_active (aux 0 queries);
638     win#queryInputText#set_text input
639   in
640   let set_whelp_query txt =
641     let query, arg = 
642       try
643         let q = Pcre.extract ~rex:whelp_query_RE txt in
644         q.(1), q.(2)
645       with Invalid_argument _ -> failwith "Malformed Whelp query"
646     in
647     activate_combo_query arg query
648   in
649   let toplevel = win#toplevel in
650   let mathView = cicMathView ~packing:win#scrolledBrowser#add () in
651   let fail message = 
652     MatitaGtkMisc.report_error ~title:"Cic browser" ~message 
653       ~parent:toplevel ()  
654   in
655   let tags =
656     [ "dir", GdkPixbuf.from_file (MatitaMisc.image_path "matita-folder.png");
657       "obj", GdkPixbuf.from_file (MatitaMisc.image_path "matita-object.png") ]
658   in
659   let handle_error f =
660     try
661       f ()
662     with exn ->
663       if not (Helm_registry.get_bool "matita.debug") then
664         fail (MatitaExcPp.to_string exn)
665       else raise exn
666   in
667   let handle_error' f = (fun () -> handle_error (fun () -> f ())) in
668   let load_easter_egg = lazy (
669     win#easterEggImage#set_file (MatitaMisc.image_path "meegg.png"))
670   in
671   object (self)
672     inherit scriptAccessor
673     
674     (* Whelp bar queries *)
675
676     initializer
677       activate_combo_query "" "locate";
678       win#whelpBarComboVbox#add combo#coerce;
679       let start_query () = 
680         let query = String.lowercase (List.nth queries combo#active) in
681         let input = win#queryInputText#text in
682         let statement = "whelp " ^ query ^ " " ^ input ^ "." in
683         (MatitaScript.current ())#advance ~statement ()
684       in
685       ignore(win#queryInputText#connect#activate ~callback:start_query);
686       ignore(combo#connect#changed ~callback:start_query);
687       win#whelpBarImage#set_file (MatitaMisc.image_path "whelp.png");
688       win#mathOrListNotebook#set_show_tabs false;
689       win#browserForwardButton#misc#set_sensitive false;
690       win#browserBackButton#misc#set_sensitive false;
691       ignore (win#browserUri#entry#connect#activate (handle_error' (fun () ->
692         self#loadInput win#browserUri#entry#text)));
693       ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
694         self#load (`About `Current_proof))));
695       ignore (win#browserRefreshButton#connect#clicked
696         (handle_error' (self#refresh ~force:true)));
697       ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
698       ignore (win#browserForwardButton#connect#clicked
699         (handle_error' self#forward));
700       ignore (win#toplevel#event#connect#delete (fun _ ->
701         let my_id = Oo.id self in
702         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
703         if !cicBrowsers = [] &&
704           Helm_registry.get "matita.mode" = "cicbrowser"
705         then
706           GMain.quit ();
707         false));
708       ignore(win#whelpResultTreeview#connect#row_activated 
709         ~callback:(fun _ _ ->
710           handle_error (fun () -> self#loadInput (self#_getSelectedUri ()))));
711       mathView#set_href_callback (Some (fun uri ->
712         handle_error (fun () ->
713           self#load (`Uri (UriManager.uri_of_string uri)))));
714       self#_load (`About `Blank);
715       toplevel#show ()
716
717     val mutable current_entry = `About `Blank 
718
719     val model =
720       new MatitaGtkMisc.taggedStringListModel tags win#whelpResultTreeview
721
722     val mutable lastDir = ""  (* last loaded "directory" *)
723
724     method mathView = (mathView :> MatitaGuiTypes.clickableMathView)
725
726     method private _getSelectedUri () =
727       match model#easy_selection () with
728       | [sel] when is_uri sel -> sel  (* absolute URI selected *)
729 (*       | [sel] -> win#browserUri#entry#text ^ sel  |+ relative URI selected +| *)
730       | [sel] -> lastDir ^ sel
731       | _ -> assert false
732
733     (** history RATIONALE 
734      *
735      * All operations about history are done using _historyFoo.
736      * Only toplevel functions (ATM load and loadInput) call _historyAdd.
737      *)
738           
739     method private _historyAdd item = 
740       history#add item;
741       win#browserBackButton#misc#set_sensitive true;
742       win#browserForwardButton#misc#set_sensitive false
743
744     method private _historyPrev () =
745       let item = history#previous in
746       if history#is_begin then win#browserBackButton#misc#set_sensitive false;
747       win#browserForwardButton#misc#set_sensitive true;
748       item
749     
750     method private _historyNext () =
751       let item = history#next in
752       if history#is_end then win#browserForwardButton#misc#set_sensitive false;
753       win#browserBackButton#misc#set_sensitive true;
754       item
755
756     (** notebook RATIONALE 
757      * 
758      * Use only these functions to switch between the tabs
759      *)
760     method private _showMath = win#mathOrListNotebook#goto_page 0
761     method private _showList = win#mathOrListNotebook#goto_page 1
762
763     method private back () =
764       try
765         self#_load (self#_historyPrev ())
766       with MatitaMisc.History_failure -> ()
767
768     method private forward () =
769       try
770         self#_load (self#_historyNext ())
771       with MatitaMisc.History_failure -> ()
772
773       (* loads a uri which can be a cic uri or an about:* uri
774       * @param uri string *)
775     method private _load ?(force=false) entry =
776       handle_error (fun () ->
777        if entry <> current_entry || entry = `About `Current_proof || force then
778         begin
779           (match entry with
780           | `About `Current_proof -> self#home ()
781           | `About `Blank -> self#blank ()
782           | `About `Us -> self#egg ()
783           | `Check term -> self#_loadCheck term
784           | `Cic (term, metasenv) -> self#_loadTermCic term metasenv
785           | `Dir dir -> self#_loadDir dir
786           | `Uri uri -> self#_loadUriManagerUri uri
787           | `Whelp (query, results) -> 
788               set_whelp_query query;
789               self#_loadList (List.map (fun r -> "obj",
790                 UriManager.string_of_uri r) results));
791           self#setEntry entry
792         end)
793
794     method private blank () =
795       self#_showMath;
796       mathView#load_root (Lazy.force empty_mathml)#get_documentElement
797
798     method private _loadCheck term =
799       failwith "not implemented _loadCheck";
800       self#_showMath
801
802     method private egg () =
803       win#mathOrListNotebook#goto_page 2;
804       Lazy.force load_easter_egg
805
806     method private home () =
807       self#_showMath;
808       match self#script#status.proof_status with
809       | Proof  (uri, metasenv, bo, ty) ->
810           let name = UriManager.name_of_uri (HExtlib.unopt uri) in
811           let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
812           self#_loadObj obj
813       | Incomplete_proof { proof = (uri, metasenv, bo, ty) } ->
814           let name = UriManager.name_of_uri (HExtlib.unopt uri) in
815           let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
816           self#_loadObj obj
817       | _ -> self#blank ()
818
819       (** loads a cic uri from the environment
820       * @param uri UriManager.uri *)
821     method private _loadUriManagerUri uri =
822       let uri = UriManager.strip_xpointer uri in
823       let (obj, _) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
824       self#_loadObj obj
825       
826     method private _loadDir dir = 
827       let content = Http_getter.ls dir in
828       let l =
829         List.fast_sort
830           Pervasives.compare
831           (List.map
832             (function 
833               | Http_getter_types.Ls_section s -> "dir", s
834               | Http_getter_types.Ls_object o -> "obj", o.Http_getter_types.uri)
835             content)
836       in
837       lastDir <- dir;
838       self#_loadList l
839
840     method private setEntry entry =
841       win#browserUri#entry#set_text (string_of_entry entry);
842       current_entry <- entry
843
844     method private _loadObj obj =
845       (* showMath must be done _before_ loading the document, since if the
846        * widget is not mapped (hidden by the notebook) the document is not
847        * rendered *)
848       self#_showMath;
849       mathView#load_object obj
850
851     method private _loadTermCic term metasenv =
852       let context = self#script#proofContext in
853       let dummyno = CicMkImplicit.new_meta metasenv [] in
854       let sequent = (dummyno, context, term) in
855       mathView#load_sequent (sequent :: metasenv) dummyno;
856       self#_showMath
857
858     method private _loadList l =
859       model#list_store#clear ();
860       List.iter (fun (tag, s) -> model#easy_append ~tag s) l;
861       self#_showList
862     
863     (** { public methods, all must call _load!! } *)
864       
865     method load entry =
866       handle_error (fun () -> self#_load entry; self#_historyAdd entry)
867
868     (**  this is what the browser does when you enter a string an hit enter *)
869     method loadInput txt =
870       let txt = HExtlib.trim_blanks txt in
871       let fix_uri txt =
872         UriManager.string_of_uri
873           (UriManager.strip_xpointer (UriManager.uri_of_string txt))
874       in
875       if is_whelp txt then begin
876         set_whelp_query txt;  
877         (MatitaScript.current ())#advance ~statement:(txt ^ ".") ()
878       end else begin
879         let entry =
880           match txt with
881           | txt when is_uri txt -> `Uri (UriManager.uri_of_string (fix_uri txt))
882           | txt when is_dir txt -> `Dir (MatitaMisc.normalize_dir txt)
883           | txt ->
884               (try
885                 entry_of_string txt
886               with Invalid_argument _ ->
887                 command_error (sprintf "unsupported uri: %s" txt))
888         in
889         self#_load entry;
890         self#_historyAdd entry
891       end
892
893       (** {2 methods accessing underlying GtkMathView} *)
894
895     method updateFontSize = mathView#set_font_size !current_font_size
896
897       (** {2 methods used by constructor only} *)
898
899     method win = win
900     method history = history
901     method currentEntry = current_entry
902     method refresh ~force () = self#_load ~force current_entry
903
904   end
905   
906 let sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) ():
907   MatitaGuiTypes.sequentsViewer
908 =
909   new sequentsViewer ~notebook ~cicMathView ()
910
911 let cicBrowser () =
912   let size = BuildTimeConf.browser_history_size in
913   let rec aux history =
914     let browser = new cicBrowser_impl ~history () in
915     let win = browser#win in
916     ignore (win#browserNewButton#connect#clicked (fun () ->
917       let history =
918         new MatitaMisc.browser_history ~memento:history#save size
919           (`About `Blank)
920       in
921       let newBrowser = aux history in
922       newBrowser#load browser#currentEntry));
923 (*
924       (* attempt (failed) to close windows on CTRL-W ... *)
925     MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
926       GdkKeysyms._W (fun () -> win#toplevel#destroy ());
927 *)
928     cicBrowsers := browser :: !cicBrowsers;
929     (browser :> MatitaGuiTypes.cicBrowser)
930   in
931   let history = new MatitaMisc.browser_history size (`About `Blank) in
932   aux history
933
934 let default_cicMathView () = cicMathView ~show:true ()
935 let cicMathView_instance = MatitaMisc.singleton default_cicMathView
936
937 let default_sequentsViewer () =
938   let gui = get_gui () in
939   let cicMathView = cicMathView_instance () in
940   sequentsViewer ~notebook:gui#main#sequentsNotebook ~cicMathView ()
941 let sequentsViewer_instance = MatitaMisc.singleton default_sequentsViewer
942
943 let mathViewer () = 
944   object(self)
945     method private get_browser reuse = 
946       if reuse then
947         (match !cicBrowsers with
948         | [] -> cicBrowser ()
949         | b :: _ -> (b :> MatitaGuiTypes.cicBrowser))
950       else
951         (cicBrowser ())
952           
953     method show_entry ?(reuse=false) t = (self#get_browser reuse)#load t
954       
955     method show_uri_list ?(reuse=false) ~entry l =
956       (self#get_browser reuse)#load entry
957   end
958
959 let refresh_all_browsers () =
960  List.iter (fun b -> b#refresh ~force:false ()) !cicBrowsers
961
962 let update_font_sizes () =
963   List.iter (fun b -> b#updateFontSize) !cicBrowsers;
964   (cicMathView_instance ())#update_font_size
965
966 let get_math_views () =
967   ((cicMathView_instance ()) :> MatitaGuiTypes.clickableMathView)
968   :: (List.map (fun b -> b#mathView) !cicBrowsers)
969
970 let get_selections () =
971   if (MatitaScript.current ())#onGoingProof () then
972     let rec aux =
973       function
974       | [] -> None
975       | mv :: tl ->
976           (match mv#string_of_selections with
977           | [] -> aux tl
978           | sels -> Some sels)
979     in
980     aux (get_math_views ())
981   else
982     None
983
984 let reset_selections () =
985   List.iter (fun mv -> mv#remove_selections) (get_math_views ())
986