]> matita.cs.unibo.it Git - helm.git/blob - helm/software/matita/matitaMathView.ml
a6aa89e8190cb62a2a0414241d113d21bbdecf5b
[helm.git] / helm / software / 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
34 module Stack = Continuationals.Stack
35
36 (** inherit from this class if you want to access current script *)
37 class scriptAccessor =
38 object (self)
39   method private script = MatitaScript.current ()
40 end
41
42 let cicBrowsers = ref []
43 let gui_instance = ref None
44 let set_gui gui = gui_instance := Some gui
45 let get_gui () =
46   match !gui_instance with
47   | None -> assert false
48   | Some gui -> gui
49
50 let default_font_size () =
51   Helm_registry.get_opt_default Helm_registry.int
52     ~default:BuildTimeConf.default_font_size "matita.font_size"
53 let current_font_size = ref ~-1
54 let increase_font_size () = incr current_font_size
55 let decrease_font_size () = decr current_font_size
56 let reset_font_size () = current_font_size := default_font_size ()
57
58   (* is there any lablgtk2 constant corresponding to the various mouse
59    * buttons??? *)
60 let left_button = 1
61 let middle_button = 2
62 let right_button = 3
63
64 let near (x1, y1) (x2, y2) =
65   let distance = sqrt (((x2 -. x1) ** 2.) +. ((y2 -. y1) ** 2.)) in
66   (distance < 4.)
67
68 let mathml_ns = Gdome.domString "http://www.w3.org/1998/Math/MathML"
69 let xlink_ns = Gdome.domString "http://www.w3.org/1999/xlink"
70 let helm_ns = Gdome.domString "http://www.cs.unibo.it/helm"
71 let href_ds = Gdome.domString "href"
72 let maction_ds = Gdome.domString "maction"
73 let xref_ds = Gdome.domString "xref"
74
75 let domImpl = Gdome.domImplementation ()
76
77   (** Gdome.element of a MathML document whose rendering should be blank. Used
78   * by cicBrowser to render "about:blank" document *)
79 let empty_mathml = lazy (
80   domImpl#createDocument ~namespaceURI:(Some DomMisc.mathml_ns)
81     ~qualifiedName:(Gdome.domString "math") ~doctype:None)
82
83 let empty_boxml = lazy (
84   domImpl#createDocument ~namespaceURI:(Some DomMisc.boxml_ns) 
85     ~qualifiedName:(Gdome.domString "box") ~doctype:None)
86
87   (** shown for goals closed by side effects *)
88 let closed_goal_mathml = lazy (
89   domImpl#createDocumentFromURI ~uri:BuildTimeConf.closed_xml ())
90
91 (* ids_to_terms should not be passed here, is just for debugging *)
92 let find_root_id annobj id ids_to_father_ids ids_to_terms ids_to_inner_types =
93   let find_parent id ids =
94     let rec aux id =
95 (*       (prerr_endline (sprintf "id %s = %s" id
96         (try
97           CicPp.ppterm (Hashtbl.find ids_to_terms id)
98         with Not_found -> "NONE"))); *)
99       if List.mem id ids then Some id
100       else
101         (match
102           (try Hashtbl.find ids_to_father_ids id with Not_found -> None)
103         with
104         | None -> None
105         | Some id' -> aux id')
106     in
107     aux id
108   in
109   let return_father id ids =
110     match find_parent id ids with
111     | None -> assert false
112     | Some parent_id -> parent_id
113   in
114   let mk_ids terms = List.map CicUtil.id_of_annterm terms in
115   let inner_types =
116    Hashtbl.fold
117     (fun _ types acc ->
118       match types.Cic2acic.annexpected with
119          None -> types.Cic2acic.annsynthesized :: acc
120        | Some ty -> ty :: types.Cic2acic.annsynthesized :: acc
121     ) ids_to_inner_types [] in
122   match annobj with
123   | Cic.AConstant (_, _, _, Some bo, ty, _, _)
124   | Cic.AVariable (_, _, Some bo, ty, _, _)
125   | Cic.ACurrentProof (_, _, _, _, bo, ty, _, _) ->
126       return_father id (mk_ids (ty :: bo :: inner_types))
127   | Cic.AConstant (_, _, _, None, ty, _, _)
128   | Cic.AVariable (_, _, None, ty, _, _) ->
129       return_father id (mk_ids (ty::inner_types))
130   | Cic.AInductiveDefinition _ ->
131       assert false  (* TODO *)
132
133   (** @return string content of a dom node having a single text child node, e.g.
134    * <m:mi xlink:href="...">bool</m:mi> *)
135 let string_of_dom_node node =
136   match node#get_firstChild with
137   | None -> ""
138   | Some node ->
139       (try
140         let text = new Gdome.text_of_node node in
141         text#get_data#to_string
142       with GdomeInit.DOMCastException _ -> "")
143
144 let name_of_hypothesis = function
145   | Some (Cic.Name s, _) -> s
146   | _ -> assert false
147
148 let id_of_node (node: Gdome.element) =
149   let xref_attr =
150     node#getAttributeNS ~namespaceURI:helm_ns ~localName:xref_ds in
151   try
152     List.hd (HExtlib.split ~sep:' ' xref_attr#to_string)
153   with Failure _ -> assert false
154
155 type selected_term =
156   | SelTerm of Cic.term * string option (* term, parent hypothesis (if any) *)
157   | SelHyp of string * Cic.context (* hypothesis, context *)
158
159 let hrefs_of_elt elt =
160   let localName = href_ds in
161   if elt#hasAttributeNS ~namespaceURI:xlink_ns ~localName then
162     let text =
163       (elt#getAttributeNS ~namespaceURI:xlink_ns ~localName)#to_string in
164     Some (HExtlib.split text)
165   else
166     None
167
168 let rec has_maction (elt :Gdome.element) = 
169   (* fix this comparison *)
170   if elt#get_tagName#to_string = "m:maction" ||
171    elt#get_tagName#to_string = "b:action" then
172     true
173   else 
174     match elt#get_parentNode with
175     | Some node when node#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE -> 
176         has_maction (new Gdome.element_of_node node)
177     | _ -> false
178 ;;
179
180 class clickableMathView obj =
181 let text_width = 80 in
182 object (self)
183   inherit GMathViewAux.multi_selection_math_view obj
184
185   val mutable href_callback: (string -> unit) option = None
186   method set_href_callback f = href_callback <- f
187
188   val mutable _cic_info = None
189   val mutable _ncic_info = None
190   method private set_cic_info info = _cic_info <- info
191   method private cic_info = _cic_info
192   method private set_ncic_info info = _ncic_info <- info
193   method private ncic_info = _ncic_info
194
195   val normal_cursor = Gdk.Cursor.create `LEFT_PTR
196   val href_cursor = Gdk.Cursor.create `HAND2
197   val maction_cursor = Gdk.Cursor.create `QUESTION_ARROW
198
199   initializer
200     self#set_font_size !current_font_size;
201     ignore (self#connect#selection_changed self#choose_selection_cb);
202     ignore (self#event#connect#button_press self#button_press_cb);
203     ignore (self#event#connect#button_release self#button_release_cb);
204     ignore (self#event#connect#selection_clear self#selection_clear_cb);
205     ignore (self#connect#element_over self#element_over_cb);
206     ignore (self#coerce#misc#connect#selection_get self#selection_get_cb)
207
208   val mutable button_press_x = -1.
209   val mutable button_press_y = -1.
210   val mutable selection_changed = false
211   val mutable href_statusbar_msg:
212     (GMisc.statusbar_context * Gtk.statusbar_message) option = None
213     (* <statusbar ctxt, statusbar msg> *)
214
215   method private selection_get_cb ctxt ~info ~time =
216     let text =
217       match ctxt#target with
218       | "PATTERN" -> self#text_of_selection `Pattern
219       | "TERM" | _ -> self#text_of_selection `Term
220     in
221     match text with
222     | None -> ()
223     | Some s -> ctxt#return s
224
225   method private text_of_selection fmt =
226     match self#get_selections with
227     | [] -> None
228     | node :: _ -> Some (self#string_of_node ~paste_kind:fmt node)
229
230   method private selection_clear_cb sel_event =
231     self#remove_selections;
232     (GData.clipboard Gdk.Atom.clipboard)#clear ();
233     false
234
235   method private button_press_cb gdk_button =
236     let button = GdkEvent.Button.button gdk_button in
237     if  button = left_button then begin
238       button_press_x <- GdkEvent.Button.x gdk_button;
239       button_press_y <- GdkEvent.Button.y gdk_button;
240       selection_changed <- false
241     end else if button = right_button then
242       self#popup_contextual_menu 
243         (self#get_element_at 
244           (int_of_float (GdkEvent.Button.x gdk_button)) 
245           (int_of_float (GdkEvent.Button.y gdk_button)))  
246         (GdkEvent.Button.time gdk_button);
247     false
248
249   method private element_over_cb (elt_opt, _, _, _) =
250     let win () = self#misc#window in
251     let leave_href () =
252       Gdk.Window.set_cursor (win ()) normal_cursor;
253       HExtlib.iter_option (fun (ctxt, msg) -> ctxt#remove msg)
254         href_statusbar_msg
255     in
256     match elt_opt with
257     | Some elt ->
258         if has_maction elt then
259           Gdk.Window.set_cursor (win ()) maction_cursor
260         else
261         (match hrefs_of_elt elt with
262         | Some ((_ :: _) as hrefs) ->
263             Gdk.Window.set_cursor (win ()) href_cursor;
264             let msg_text = (* now create statusbar msg and store it *)
265               match hrefs with
266               | [ href ] -> sprintf "Hyperlink to %s" href
267               | _ -> sprintf "Hyperlinks to: %s" (String.concat ", " hrefs) in
268             let ctxt = (get_gui ())#main#statusBar#new_context ~name:"href" in
269             let msg = ctxt#push msg_text in
270             href_statusbar_msg <- Some (ctxt, msg)
271         | _ -> leave_href ())
272     | None -> leave_href ()
273
274   method private tactic_text_pattern_of_node node =
275    let id = id_of_node node in
276    let cic_info, unsh_sequent = self#get_cic_info id in
277    match self#get_term_by_id cic_info id with
278    | SelTerm (t, father_hyp) ->
279        let sequent = self#sequent_of_id ~paste_kind:`Pattern id in
280        let text = self#string_of_cic_sequent ~output_type:`Pattern sequent in
281        (match father_hyp with
282        | None -> None, [], Some text
283        | Some hyp_name -> None, [ hyp_name, text ], None)
284    | SelHyp (hyp_name, _ctxt) -> None, [ hyp_name, "%" ], None
285
286   method private tactic_text_of_node node =
287    let id = id_of_node node in
288    let cic_info, unsh_sequent = self#get_cic_info id in
289    match self#get_term_by_id cic_info id with
290    | SelTerm (t, father_hyp) ->
291        let sequent = self#sequent_of_id ~paste_kind:`Term id in
292        let text = self#string_of_cic_sequent ~output_type:`Term sequent in
293        text
294    | SelHyp (hyp_name, _ctxt) -> hyp_name
295
296     (** @return a pattern structure which contains pretty printed terms *)
297   method private tactic_text_pattern_of_selection =
298     match self#get_selections with
299     | [] -> assert false (* this method is invoked only if there's a sel. *)
300     | node :: _ -> self#tactic_text_pattern_of_node node
301
302   method private popup_contextual_menu element time =
303     let menu = GMenu.menu () in
304     let add_menu_item ?(menu = menu) ?stock ?label () =
305       GMenu.image_menu_item ?stock ?label ~packing:menu#append () in
306     let check = add_menu_item ~label:"Check" () in
307     let reductions_menu_item = GMenu.menu_item ~label:"βδιζ-reduce" () in
308     let tactics_menu_item = GMenu.menu_item ~label:"Apply tactic" () in
309     let hyperlinks_menu_item = GMenu.menu_item ~label:"Hyperlinks" () in
310     menu#append reductions_menu_item;
311     menu#append tactics_menu_item;
312     menu#append hyperlinks_menu_item;
313     let reductions = GMenu.menu () in
314     let tactics = GMenu.menu () in
315     let hyperlinks = GMenu.menu () in
316     reductions_menu_item#set_submenu reductions;
317     tactics_menu_item#set_submenu tactics;
318     hyperlinks_menu_item#set_submenu hyperlinks;
319     let normalize = add_menu_item ~menu:reductions ~label:"Normalize" () in
320     let simplify = add_menu_item ~menu:reductions ~label:"Simplify" () in
321     let whd = add_menu_item ~menu:reductions ~label:"Weak head" () in
322     (match element with 
323     | None -> hyperlinks_menu_item#misc#set_sensitive false
324     | Some elt -> 
325         match hrefs_of_elt elt, href_callback with
326         | Some l, Some f ->
327             List.iter 
328               (fun h ->
329                 let item = add_menu_item ~menu:hyperlinks ~label:h () in
330                 connect_menu_item item (fun () -> f h)) l
331         | _ -> hyperlinks_menu_item#misc#set_sensitive false);
332     menu#append (GMenu.separator_item ());
333     let copy = add_menu_item ~stock:`COPY () in
334     let gui = get_gui () in
335     List.iter (fun item -> item#misc#set_sensitive gui#canCopy)
336       [ copy; check; normalize; simplify; whd ];
337     let reduction_action kind () =
338       let pat = self#tactic_text_pattern_of_selection in
339       let statement =
340         let loc = HExtlib.dummy_floc in
341         "\n" ^
342         GrafiteAstPp.pp_executable ~term_pp:(fun s -> s)
343           ~lazy_term_pp:(fun _ -> assert false) ~obj_pp:(fun _ -> assert false)
344           ~map_unicode_to_tex:(Helm_registry.get_bool
345             "matita.paste_unicode_as_tex")
346           (GrafiteAst.Tactic (loc,
347             Some (GrafiteAst.Reduce (loc, kind, pat)),
348             GrafiteAst.Semicolon loc)) in
349       (MatitaScript.current ())#advance ~statement () in
350     connect_menu_item copy gui#copy;
351     connect_menu_item normalize (reduction_action `Normalize);
352     connect_menu_item simplify (reduction_action `Simpl);
353     connect_menu_item whd (reduction_action `Whd);
354     menu#popup ~button:right_button ~time
355
356   method private button_release_cb gdk_button =
357     if GdkEvent.Button.button gdk_button = left_button then begin
358       let button_release_x = GdkEvent.Button.x gdk_button in
359       let button_release_y = GdkEvent.Button.y gdk_button in
360       if selection_changed then
361         ()
362       else  (* selection _not_ changed *)
363         if near (button_press_x, button_press_y)
364           (button_release_x, button_release_y)
365         then
366           let x = int_of_float button_press_x in
367           let y = int_of_float button_press_y in
368           (match self#get_element_at x y with
369           | None -> ()
370           | Some elt ->
371               if has_maction elt then ignore(self#action_toggle elt) else
372               (match hrefs_of_elt elt with
373               | Some hrefs -> self#invoke_href_callback hrefs gdk_button
374               | None -> ()))
375     end;
376     false
377
378   method private invoke_href_callback hrefs gdk_button =
379     let button = GdkEvent.Button.button gdk_button in
380     if button = left_button then
381       let time = GdkEvent.Button.time gdk_button in
382       match href_callback with
383       | None -> ()
384       | Some f ->
385           (match hrefs with
386           | [ uri ] ->  f uri
387           | uris ->
388               let menu = GMenu.menu () in
389               List.iter
390                 (fun uri ->
391                   let menu_item =
392                     GMenu.menu_item ~label:uri ~packing:menu#append () in
393                   connect_menu_item menu_item 
394                   (fun () -> try f uri with Not_found -> assert false))
395                 uris;
396               menu#popup ~button ~time)
397
398   method private choose_selection_cb gdome_elt =
399     let set_selection elt =
400       let misc = self#coerce#misc in
401       self#set_selection (Some elt);
402       misc#add_selection_target ~target:"STRING" Gdk.Atom.primary;
403       ignore (misc#grab_selection Gdk.Atom.primary);
404     in
405     let rec aux elt =
406       if (elt#getAttributeNS ~namespaceURI:helm_ns
407             ~localName:xref_ds)#to_string <> ""
408       then
409         set_selection elt
410       else
411         try
412           (match elt#get_parentNode with
413           | None -> assert false
414           | Some p -> aux (new Gdome.element_of_node p))
415         with GdomeInit.DOMCastException _ -> ()
416     in
417     (match gdome_elt with
418     | Some elt when (elt#getAttributeNS ~namespaceURI:xlink_ns
419         ~localName:href_ds)#to_string <> "" ->
420           set_selection elt
421     | Some elt -> aux elt
422     | None -> self#set_selection None);
423     selection_changed <- true
424
425   method update_font_size = self#set_font_size !current_font_size
426
427     (** find a term by id from stored CIC infos @return either `Hyp if the id
428      * correspond to an hypothesis or `Term (cic, hyp) if the id correspond to a
429      * term. In the latter case hyp is either None (if the term is a subterm of
430      * the sequent conclusion) or Some hyp_name if the term belongs to an
431      * hypothesis *)
432   method private get_term_by_id cic_info id =
433     let unsh_item, ids_to_terms, ids_to_hypotheses, ids_to_father_ids, _, _ =
434       cic_info in
435     let rec find_father_hyp id =
436       if Hashtbl.mem ids_to_hypotheses id
437       then Some (name_of_hypothesis (Hashtbl.find ids_to_hypotheses id))
438       else
439         let father_id =
440           try Hashtbl.find ids_to_father_ids id
441           with Not_found -> assert false in
442         match father_id with
443         | Some id -> find_father_hyp id
444         | None -> None
445     in
446     try
447       let term = Hashtbl.find ids_to_terms id in
448       let father_hyp = find_father_hyp id in
449       SelTerm (term, father_hyp)
450     with Not_found ->
451       try
452         let hyp = Hashtbl.find ids_to_hypotheses id in
453         let _, context, _ =
454           match unsh_item with Some seq -> seq | None -> assert false in
455         let context' = MatitaMisc.list_tl_at hyp context in
456         SelHyp (name_of_hypothesis hyp, context')
457       with Not_found -> assert false
458     
459   method private find_obj_conclusion id =
460     match self#cic_info with
461     | None
462     | Some (_, _, _, _, _, None) -> assert false
463     | Some (_, ids_to_terms, _, ids_to_father_ids, ids_to_inner_types, Some annobj) ->
464         let id =
465          find_root_id annobj id ids_to_father_ids ids_to_terms ids_to_inner_types
466         in
467          (try Hashtbl.find ids_to_terms id with Not_found -> assert false)
468
469   method private string_of_node ~(paste_kind:paste_kind) node =
470     if node#hasAttributeNS ~namespaceURI:helm_ns ~localName:xref_ds
471     then
472       match paste_kind with
473       | `Pattern ->
474           let tactic_text_pattern =  self#tactic_text_pattern_of_node node in
475           GrafiteAstPp.pp_tactic_pattern
476             ~term_pp:(fun s -> s) ~lazy_term_pp:(fun _ -> assert false)
477             ~map_unicode_to_tex:(Helm_registry.get_bool
478               "matita.paste_unicode_as_tex")
479             tactic_text_pattern
480       | `Term -> self#tactic_text_of_node node
481     else string_of_dom_node node
482
483   method private string_of_cic_sequent ~output_type cic_sequent =
484     let script = MatitaScript.current () in
485     let metasenv =
486       if script#onGoingProof () then script#proofMetasenv else [] in
487     let map_unicode_to_tex =
488       Helm_registry.get_bool "matita.paste_unicode_as_tex" in
489     ApplyTransformation.txt_of_cic_sequent_conclusion ~map_unicode_to_tex
490      ~output_type text_width metasenv cic_sequent
491
492   method private pattern_of term father_hyp unsh_sequent =
493     let _, unsh_context, conclusion = unsh_sequent in
494     let where =
495      match father_hyp with
496         None -> conclusion
497       | Some name ->
498          let rec aux =
499           function
500              [] -> assert false
501            | Some (Cic.Name name', Cic.Decl ty)::_ when name' = name -> ty
502            | Some (Cic.Name name', Cic.Def (bo,_))::_ when name' = name-> bo
503            | _::tl -> aux tl
504          in
505           aux unsh_context
506     in
507      ProofEngineHelpers.pattern_of ~term:where [term]
508
509   method private get_cic_info id =
510     match self#cic_info with
511     | Some ((Some unsh_sequent, _, _, _, _, _) as info) -> info, unsh_sequent
512     | Some ((None, _, _, _, _, _) as info) ->
513         let t = self#find_obj_conclusion id in
514         info, (~-1, [], t) (* dummy sequent for obj *)
515     | None -> assert false
516
517   method private get_ncic_info id =
518     match self#ncic_info with
519     | Some info -> info
520     | None -> assert false
521
522   method private sequent_of_id ~(paste_kind:paste_kind) id =
523     let cic_info, unsh_sequent = self#get_cic_info id in
524     let cic_sequent =
525       match self#get_term_by_id cic_info id with
526       | SelTerm (t, father_hyp) ->
527 (*
528 IDIOTA: PRIMA SI FA LA LOCATE, POI LA PATTERN_OF. MEGLIO UN'UNICA pattern_of CHE PRENDA IN INPUT UN TERMINE E UN SEQUENTE. PER IL MOMENTO RISOLVO USANDO LA father_hyp PER RITROVARE L'IPOTESI PERDUTA
529 *)
530           let occurrences =
531             ProofEngineHelpers.locate_in_conjecture t unsh_sequent in
532           (match occurrences with
533           | [ context, _t ] ->
534               (match paste_kind with
535               | `Term -> ~-1, context, t
536               | `Pattern -> ~-1, [], self#pattern_of t father_hyp unsh_sequent)
537           | _ ->
538               HLog.error (sprintf "found %d occurrences while 1 was expected"
539                 (List.length occurrences));
540               assert false) (* since it uses physical equality *)
541       | SelHyp (_name, context) -> ~-1, context, Cic.Rel 1 in
542     cic_sequent
543
544   method private string_of_selection ~(paste_kind:paste_kind) =
545     match self#get_selections with
546     | [] -> None
547     | node :: _ -> Some (self#string_of_node ~paste_kind node)
548
549   method has_selection = self#get_selections <> []
550
551     (** @return an associative list format -> string with all possible selection
552      * formats. Rationale: in order to convert the selection to TERM or PATTERN
553      * format we need the sequent, the metasenv, ... keeping all of them in a
554      * closure would be more expensive than keeping their already converted
555      * forms *)
556   method strings_of_selection =
557     try
558       let misc = self#coerce#misc in
559       List.iter
560         (fun target -> misc#add_selection_target ~target Gdk.Atom.clipboard)
561         [ "TERM"; "PATTERN"; "STRING" ];
562       ignore (misc#grab_selection Gdk.Atom.clipboard);
563       List.map
564         (fun paste_kind ->
565           paste_kind, HExtlib.unopt (self#string_of_selection ~paste_kind))
566         [ `Term; `Pattern ]
567     with Failure _ -> failwith "no selection"
568
569 end
570
571 let clickableMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity =
572   GtkBase.Widget.size_params
573     ~cont:(OgtkMathViewProps.pack_return (fun p ->
574       OgtkMathViewProps.set_params
575         (new clickableMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
576         ~font_size:None ~log_verbosity:None))
577     []
578
579 class cicMathView obj =
580 object (self)
581   inherit clickableMathView obj
582
583   val mutable current_mathml = None
584
585   method load_sequent metasenv metano =
586     let sequent = CicUtil.lookup_meta metano metasenv in
587     let (mathml, unsh_sequent,
588       (_, (ids_to_terms, ids_to_father_ids, ids_to_hypotheses,_ )))
589     =
590       ApplyTransformation.mml_of_cic_sequent metasenv sequent
591     in
592     self#set_cic_info
593       (Some (Some unsh_sequent,
594         ids_to_terms, ids_to_hypotheses, ids_to_father_ids,
595         Hashtbl.create 1, None));
596     if BuildTimeConf.debug then begin
597       let name =
598        "/tmp/sequent_viewer_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in
599       HLog.debug ("load_sequent: dumping MathML to ./" ^ name);
600       ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ())
601     end;
602     self#load_root ~root:mathml#get_documentElement
603
604   method nload_sequent metasenv subst metano =
605     let sequent = List.assoc metano metasenv in
606     let mathml,ids_to_father_ids =
607      ApplyTransformation.nmml_of_cic_sequent metasenv subst (metano,sequent)
608     in
609     self#set_ncic_info (Some ids_to_father_ids);
610     if BuildTimeConf.debug then begin
611       let name =
612        "/tmp/sequent_viewer_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in
613       HLog.debug ("load_sequent: dumping MathML to ./" ^ name);
614       ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ())
615     end;
616     self#load_root ~root:mathml#get_documentElement
617
618   method load_object obj =
619     let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *)
620     let (mathml,
621       (annobj, (ids_to_terms, ids_to_father_ids, _, ids_to_hypotheses, _, ids_to_inner_types)))
622     =
623       ApplyTransformation.mml_of_cic_object obj
624     in
625     self#set_cic_info
626       (Some (None, ids_to_terms, ids_to_hypotheses, ids_to_father_ids, ids_to_inner_types, Some annobj));
627     (match current_mathml with
628     | Some current_mathml when use_diff ->
629         self#freeze;
630         XmlDiff.update_dom ~from:current_mathml mathml;
631         self#thaw
632     |  _ ->
633         if BuildTimeConf.debug then begin
634           let name =
635            "/tmp/cic_browser_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in
636           HLog.debug ("cic_browser: dumping MathML to ./" ^ name);
637           ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ())
638         end;
639         self#load_root ~root:mathml#get_documentElement;
640         current_mathml <- Some mathml);
641
642   method load_nobject obj =
643     let mathml,ids_to_father_ids = ApplyTransformation.nmml_of_cic_object obj in
644      self#set_ncic_info (Some ids_to_father_ids);
645 (*
646     (match current_mathml with
647     | Some current_mathml when use_diff ->
648         self#freeze;
649         XmlDiff.update_dom ~from:current_mathml mathml;
650         self#thaw
651     |  _ ->
652 *)
653         if BuildTimeConf.debug then begin
654           let name =
655            "/tmp/cic_browser_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in
656           HLog.debug ("cic_browser: dumping MathML to ./" ^ name);
657           ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ())
658         end;
659         self#load_root ~root:mathml#get_documentElement;
660         (*current_mathml <- Some mathml*)(*)*);
661 end
662
663 let tab_label meta_markup =
664   let rec aux =
665     function
666     | `Closed m -> sprintf "<s>%s</s>" (aux m)
667     | `Current m -> sprintf "<b>%s</b>" (aux m)
668     | `Shift (pos, m) -> sprintf "|<sub>%d</sub>: %s" pos (aux m)
669     | `Meta n -> sprintf "?%d" n
670   in
671   let markup = aux meta_markup in
672   (GMisc.label ~markup ~show:true ())#coerce
673
674 let goal_of_switch = function Stack.Open g | Stack.Closed g -> g
675
676 class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () =
677   object (self)
678     inherit scriptAccessor
679
680     method cicMathView = cicMathView  (** clickableMathView accessor *)
681
682     val mutable pages = 0
683     val mutable switch_page_callback = None
684     val mutable page2goal = []  (* associative list: page no -> goal no *)
685     val mutable goal2page = []  (* the other way round *)
686     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
687     val mutable _metasenv = `Old []
688     val mutable scrolledWin: GBin.scrolled_window option = None
689       (* scrolled window to which the sequentViewer is currently attached *)
690     val logo = (GMisc.image
691       ~file:(MatitaMisc.image_path "matita_medium.png") ()
692       :> GObj.widget)
693             
694     val logo_with_qed = (GMisc.image
695       ~file:(MatitaMisc.image_path "matita_small.png") ()
696       :> GObj.widget)
697
698     method load_logo =
699      notebook#set_show_tabs false;
700      ignore(notebook#append_page logo)
701
702     method load_logo_with_qed =
703      notebook#set_show_tabs false;
704      ignore(notebook#append_page logo_with_qed)
705
706     method reset =
707       cicMathView#remove_selections;
708       (match scrolledWin with
709       | Some w ->
710           (* removing page from the notebook will destroy all contained widget,
711           * we do not want the cicMathView to be destroyed as well *)
712           w#remove cicMathView#coerce;
713           scrolledWin <- None
714       | None -> ());
715       (match switch_page_callback with
716       | Some id ->
717           GtkSignal.disconnect notebook#as_widget id;
718           switch_page_callback <- None
719       | None -> ());
720       for i = 0 to pages do notebook#remove_page 0 done; 
721       notebook#set_show_tabs true;
722       pages <- 0;
723       page2goal <- [];
724       goal2page <- [];
725       goal2win <- [];
726       _metasenv <- `Old []; 
727       self#script#setGoal None
728
729     method load_sequents 
730       { proof = (_,metasenv,_subst,_,_, _) as proof; stack = stack } 
731     =
732       _metasenv <- `Old metasenv;
733       pages <- 0;
734       let win goal_switch =
735         let w =
736           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`ALWAYS
737             ~shadow_type:`IN ~show:true ()
738         in
739         let reparent () =
740           scrolledWin <- Some w;
741           match cicMathView#misc#parent with
742           | None -> w#add cicMathView#coerce
743           | Some parent ->
744              let parent =
745               match cicMathView#misc#parent with
746                  None -> assert false
747                | Some p -> GContainer.cast_container p
748              in
749               parent#remove cicMathView#coerce;
750               w#add cicMathView#coerce
751         in
752         goal2win <- (goal_switch, reparent) :: goal2win;
753         w#coerce
754       in
755       assert (
756         let stack_goals = Stack.open_goals stack in
757         let proof_goals = ProofEngineTypes.goals_of_proof proof in
758         if
759           HExtlib.list_uniq (List.sort Pervasives.compare stack_goals)
760           <> List.sort Pervasives.compare proof_goals
761         then begin
762           prerr_endline ("STACK GOALS = " ^ String.concat " " (List.map string_of_int stack_goals));
763           prerr_endline ("PROOF GOALS = " ^ String.concat " " (List.map string_of_int proof_goals));
764           false
765         end
766         else true
767       );
768       let render_switch =
769         function Stack.Open i ->`Meta i | Stack.Closed i ->`Closed (`Meta i)
770       in
771       let page = ref 0 in
772       let added_goals = ref [] in
773         (* goals can be duplicated on the tack due to focus, but we should avoid
774          * multiple labels in the user interface *)
775       let add_tab markup goal_switch =
776         let goal = Stack.goal_of_switch goal_switch in
777         if not (List.mem goal !added_goals) then begin
778           ignore(notebook#append_page 
779             ~tab_label:(tab_label markup) (win goal_switch));
780           page2goal <- (!page, goal_switch) :: page2goal;
781           goal2page <- (goal_switch, !page) :: goal2page;
782           incr page;
783           pages <- pages + 1;
784           added_goals := goal :: !added_goals
785         end
786       in
787       let add_switch _ _ (_, sw) = add_tab (render_switch sw) sw in
788       Stack.iter  (** populate notebook with tabs *)
789         ~env:(fun depth tag (pos, sw) ->
790           let markup =
791             match depth, pos with
792             | 0, 0 -> `Current (render_switch sw)
793             | 0, _ -> `Shift (pos, `Current (render_switch sw))
794             | 1, pos when Stack.head_tag stack = `BranchTag ->
795                 `Shift (pos, render_switch sw)
796             | _ -> render_switch sw
797           in
798           add_tab markup sw)
799         ~cont:add_switch ~todo:add_switch
800         stack;
801       switch_page_callback <-
802         Some (notebook#connect#switch_page ~callback:(fun page ->
803           let goal_switch =
804             try List.assoc page page2goal with Not_found -> assert false
805           in
806           self#script#setGoal (Some (goal_of_switch goal_switch));
807           self#render_page ~page ~goal_switch))
808
809     method nload_sequents 
810       { NTacStatus.istatus = { NTacStatus.pstatus = (_,_,metasenv,subst,_) }; gstatus = stack } 
811     =
812       _metasenv <- `New (metasenv,subst);
813       pages <- 0;
814       let win goal_switch =
815         let w =
816           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`ALWAYS
817             ~shadow_type:`IN ~show:true ()
818         in
819         let reparent () =
820           scrolledWin <- Some w;
821           match cicMathView#misc#parent with
822           | None -> w#add cicMathView#coerce
823           | Some parent ->
824              let parent =
825               match cicMathView#misc#parent with
826                  None -> assert false
827                | Some p -> GContainer.cast_container p
828              in
829               parent#remove cicMathView#coerce;
830               w#add cicMathView#coerce
831         in
832         goal2win <- (goal_switch, reparent) :: goal2win;
833         w#coerce
834       in
835       assert (
836         let stack_goals = Stack.open_goals stack in
837         let proof_goals = List.map fst metasenv in
838         if
839           HExtlib.list_uniq (List.sort Pervasives.compare stack_goals)
840           <> List.sort Pervasives.compare proof_goals
841         then begin
842           prerr_endline ("STACK GOALS = " ^ String.concat " " (List.map string_of_int stack_goals));
843           prerr_endline ("PROOF GOALS = " ^ String.concat " " (List.map string_of_int proof_goals));
844           false
845         end
846         else true
847       );
848       let render_switch =
849         function Stack.Open i ->`Meta i | Stack.Closed i ->`Closed (`Meta i)
850       in
851       let page = ref 0 in
852       let added_goals = ref [] in
853         (* goals can be duplicated on the tack due to focus, but we should avoid
854          * multiple labels in the user interface *)
855       let add_tab markup goal_switch =
856         let goal = Stack.goal_of_switch goal_switch in
857         if not (List.mem goal !added_goals) then begin
858           ignore(notebook#append_page 
859             ~tab_label:(tab_label markup) (win goal_switch));
860           page2goal <- (!page, goal_switch) :: page2goal;
861           goal2page <- (goal_switch, !page) :: goal2page;
862           incr page;
863           pages <- pages + 1;
864           added_goals := goal :: !added_goals
865         end
866       in
867       let add_switch _ _ (_, sw) = add_tab (render_switch sw) sw in
868       Stack.iter  (** populate notebook with tabs *)
869         ~env:(fun depth tag (pos, sw) ->
870           let markup =
871             match depth, pos with
872             | 0, 0 -> `Current (render_switch sw)
873             | 0, _ -> `Shift (pos, `Current (render_switch sw))
874             | 1, pos when Stack.head_tag stack = `BranchTag ->
875                 `Shift (pos, render_switch sw)
876             | _ -> render_switch sw
877           in
878           add_tab markup sw)
879         ~cont:add_switch ~todo:add_switch
880         stack;
881       switch_page_callback <-
882         Some (notebook#connect#switch_page ~callback:(fun page ->
883           let goal_switch =
884             try List.assoc page page2goal with Not_found -> assert false
885           in
886           self#script#setGoal (Some (goal_of_switch goal_switch));
887           self#render_page ~page ~goal_switch))
888
889     method private render_page ~page ~goal_switch =
890       (match goal_switch with
891       | Stack.Open goal ->
892          (match _metasenv with
893              `Old menv -> cicMathView#load_sequent menv goal
894            | `New (menv,subst) -> cicMathView#nload_sequent menv subst goal)
895       | Stack.Closed goal ->
896           let doc = Lazy.force closed_goal_mathml in
897           cicMathView#load_root ~root:doc#get_documentElement);
898       (try
899         cicMathView#set_selection None;
900         List.assoc goal_switch goal2win ()
901       with Not_found -> assert false)
902
903     method goto_sequent goal =
904       let goal_switch, page =
905         try
906           List.find
907             (function Stack.Open g, _ | Stack.Closed g, _ -> g = goal)
908             goal2page
909         with Not_found -> assert false
910       in
911       notebook#goto_page page;
912       self#render_page page goal_switch
913
914   end
915
916  (** constructors *)
917
918 type 'widget constructor =
919   ?hadjustment:GData.adjustment ->
920   ?vadjustment:GData.adjustment ->
921   ?font_size:int ->
922   ?log_verbosity:int ->
923   ?width:int ->
924   ?height:int ->
925   ?packing:(GObj.widget -> unit) ->
926   ?show:bool ->
927   unit ->
928     'widget
929
930 let cicMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity =
931   GtkBase.Widget.size_params
932     ~cont:(OgtkMathViewProps.pack_return (fun p ->
933       OgtkMathViewProps.set_params
934         (new cicMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
935         ~font_size ~log_verbosity))
936     []
937
938 let blank_uri = BuildTimeConf.blank_uri
939 let current_proof_uri = BuildTimeConf.current_proof_uri
940
941 type term_source =
942   [ `Ast of CicNotationPt.term
943   | `Cic of Cic.term * Cic.metasenv
944   | `String of string
945   ]
946
947 class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history)
948   ()
949 =
950   let whelp_RE = Pcre.regexp "^\\s*whelp" in
951   let uri_RE =
952     Pcre.regexp
953       "^cic:/([^/]+/)*[^/]+\\.(con|ind|var)(#xpointer\\(\\d+(/\\d+)+\\))?$"
954   in
955   let dir_RE = Pcre.regexp "^cic:((/([^/]+/)*[^/]+(/)?)|/|)$" in
956   let metadata_RE = Pcre.regexp "^metadata:/(deps)/(forward|backward)/(.*)$" in
957   let whelp_query_RE = Pcre.regexp
958     "^\\s*whelp\\s+([^\\s]+)\\s+(\"|\\()(.*)(\\)|\")$" 
959   in
960   let is_metadata txt = Pcre.pmatch ~rex:metadata_RE txt in
961   let is_whelp txt = Pcre.pmatch ~rex:whelp_RE txt in
962   let is_uri txt = Pcre.pmatch ~rex:uri_RE txt in
963   let is_dir txt = Pcre.pmatch ~rex:dir_RE txt in
964   let gui = get_gui () in
965   let (win: MatitaGuiTypes.browserWin) = gui#newBrowserWin () in
966   let gviz = LablGraphviz.graphviz ~packing:win#graphScrolledWin#add () in
967   let queries = ["Locate";"Hint";"Match";"Elim";"Instance"] in
968   let combo,_ = GEdit.combo_box_text ~strings:queries () in
969   let activate_combo_query input q =
970     let q' = String.lowercase q in
971     let rec aux i = function
972       | [] -> failwith ("Whelp query '" ^ q ^ "' not found")
973       | h::_ when String.lowercase h = q' -> i
974       | _::tl -> aux (i+1) tl
975     in
976     win#queryInputText#set_text input;
977     combo#set_active (aux 0 queries);
978   in
979   let searchText = 
980     GSourceView.source_view ~auto_indent:false ~editable:false ()
981   in
982   let _ =
983      win#scrolledwinContent#add (searchText :> GObj.widget);
984      let callback () = 
985        let text = win#entrySearch#text in
986        let highlight start end_ =
987          searchText#source_buffer#move_mark `INSERT ~where:start;
988          searchText#source_buffer#move_mark `SEL_BOUND ~where:end_;
989          searchText#scroll_mark_onscreen `INSERT
990        in
991        let iter = searchText#source_buffer#get_iter `SEL_BOUND in
992        match iter#forward_search text with
993        | None -> 
994            (match searchText#source_buffer#start_iter#forward_search text with
995            | None -> ()
996            | Some (start,end_) -> highlight start end_)
997        | Some (start,end_) -> highlight start end_
998      in
999      ignore(win#entrySearch#connect#activate ~callback);
1000      ignore(win#buttonSearch#connect#clicked ~callback);
1001   in
1002   let set_whelp_query txt =
1003     let query, arg = 
1004       try
1005         let q = Pcre.extract ~rex:whelp_query_RE txt in
1006         q.(1), q.(3)
1007       with Not_found -> failwith "Malformed Whelp query"
1008     in
1009     activate_combo_query arg query;
1010   in
1011   let toplevel = win#toplevel in
1012   let mathView = cicMathView ~packing:win#scrolledBrowser#add () in
1013   let fail message = 
1014     MatitaGtkMisc.report_error ~title:"Cic browser" ~message 
1015       ~parent:toplevel ()  
1016   in
1017   let tags =
1018     [ "dir", GdkPixbuf.from_file (MatitaMisc.image_path "matita-folder.png");
1019       "obj", GdkPixbuf.from_file (MatitaMisc.image_path "matita-object.png") ]
1020   in
1021   let b = (not (Helm_registry.get_bool "matita.debug")) in
1022   let handle_error f =
1023     try
1024       f ()
1025     with exn ->
1026       if b then
1027         fail (snd (MatitaExcPp.to_string exn))
1028       else raise exn
1029   in
1030   let handle_error' f = (fun () -> handle_error (fun () -> f ())) in
1031   let load_easter_egg = lazy (
1032     win#browserImage#set_file (MatitaMisc.image_path "meegg.png"))
1033   in
1034   let load_coerchgraph tred () = 
1035       let str = CoercGraph.generate_dot_file () in
1036       let filename, oc = Filename.open_temp_file "matita" ".dot" in
1037       output_string oc str;
1038       close_out oc;
1039       if tred then
1040         gviz#load_graph_from_file ~gviz_cmd:"tred|dot" filename
1041       else
1042         gviz#load_graph_from_file filename;
1043       HExtlib.safe_remove filename
1044   in
1045   object (self)
1046     inherit scriptAccessor
1047     
1048     (* Whelp bar queries *)
1049
1050     val mutable gviz_graph = MetadataDeps.DepGraph.dummy
1051     val mutable gviz_uri = UriManager.uri_of_string "cic:/dummy.con";
1052
1053     val dep_contextual_menu = GMenu.menu ()
1054
1055     initializer
1056       activate_combo_query "" "locate";
1057       win#whelpBarComboVbox#add combo#coerce;
1058       let start_query () = 
1059        let query = 
1060          try
1061            String.lowercase (List.nth queries combo#active) 
1062          with Not_found -> assert false in
1063        let input = win#queryInputText#text in
1064        let statement = 
1065          if query = "locate" then
1066              "whelp " ^ query ^ " \"" ^ input ^ "\"." 
1067            else
1068              "whelp " ^ query ^ " (" ^ input ^ ")." 
1069        in
1070         (MatitaScript.current ())#advance ~statement ()
1071       in
1072       ignore(win#queryInputText#connect#activate ~callback:start_query);
1073       ignore(combo#connect#changed ~callback:start_query);
1074       win#whelpBarImage#set_file (MatitaMisc.image_path "whelp.png");
1075       win#mathOrListNotebook#set_show_tabs false;
1076       win#browserForwardButton#misc#set_sensitive false;
1077       win#browserBackButton#misc#set_sensitive false;
1078       ignore (win#browserUri#connect#activate (handle_error' (fun () ->
1079         self#loadInput win#browserUri#text)));
1080       ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
1081         self#load (`About `Current_proof))));
1082       ignore (win#browserRefreshButton#connect#clicked
1083         (handle_error' (self#refresh ~force:true)));
1084       ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
1085       ignore (win#browserForwardButton#connect#clicked
1086         (handle_error' self#forward));
1087       ignore (win#toplevel#event#connect#delete (fun _ ->
1088         let my_id = Oo.id self in
1089         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
1090         false));
1091       ignore(win#whelpResultTreeview#connect#row_activated 
1092         ~callback:(fun _ _ ->
1093           handle_error (fun () -> self#loadInput (self#_getSelectedUri ()))));
1094       mathView#set_href_callback (Some (fun uri ->
1095         handle_error (fun () ->
1096          let uri =
1097           try
1098            `Uri (UriManager.uri_of_string uri)
1099           with
1100            UriManager.IllFormedUri _ ->
1101             `NRef (NReference.reference_of_string uri)
1102          in
1103           self#load uri)));
1104       gviz#connect_href (fun button_ev attrs ->
1105         let time = GdkEvent.Button.time button_ev in
1106         let uri = List.assoc "href" attrs in
1107         gviz_uri <- UriManager.uri_of_string uri;
1108         match GdkEvent.Button.button button_ev with
1109         | button when button = left_button -> self#load (`Uri gviz_uri)
1110         | button when button = right_button ->
1111             dep_contextual_menu#popup ~button ~time
1112         | _ -> ());
1113       connect_menu_item win#depGraphMenuItem (fun () ->
1114         match self#currentCicUri with
1115         | Some uri -> self#load (`Metadata (`Deps (`Fwd, uri)))
1116         | None -> ());
1117       connect_menu_item win#invDepGraphMenuItem (fun () ->
1118         match self#currentCicUri with
1119         | Some uri -> self#load (`Metadata (`Deps (`Back, uri)))
1120         | None -> ());
1121       connect_menu_item win#browserCloseMenuItem (fun () ->
1122         let my_id = Oo.id self in
1123         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
1124         win#toplevel#misc#hide(); win#toplevel#destroy ());
1125       (* remove hbugs *)
1126       (*
1127       connect_menu_item win#hBugsTutorsMenuItem (fun () ->
1128         self#load (`HBugs `Tutors));
1129       *)
1130       win#hBugsTutorsMenuItem#misc#hide ();
1131       connect_menu_item win#browserUrlMenuItem (fun () ->
1132         win#browserUri#misc#grab_focus ());
1133       connect_menu_item win#univMenuItem (fun () ->
1134         match self#currentCicUri with
1135         | Some uri -> self#load (`Univs uri)
1136         | None -> ());
1137
1138       (* fill dep graph contextual menu *)
1139       let go_menu_item =
1140         GMenu.image_menu_item ~label:"Browse it"
1141           ~packing:dep_contextual_menu#append () in
1142       let expand_menu_item =
1143         GMenu.image_menu_item ~label:"Expand"
1144           ~packing:dep_contextual_menu#append () in
1145       let collapse_menu_item =
1146         GMenu.image_menu_item ~label:"Collapse"
1147           ~packing:dep_contextual_menu#append () in
1148       dep_contextual_menu#append (go_menu_item :> GMenu.menu_item);
1149       dep_contextual_menu#append (expand_menu_item :> GMenu.menu_item);
1150       dep_contextual_menu#append (collapse_menu_item :> GMenu.menu_item);
1151       connect_menu_item go_menu_item (fun () -> self#load (`Uri gviz_uri));
1152       connect_menu_item expand_menu_item (fun () ->
1153         MetadataDeps.DepGraph.expand gviz_uri gviz_graph;
1154         self#redraw_gviz ~center_on:gviz_uri ());
1155       connect_menu_item collapse_menu_item (fun () ->
1156         MetadataDeps.DepGraph.collapse gviz_uri gviz_graph;
1157         self#redraw_gviz ~center_on:gviz_uri ());
1158
1159       self#_load (`About `Blank);
1160       toplevel#show ()
1161
1162     val mutable current_entry = `About `Blank 
1163
1164       (** @return None if no object uri can be built from the current entry *)
1165     method private currentCicUri =
1166       match current_entry with
1167       | `Uri uri
1168       | `Metadata (`Deps (_, uri)) -> Some uri
1169       | _ -> None
1170
1171     val model =
1172       new MatitaGtkMisc.taggedStringListModel tags win#whelpResultTreeview
1173     val model_univs =
1174       new MatitaGtkMisc.multiStringListModel ~cols:2 win#universesTreeview
1175
1176     val mutable lastDir = ""  (* last loaded "directory" *)
1177
1178     method mathView = (mathView :> MatitaGuiTypes.clickableMathView)
1179
1180     method private _getSelectedUri () =
1181       match model#easy_selection () with
1182       | [sel] when is_uri sel -> sel  (* absolute URI selected *)
1183 (*       | [sel] -> win#browserUri#entry#text ^ sel  |+ relative URI selected +| *)
1184       | [sel] -> lastDir ^ sel
1185       | _ -> assert false
1186
1187     (** history RATIONALE 
1188      *
1189      * All operations about history are done using _historyFoo.
1190      * Only toplevel functions (ATM load and loadInput) call _historyAdd.
1191      *)
1192           
1193     method private _historyAdd item = 
1194       history#add item;
1195       win#browserBackButton#misc#set_sensitive true;
1196       win#browserForwardButton#misc#set_sensitive false
1197
1198     method private _historyPrev () =
1199       let item = history#previous in
1200       if history#is_begin then win#browserBackButton#misc#set_sensitive false;
1201       win#browserForwardButton#misc#set_sensitive true;
1202       item
1203     
1204     method private _historyNext () =
1205       let item = history#next in
1206       if history#is_end then win#browserForwardButton#misc#set_sensitive false;
1207       win#browserBackButton#misc#set_sensitive true;
1208       item
1209
1210     (** notebook RATIONALE 
1211      * 
1212      * Use only these functions to switch between the tabs
1213      *)
1214     method private _showMath = win#mathOrListNotebook#goto_page  0
1215     method private _showList = win#mathOrListNotebook#goto_page  1
1216     method private _showList2 = win#mathOrListNotebook#goto_page 5
1217     method private _showSearch = win#mathOrListNotebook#goto_page 6
1218     method private _showGviz = win#mathOrListNotebook#goto_page  3
1219     method private _showHBugs = win#mathOrListNotebook#goto_page 4
1220
1221     method private back () =
1222       try
1223         self#_load (self#_historyPrev ())
1224       with MatitaMisc.History_failure -> ()
1225
1226     method private forward () =
1227       try
1228         self#_load (self#_historyNext ())
1229       with MatitaMisc.History_failure -> ()
1230
1231       (* loads a uri which can be a cic uri or an about:* uri
1232       * @param uri string *)
1233     method private _load ?(force=false) entry =
1234       handle_error (fun () ->
1235        if entry <> current_entry || entry = `About `Current_proof || entry =
1236          `About `Coercions || entry = `About `CoercionsFull || force then
1237         begin
1238           (match entry with
1239           | `About `Current_proof -> self#home ()
1240           | `About `Blank -> self#blank ()
1241           | `About `Us -> self#egg ()
1242           | `About `CoercionsFull -> self#coerchgraph false ()
1243           | `About `Coercions -> self#coerchgraph true ()
1244           | `About `TeX -> self#tex ()
1245           | `About `Grammar -> self#grammar () 
1246           | `Check term -> self#_loadCheck term
1247           | `Cic (term, metasenv) -> self#_loadTermCic term metasenv
1248           | `Dir dir -> self#_loadDir dir
1249           | `HBugs `Tutors -> self#_loadHBugsTutors
1250           | `Metadata (`Deps ((`Fwd | `Back) as dir, uri)) ->
1251               self#dependencies dir uri ()
1252           | `Uri uri -> self#_loadUriManagerUri uri
1253           | `NRef nref -> self#_loadNReference nref
1254           | `Univs uri -> self#_loadUnivs uri
1255           | `Whelp (query, results) -> 
1256               set_whelp_query query;
1257               self#_loadList (List.map (fun r -> "obj",
1258                 UriManager.string_of_uri r) results));
1259           self#setEntry entry
1260         end)
1261
1262     method private blank () =
1263       self#_showMath;
1264       mathView#load_root (Lazy.force empty_mathml)#get_documentElement
1265
1266     method private _loadCheck term =
1267       failwith "not implemented _loadCheck";
1268 (*       self#_showMath *)
1269
1270     method private egg () =
1271       win#mathOrListNotebook#goto_page 2;
1272       Lazy.force load_easter_egg
1273
1274     method private redraw_gviz ?center_on () =
1275       if Sys.command "which dot" = 0 then
1276        let tmpfile, oc = Filename.open_temp_file "matita" ".dot" in
1277        let fmt = Format.formatter_of_out_channel oc in
1278        MetadataDeps.DepGraph.render fmt gviz_graph;
1279        close_out oc;
1280        gviz#load_graph_from_file ~gviz_cmd:"tred | dot" tmpfile;
1281        (match center_on with
1282        | None -> ()
1283        | Some uri -> gviz#center_on_href (UriManager.string_of_uri uri));
1284        HExtlib.safe_remove tmpfile
1285       else
1286        MatitaGtkMisc.report_error ~title:"graphviz error"
1287         ~message:("Graphviz is not installed but is necessary to render "^
1288          "the graph of dependencies amoung objects. Please install it.")
1289         ~parent:win#toplevel ()
1290
1291     method private dependencies direction uri () =
1292       let dbd = LibraryDb.instance () in
1293       let graph =
1294         match direction with
1295         | `Fwd -> MetadataDeps.DepGraph.direct_deps ~dbd uri
1296         | `Back -> MetadataDeps.DepGraph.inverse_deps ~dbd uri in
1297       gviz_graph <- graph;  (** XXX check this for memory consuption *)
1298       self#redraw_gviz ~center_on:uri ();
1299       self#_showGviz
1300
1301     method private coerchgraph tred () =
1302       load_coerchgraph tred ();
1303       self#_showGviz
1304
1305     method private tex () =
1306       let b = Buffer.create 1000 in
1307       Printf.bprintf b "UTF-8 equivalence classes (rotate with ALT-L):\n\n";
1308       List.iter 
1309         (fun l ->
1310            List.iter (fun sym ->
1311              Printf.bprintf b "  %s" (Glib.Utf8.from_unichar sym) 
1312            ) l;
1313            Printf.bprintf b "\n";
1314         )
1315         (List.sort 
1316           (fun l1 l2 -> compare (List.hd l1) (List.hd l2))
1317           (Virtuals.get_all_eqclass ()));
1318       Printf.bprintf b "\n\nVirtual keys (trigger with ALT-L):\n\n";
1319       List.iter 
1320         (fun tag, items -> 
1321            Printf.bprintf b "  %s:\n" tag;
1322            List.iter 
1323              (fun names, symbol ->
1324                 Printf.bprintf b "  \t%s\t%s\n" 
1325                   (Glib.Utf8.from_unichar symbol)
1326                   (String.concat ", " names))
1327              (List.sort 
1328                (fun (_,a) (_,b) -> compare a b)
1329                items);
1330            Printf.bprintf b "\n")
1331         (List.sort 
1332           (fun (a,_) (b,_) -> compare a b)
1333           (Virtuals.get_all_virtuals ()));
1334       self#_loadText (Buffer.contents b)
1335
1336     method private _loadText text =
1337       searchText#source_buffer#set_text text;
1338       win#entrySearch#misc#grab_focus ();
1339       self#_showSearch
1340
1341     method private grammar () =
1342       self#_loadText (Print_grammar.ebnf_of_term ());
1343
1344     method private home () =
1345       self#_showMath;
1346       match self#script#grafite_status.proof_status with
1347       | Proof  (uri, metasenv, _subst, bo, ty, attrs) ->
1348          let name = UriManager.name_of_uri (HExtlib.unopt uri) in
1349          let obj =
1350           Cic.CurrentProof (name, metasenv, Lazy.force bo, ty, [], attrs)
1351          in
1352           self#_loadObj obj
1353       | Incomplete_proof { proof = (uri, metasenv, _subst, bo, ty, attrs) } ->
1354          let name = UriManager.name_of_uri (HExtlib.unopt uri) in
1355          let obj =
1356           Cic.CurrentProof (name, metasenv, Lazy.force bo, ty, [], attrs)
1357          in
1358           self#_loadObj obj
1359       | _ ->
1360         match self#script#grafite_status.ng_status with
1361            ProofMode tstatus ->
1362             let nobj = tstatus.NTacStatus.istatus.NTacStatus.pstatus in
1363              self#_loadNObj nobj
1364          | _ -> self#blank ()
1365
1366       (** loads a cic uri from the environment
1367       * @param uri UriManager.uri *)
1368     method private _loadUriManagerUri uri =
1369       let uri = UriManager.strip_xpointer uri in
1370       let (obj, _) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
1371       self#_loadObj obj
1372
1373     method private _loadNReference (NReference.Ref (uri,_)) =
1374       let obj = NCicEnvironment.get_checked_obj uri in
1375       self#_loadNObj obj
1376
1377     method private _loadUnivs uri =
1378       let uri = UriManager.strip_xpointer uri in
1379       let (_, u) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
1380       let _,us = CicUniv.do_rank u in
1381       let l = 
1382         List.map 
1383           (fun u -> 
1384            [ CicUniv.string_of_universe u ; string_of_int (CicUniv.get_rank u)])
1385           us 
1386       in
1387       self#_loadList2 l
1388       
1389     method private _loadDir dir = 
1390       let content = Http_getter.ls ~local:false dir in
1391       let l =
1392         List.fast_sort
1393           Pervasives.compare
1394           (List.map
1395             (function 
1396               | Http_getter_types.Ls_section s -> "dir", s
1397               | Http_getter_types.Ls_object o -> "obj", o.Http_getter_types.uri)
1398             content)
1399       in
1400       lastDir <- dir;
1401       self#_loadList l
1402
1403     method private _loadHBugsTutors =
1404       self#_showHBugs
1405
1406     method private setEntry entry =
1407       win#browserUri#set_text (MatitaTypes.string_of_entry entry);
1408       current_entry <- entry
1409
1410     method private _loadObj obj =
1411       (* showMath must be done _before_ loading the document, since if the
1412        * widget is not mapped (hidden by the notebook) the document is not
1413        * rendered *)
1414       self#_showMath;
1415       mathView#load_object obj
1416
1417     method private _loadNObj obj =
1418       (* showMath must be done _before_ loading the document, since if the
1419        * widget is not mapped (hidden by the notebook) the document is not
1420        * rendered *)
1421       self#_showMath;
1422       mathView#load_nobject obj
1423
1424     method private _loadTermCic term metasenv =
1425       let context = self#script#proofContext in
1426       let dummyno = CicMkImplicit.new_meta metasenv [] in
1427       let sequent = (dummyno, context, term) in
1428       mathView#load_sequent (sequent :: metasenv) dummyno;
1429       self#_showMath
1430
1431     method private _loadList l =
1432       model#list_store#clear ();
1433       List.iter (fun (tag, s) -> model#easy_append ~tag s) l;
1434       self#_showList
1435
1436     method private _loadList2 l =
1437       model_univs#list_store#clear ();
1438       List.iter model_univs#easy_mappend l;
1439       self#_showList2
1440     
1441     (** { public methods, all must call _load!! } *)
1442       
1443     method load entry =
1444       handle_error (fun () -> self#_load entry; self#_historyAdd entry)
1445
1446     (**  this is what the browser does when you enter a string an hit enter *)
1447     method loadInput txt =
1448       let parse_metadata s =
1449         let subs = Pcre.extract ~rex:metadata_RE s in
1450         let uri = UriManager.uri_of_string ("cic:/" ^ subs.(3)) in
1451         match subs.(1), subs.(2) with
1452         | "deps", "forward" -> `Deps (`Fwd, uri)
1453         | "deps", "backward" -> `Deps (`Back, uri)
1454         | _ -> assert false
1455       in
1456       let txt = HExtlib.trim_blanks txt in
1457       (* (* ZACK: what the heck? *)
1458       let fix_uri txt =
1459         UriManager.string_of_uri
1460           (UriManager.strip_xpointer (UriManager.uri_of_string txt))
1461       in
1462       *)
1463       if is_whelp txt then begin
1464         set_whelp_query txt;  
1465         (MatitaScript.current ())#advance ~statement:(txt ^ ".") ()
1466       end else begin
1467         let entry =
1468           match txt with
1469           | txt when is_uri txt ->
1470               `Uri (UriManager.uri_of_string ((*fix_uri*) txt))
1471           | txt when is_dir txt -> `Dir (MatitaMisc.normalize_dir txt)
1472           | txt when is_metadata txt -> `Metadata (parse_metadata txt)
1473           | "hbugs:/tutors/" -> `HBugs `Tutors
1474           | txt ->
1475              (try
1476                MatitaTypes.entry_of_string txt
1477               with Invalid_argument _ ->
1478                raise
1479                 (GrafiteTypes.Command_error(sprintf "unsupported uri: %s" txt)))
1480         in
1481         self#_load entry;
1482         self#_historyAdd entry
1483       end
1484
1485       (** {2 methods accessing underlying GtkMathView} *)
1486
1487     method updateFontSize = mathView#set_font_size !current_font_size
1488
1489       (** {2 methods used by constructor only} *)
1490
1491     method win = win
1492     method history = history
1493     method currentEntry = current_entry
1494     method refresh ~force () = self#_load ~force current_entry
1495
1496   end
1497   
1498 let sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) ():
1499   MatitaGuiTypes.sequentsViewer
1500 =
1501   new sequentsViewer ~notebook ~cicMathView ()
1502
1503 let cicBrowser () =
1504   let size = BuildTimeConf.browser_history_size in
1505   let rec aux history =
1506     let browser = new cicBrowser_impl ~history () in
1507     let win = browser#win in
1508     ignore (win#browserNewButton#connect#clicked (fun () ->
1509       let history =
1510         new MatitaMisc.browser_history ~memento:history#save size
1511           (`About `Blank)
1512       in
1513       let newBrowser = aux history in
1514       newBrowser#load browser#currentEntry));
1515 (*
1516       (* attempt (failed) to close windows on CTRL-W ... *)
1517     MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
1518       GdkKeysyms._W (fun () -> win#toplevel#destroy ());
1519 *)
1520     cicBrowsers := browser :: !cicBrowsers;
1521     (browser :> MatitaGuiTypes.cicBrowser)
1522   in
1523   let history = new MatitaMisc.browser_history size (`About `Blank) in
1524   aux history
1525
1526 let default_cicMathView () = cicMathView ~show:true ()
1527 let cicMathView_instance = MatitaMisc.singleton default_cicMathView
1528
1529 let default_sequentsViewer () =
1530   let gui = get_gui () in
1531   let cicMathView = cicMathView_instance () in
1532   sequentsViewer ~notebook:gui#main#sequentsNotebook ~cicMathView ()
1533 let sequentsViewer_instance = MatitaMisc.singleton default_sequentsViewer
1534
1535 let mathViewer () = 
1536   object(self)
1537     method private get_browser reuse = 
1538       if reuse then
1539         (match !cicBrowsers with
1540         | [] -> cicBrowser ()
1541         | b :: _ -> (b :> MatitaGuiTypes.cicBrowser))
1542       else
1543         (cicBrowser ())
1544           
1545     method show_entry ?(reuse=false) t = (self#get_browser reuse)#load t
1546       
1547     method show_uri_list ?(reuse=false) ~entry l =
1548       (self#get_browser reuse)#load entry
1549   end
1550
1551 let refresh_all_browsers () =
1552   List.iter (fun b -> b#refresh ~force:false ()) !cicBrowsers
1553
1554 let update_font_sizes () =
1555   List.iter (fun b -> b#updateFontSize) !cicBrowsers;
1556   (cicMathView_instance ())#update_font_size
1557
1558 let get_math_views () =
1559   ((cicMathView_instance ()) :> MatitaGuiTypes.clickableMathView)
1560   :: (List.map (fun b -> b#mathView) !cicBrowsers)
1561
1562 let find_selection_owner () =
1563   let rec aux =
1564     function
1565     | [] -> raise Not_found
1566     | mv :: tl ->
1567         (match mv#get_selections with
1568         | [] -> aux tl
1569         | sel :: _ -> mv)
1570   in
1571   aux (get_math_views ())
1572
1573 let has_selection () =
1574   try ignore (find_selection_owner ()); true
1575   with Not_found -> false
1576
1577 let math_view_clipboard = ref None (* associative list target -> string *)
1578 let has_clipboard () = !math_view_clipboard <> None
1579 let empty_clipboard () = math_view_clipboard := None
1580
1581 let copy_selection () =
1582   try
1583     math_view_clipboard :=
1584       Some ((find_selection_owner ())#strings_of_selection)
1585   with Not_found -> failwith "no selection"
1586
1587 let paste_clipboard paste_kind =
1588   match !math_view_clipboard with
1589   | None -> failwith "empty clipboard"
1590   | Some cb ->
1591       (try List.assoc paste_kind cb with Not_found -> assert false)
1592