]> matita.cs.unibo.it Git - helm.git/blob - helm/matita/matitaMathView.ml
- fixed "error loading dom error" avoiding sequent_viewer be delivered
[helm.git] / helm / matita / matitaMathView.ml
1 (* Copyright (C) 2000-2002, 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 MatitaCicMisc
29 open MatitaTypes
30
31 (* List utility functions *)
32 exception Skip
33
34 let list_map_fail f =
35  let rec aux =
36   function
37      [] -> []
38    | he::tl ->
39       try
40        let he' = f he in
41         he'::(aux tl)
42       with Skip ->
43        (aux tl)
44  in
45   aux
46
47 class clickable_math_view obj =
48   let href = Gdome.domString "href" in
49   let xref = Gdome.domString "xref" in
50   object (self)
51     inherit GMathViewAux.multi_selection_math_view obj
52
53     val mutable href_callback: (string -> unit) option = None
54     method set_href_callback f = href_callback <- f
55
56     initializer
57       ignore (self#connect#selection_changed self#choose_selection);
58       ignore (self#connect#click (fun (gdome_elt, _, _, _) ->
59         match gdome_elt with
60         | Some elt  (* element is an hyperlink, use href_callback on it *)
61           when elt#hasAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href ->
62             (match href_callback with
63             | None -> ()
64             | Some f ->
65                 let uri =
66                   elt#getAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href
67                 in
68                 f (uri#to_string))
69         | Some elt -> ignore (self#action_toggle elt)
70         | None -> ()))
71     method private choose_selection gdome_elt =
72       let rec aux elt =
73         if elt#hasAttributeNS ~namespaceURI:Misc.helm_ns ~localName:xref then
74           self#set_selection (Some elt)
75         else
76           try
77             (match elt#get_parentNode with
78             | None -> assert false
79             | Some p -> aux (new Gdome.element_of_node p))
80           with GdomeInit.DOMCastException _ -> ()
81 (*             debug_print "trying to select above the document root" *)
82       in
83       match gdome_elt with
84       | Some elt -> aux elt
85       | None   -> self#set_selection None
86   end
87
88 let clickable_math_view ?hadjustment ?vadjustment ?font_size ?log_verbosity =
89   GtkBase.Widget.size_params
90     ~cont:(OgtkMathViewProps.pack_return (fun p ->
91       OgtkMathViewProps.set_params
92         (new clickable_math_view (GtkMathViewProps.MathView_GMetaDOM.create p))
93         ~font_size:None ~log_verbosity:None))
94     []
95
96 class sequent_viewer obj =
97   object(self)
98
99     inherit clickable_math_view obj
100
101     val mutable current_infos = None
102
103     method get_selected_terms =
104       let selections = self#get_selections in
105       list_map_fail
106         (fun node ->
107           let xpath =
108             ((node : Gdome.element)#getAttributeNS
109               ~namespaceURI:Misc.helm_ns
110               ~localName:(Gdome.domString "xref"))#to_string
111           in
112           if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
113           else
114             match current_infos with
115             | Some (ids_to_terms,_,_) ->
116                 (try
117                   Hashtbl.find ids_to_terms xpath
118                  with _ -> raise Skip)
119             | None -> assert false) (* "ERROR: No current term!!!" *)
120         selections
121
122     method get_selected_hypotheses =
123       let selections = self#get_selections in
124       list_map_fail
125         (fun node ->
126           let xpath =
127             ((node : Gdome.element)#getAttributeNS
128               ~namespaceURI:Misc.helm_ns
129               ~localName:(Gdome.domString "xref"))#to_string
130           in
131           if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
132           else
133             match current_infos with
134             | Some (_,_,ids_to_hypotheses) ->
135                 (try
136                   Hashtbl.find ids_to_hypotheses xpath
137                 with _ -> raise Skip)
138             | None -> assert false) (* "ERROR: No current term!!!" *)
139         selections
140   
141   method load_sequent metasenv metano =
142     let sequent = CicUtil.lookup_meta metano metasenv in
143     let (mathml,(_,(ids_to_terms, ids_to_father_ids, ids_to_hypotheses,_))) =
144       ApplyTransformation.mml_of_cic_sequent metasenv sequent
145     in
146     current_infos <- Some (ids_to_terms, ids_to_father_ids, ids_to_hypotheses);
147 (*
148     debug_print "load_sequent: dumping MathML to ./prova";
149     ignore (Misc.domImpl#saveDocumentToFile ~name:"./prova" ~doc:mathml ());
150 *)
151     self#load_root ~root:mathml#get_documentElement
152  end
153
154
155 class sequents_viewer ~(notebook:GPack.notebook)
156   ~(sequent_viewer:sequent_viewer) ()
157 =
158   let tab_label metano =
159     (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
160   in
161   let set_goal goal =
162     let currentProof = MatitaProof.instance () in
163     assert (currentProof#onGoing ());
164     currentProof#proof#set_goal goal
165   in
166   object (self)
167     val mutable pages = 0
168     val mutable switch_page_callback = None
169     val mutable page2goal = []  (* associative list: page no -> goal no *)
170     val mutable goal2page = []  (* the other way round *)
171     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
172     val mutable _metasenv = []
173     val mutable scrolledWin: GBin.scrolled_window option = None
174       (* scrolled window to which the sequent_viewer is currently attached *)
175
176     method reset =
177       (match scrolledWin with
178       | Some w ->
179           (* removing page from the notebook will destroy all contained widget,
180           * we do not want the sequent_viewer to be destroyed as well *)
181           w#remove sequent_viewer#coerce;
182           scrolledWin <- None
183       | None -> ());
184       for i = 1 to pages do notebook#remove_page 0 done;
185       pages <- 0;
186       page2goal <- [];
187       goal2page <- [];
188       goal2win <- [];
189       _metasenv <- [];
190       (match switch_page_callback with
191       | Some id ->
192           GtkSignal.disconnect notebook#as_widget id;
193           switch_page_callback <- None
194       | None -> ())
195
196     method load_sequents metasenv =
197       let sequents_no = List.length metasenv in
198       _metasenv <- metasenv;
199       pages <- sequents_no;
200       let win metano =
201         let w =
202           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC
203             ~shadow_type:`IN ~show:true ()
204         in
205         let reparent () =
206           scrolledWin <- Some w;
207           match sequent_viewer#misc#parent with
208           | None -> w#add sequent_viewer#coerce
209           | Some _ -> sequent_viewer#misc#reparent w#coerce
210         in
211         goal2win <- (metano, reparent) :: goal2win;
212         w#coerce
213       in
214       let page = ref 0 in
215       List.iter
216         (fun (metano, _, _) ->
217           page2goal <- (!page, metano) :: page2goal;
218           goal2page <- (metano, !page) :: goal2page;
219           incr page;
220           notebook#append_page ~tab_label:(tab_label metano) (win metano))
221         metasenv;
222       switch_page_callback <-
223         Some (notebook#connect#switch_page ~callback:(fun page ->
224           let goal =
225             try
226               List.assoc page page2goal
227             with Not_found -> assert false
228           in
229           set_goal goal;
230           self#render_page ~page ~goal))
231
232     method private render_page ~page ~goal =
233       sequent_viewer#load_sequent _metasenv goal;
234       try
235         List.assoc goal goal2win ();
236         sequent_viewer#set_selection None
237       with Not_found -> assert false
238
239     method goto_sequent goal =
240       let page =
241         try
242           List.assoc goal goal2page
243         with Not_found -> assert false
244       in
245       notebook#goto_page page;
246       self#render_page page goal
247
248   end
249
250  (** constructors *)
251
252 type 'widget constructor =
253   ?hadjustment:GData.adjustment ->
254   ?vadjustment:GData.adjustment ->
255   ?font_size:int ->
256   ?log_verbosity:int ->
257   ?width:int ->
258   ?height:int ->
259   ?packing:(GObj.widget -> unit) ->
260   ?show:bool ->
261   unit ->
262     'widget
263
264 let sequent_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
265   GtkBase.Widget.size_params
266     ~cont:(OgtkMathViewProps.pack_return (fun p ->
267       OgtkMathViewProps.set_params
268         (new sequent_viewer (GtkMathViewProps.MathView_GMetaDOM.create p))
269         ~font_size ~log_verbosity))
270     []
271
272 let blank_uri = BuildTimeConf.blank_uri
273 let current_proof_uri = BuildTimeConf.current_proof_uri
274
275 exception Browser_failure of string
276
277 let cicBrowsers = ref []
278
279 class cicBrowser ~(history:string MatitaMisc.history) () =
280   let term_RE = Pcre.regexp "^term:(.*)" in
281   let trailing_slash_RE = Pcre.regexp "/$" in
282   let gui = MatitaGui.instance () in
283   let win = gui#newBrowserWin () in
284   let toplevel = win#toplevel in
285   let mathView = sequent_viewer ~packing:win#scrolledBrowser#add () in
286   let fail msg =
287     ignore (MatitaGtkMisc.ask_confirmation ~gui:(MatitaGui.instance ())
288       ~title:"Cic browser" ~msg ~cancel:false ());
289   in
290   let handle_error f =
291     try
292       f ()
293     with exn ->
294       fail (sprintf "Uncaught exception:\n%s" (Printexc.to_string exn))
295   in
296   let handle_error' f = fun () -> handle_error f in  (* used in callbacks *)
297   object (self)
298     initializer
299       ignore (win#browserUri#connect#activate (handle_error' (fun () ->
300         self#_loadUri win#browserUri#text)));
301       ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
302         self#_loadUri current_proof_uri)));
303       ignore (win#browserRefreshButton#connect#clicked
304         (handle_error' self#refresh));
305       ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
306       ignore (win#browserForwardButton#connect#clicked
307         (handle_error' self#forward));
308       ignore (win#toplevel#event#connect#delete (fun _ ->
309         let my_id = Oo.id self in
310         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
311         if !cicBrowsers = [] &&
312           Helm_registry.get "matita.mode" = "cicbrowser"
313         then
314           GMain.quit ();
315         false));
316       mathView#set_href_callback (Some (fun uri ->
317         handle_error (fun () -> self#_loadUri uri)));
318       self#_loadUri ~add_to_history:false blank_uri;
319       toplevel#show ();
320
321     val disambiguator = MatitaDisambiguator.instance ()
322     val currentProof = MatitaProof.instance ()
323
324     val mutable current_uri = ""
325     val mutable current_infos = None
326     val mutable current_mathml = None
327
328     method private back () =
329       try
330         self#_loadUri ~add_to_history:false history#previous
331       with MatitaMisc.History_failure -> ()
332
333     method private forward () =
334       try
335         self#_loadUri ~add_to_history:false history#next
336       with MatitaMisc.History_failure -> ()
337
338       (* loads a uri which can be a cic uri or an about:* uri
339       * @param uri string *)
340     method private _loadUri ?(add_to_history = true) uri =
341       try
342         if current_uri <> uri || uri = current_proof_uri then begin
343           (match uri with
344           | uri when uri = blank_uri -> self#blank ()
345           | uri when uri = current_proof_uri -> self#home ()
346           | uri when Pcre.pmatch ~rex:term_RE uri ->
347               self#loadTerm (`String (Pcre.extract ~rex:term_RE uri).(1))
348           | uri when Pcre.pmatch ~rex:trailing_slash_RE uri -> self#loadDir uri
349           | _ -> self#loadUriManagerUri (UriManager.uri_of_string uri));
350           self#setUri uri;
351           if add_to_history then history#add uri
352         end
353       with
354       | UriManager.IllFormedUri _ -> fail (sprintf "invalid uri: %s" uri)
355       | CicEnvironment.Object_not_found _ ->
356           fail (sprintf "object not found: %s" uri)
357       | Browser_failure msg -> fail msg
358
359     method loadUri uri =
360       handle_error (fun () -> self#_loadUri ~add_to_history:true uri)
361
362     method private blank () =
363       mathView#load_root (MatitaMisc.empty_mathml ())#get_documentElement
364
365     method private home () =
366       if currentProof#onGoing () then
367         self#loadObj (cicCurrentProof currentProof#proof#proof)
368       else
369         raise (Browser_failure "no on going proof")
370
371       (** loads a cic uri from the environment
372       * @param uri UriManager.uri *)
373     method private loadUriManagerUri uri =
374       let uri = UriManager.strip_xpointer uri in
375       let (obj, _) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
376       self#loadObj obj
377
378     method private loadDir dir =
379       let mathml = MatitaMisc.empty_boxml () in
380       let content = Http_getter.ls dir in
381       let root = mathml#get_documentElement in
382       let new_box_elt name =
383         mathml#createElementNS ~namespaceURI:(Some Misc.boxml_ns)
384           ~qualifiedName:(Gdome.domString ("b:" ^ name))
385       in
386       let new_text content = mathml#createTextNode (Gdome.domString content) in
387       let b_v = new_box_elt "v" in
388       List.iter
389         (fun item ->
390           let b_text = new_box_elt "text" in
391           let uri, elt =
392             match item with
393             | Http_getter_types.Ls_section subdir ->
394                 (dir ^ subdir ^ "/"), (new_text (subdir ^ "/"))
395             | Http_getter_types.Ls_object obj ->
396                 (dir ^ obj.Http_getter_types.uri),
397                 (new_text obj.Http_getter_types.uri)
398           in
399           b_text#setAttributeNS ~namespaceURI:(Some Misc.xlink_ns)
400             ~qualifiedName:(Gdome.domString "xlink:href")
401             ~value:(Gdome.domString uri);
402           ignore (b_v#appendChild ~newChild:(b_text :> Gdome.node));
403           ignore (b_text#appendChild ~newChild:(elt :> Gdome.node)))
404         content;
405       ignore (root#appendChild ~newChild:(b_v :> Gdome.node));
406 (*       Misc.domImpl#saveDocumentToFile ~doc:mathml ~name:"pippo" (); *)
407       mathView#load_root ~root:root
408
409     method private setUri uri =
410         win#browserUri#set_text uri;
411         current_uri <- uri
412
413     method private loadObj obj =
414       let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *)
415       let (mathml, (_,(ids_to_terms, ids_to_father_ids, ids_to_conjectures,
416            ids_to_hypotheses,_,_))) =
417         ApplyTransformation.mml_of_cic_object obj
418       in
419       current_infos <- Some (ids_to_terms, ids_to_father_ids,
420         ids_to_conjectures, ids_to_hypotheses);
421       match current_mathml with
422       | Some current_mathml when use_diff ->
423           mathView#freeze;
424           XmlDiff.update_dom ~from:current_mathml mathml;
425           mathView#thaw
426       |  _ ->
427           mathView#load_root ~root:mathml#get_documentElement;
428           current_mathml <- Some mathml
429
430     method private _loadTerm s =
431       self#_loadTermAst (disambiguator#parserr#parseTerm (Stream.of_string s))
432
433     method private _loadTermAst ast =
434       let (_, _, term, _) =
435         MatitaCicMisc.disambiguate ~disambiguator ~currentProof ast
436       in
437       self#_loadTermCic term
438
439     method private _loadTermCic term =
440       let (context, metasenv) =
441         MatitaCicMisc.get_context_and_metasenv currentProof
442       in
443       let dummyno = CicMkImplicit.new_meta metasenv [] in
444       let sequent = (dummyno, context, term) in
445       mathView#load_sequent (sequent :: metasenv) dummyno
446
447     method loadTerm (src:MatitaTypes.term_source) =
448       handle_error (fun () ->
449         (match src with
450         | `Ast ast -> self#_loadTermAst ast
451         | `Cic cic -> self#_loadTermCic cic
452         | `String s -> self#_loadTerm s);
453         self#setUri "check")
454
455       (** {2 methods used by constructor only} *)
456
457     method win = win
458     method history = history
459     method currentUri = current_uri
460     method refresh () =
461       if current_uri = current_proof_uri then
462       self#_loadUri ~add_to_history:false current_proof_uri
463
464   end
465
466 let sequents_viewer ~(notebook:GPack.notebook)
467   ~(sequent_viewer:sequent_viewer) ()
468 =
469   new sequents_viewer ~notebook ~sequent_viewer ()
470
471 let cicBrowser () =
472   let size = BuildTimeConf.browser_history_size in
473   let rec aux history =
474     let browser = new cicBrowser ~history () in
475     let win = browser#win in
476     ignore (win#browserNewButton#connect#clicked (fun () ->
477       let history =
478         new MatitaMisc.browser_history ~memento:history#save size ""
479       in
480       let newBrowser = aux history in
481       newBrowser#loadUri browser#currentUri));
482 (*
483       (* attempt (failed) to close windows on CTRL-W ... *)
484     MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
485       GdkKeysyms._W (fun () -> win#toplevel#destroy ());
486 *)
487     cicBrowsers := browser :: !cicBrowsers;
488     (browser :> MatitaTypes.cicBrowser)
489   in
490   let history = new MatitaMisc.browser_history size blank_uri in
491   aux history
492
493 let refresh_all_browsers () = List.iter (fun b -> b#refresh ()) !cicBrowsers
494
495 class mathViewer =
496   object
497     method checkTerm (src:MatitaTypes.term_source) =
498       (cicBrowser ())#loadTerm src
499   end
500
501 let mathViewer () = new mathViewer
502
503 let default_sequent_viewer () = sequent_viewer ~show:true ()
504 let sequent_viewer_instance = MatitaMisc.singleton default_sequent_viewer
505
506 let default_sequents_viewer () =
507   let gui = MatitaGui.instance () in
508   let sequent_viewer = sequent_viewer_instance () in
509   sequents_viewer ~notebook:gui#main#sequentsNotebook ~sequent_viewer ()
510 let sequents_viewer_instance = MatitaMisc.singleton default_sequents_viewer
511