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