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