]> matita.cs.unibo.it Git - helm.git/blob - helm/matita/matitaMathView.ml
added support for directory browsing in cicBrowser
[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 (*
143     let (annconjecture, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
144         ids_to_hypotheses) =
145       Cic2acic.asequent_of_sequent metasenv conjecture
146     in
147 *)
148     let sequent = CicUtil.lookup_meta metano metasenv in
149     let (mathml,(_,(ids_to_terms, ids_to_father_ids, ids_to_hypotheses,_))) =
150       ApplyTransformation.mml_of_cic_sequent metasenv sequent
151     in
152     current_infos <- Some (ids_to_terms, ids_to_father_ids, ids_to_hypotheses);
153     debug_print "load_sequent: dumping MathML to ./prova";
154     ignore (Misc.domImpl#saveDocumentToFile ~name:"./prova" ~doc:mathml ());
155     self#load_root ~root:mathml#get_documentElement
156  end
157
158
159 class sequents_viewer ~(notebook:GPack.notebook)
160   ~(sequent_viewer:sequent_viewer) ~set_goal ()
161 =
162   let tab_label metano =
163     (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
164   in
165   object (self)
166     val mutable pages = 0
167     val mutable switch_page_callback = None
168     val mutable page2goal = []  (* associative list: page no -> goal no *)
169     val mutable goal2page = []  (* the other way round *)
170     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
171     val mutable _metasenv = []
172
173     method reset =
174       for i = 1 to pages do notebook#remove_page 0 done;
175       pages <- 0;
176       page2goal <- [];
177       goal2page <- [];
178       goal2win <- [];
179       _metasenv <- [];
180       (match switch_page_callback with
181       | Some id ->
182           GtkSignal.disconnect notebook#as_widget id;
183           switch_page_callback <- None
184       | None -> ())
185
186     method load_sequents metasenv =
187       let sequents_no = List.length metasenv in
188       _metasenv <- metasenv;
189       pages <- sequents_no;
190       let win metano =
191         let w =
192           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC
193             ~shadow_type:`IN ~show:true ()
194         in
195         let reparent () =
196           match sequent_viewer#misc#parent with
197           | None -> w#add sequent_viewer#coerce
198           | Some _ -> sequent_viewer#misc#reparent w#coerce
199         in
200         goal2win <- (metano, reparent) :: goal2win;
201         w#coerce
202       in
203       let page = ref 0 in
204       List.iter
205         (fun (metano, _, _) ->
206           page2goal <- (!page, metano) :: page2goal;
207           goal2page <- (metano, !page) :: goal2page;
208           incr page;
209           notebook#append_page ~tab_label:(tab_label metano) (win metano))
210         metasenv;
211       switch_page_callback <-
212         Some (notebook#connect#switch_page ~callback:(fun page ->
213           let goal =
214             try
215               List.assoc page page2goal
216             with Not_found -> assert false
217           in
218           set_goal goal;
219           self#render_page ~page ~goal))
220
221     method private render_page ~page ~goal =
222       sequent_viewer#load_sequent _metasenv goal;
223       try
224         List.assoc goal goal2win ();
225         sequent_viewer#set_selection None
226       with Not_found -> assert false
227
228     method goto_sequent goal =
229       let page =
230         try
231           List.assoc goal goal2page
232         with Not_found -> assert false
233       in
234       notebook#goto_page page;
235       self#render_page page goal;
236
237   end
238
239  (** constructors *)
240
241 type 'widget constructor =
242   ?hadjustment:GData.adjustment ->
243   ?vadjustment:GData.adjustment ->
244   ?font_size:int ->
245   ?log_verbosity:int ->
246   ?width:int ->
247   ?height:int ->
248   ?packing:(GObj.widget -> unit) ->
249   ?show:bool ->
250   unit ->
251     'widget
252
253 let sequent_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
254   GtkBase.Widget.size_params
255     ~cont:(OgtkMathViewProps.pack_return (fun p ->
256       OgtkMathViewProps.set_params
257         (new sequent_viewer (GtkMathViewProps.MathView_GMetaDOM.create p))
258         ~font_size ~log_verbosity))
259     []
260
261 let blank_uri = BuildTimeConf.blank_uri
262 let current_proof_uri = BuildTimeConf.current_proof_uri
263
264 exception Browser_failure of string
265
266 let cicBrowsers = ref []
267
268 class cicBrowser ~(history:string MatitaMisc.history) () =
269   let term_RE = Pcre.regexp "^term:(.*)" in
270   let trailing_slash_RE = Pcre.regexp "/$" in
271   let gui = MatitaGui.instance () in
272   let win = gui#newBrowserWin () in
273   let toplevel = win#toplevel in
274   let mathView = sequent_viewer ~packing:win#scrolledBrowser#add () in
275   let fail msg =
276     ignore (MatitaGtkMisc.ask_confirmation ~gui:(MatitaGui.instance ())
277       ~title:"Cic browser" ~msg ~cancel:false ());
278   in
279   let handle_error f =
280     try
281       f ()
282     with exn ->
283       fail (sprintf "Uncaught exception:\n%s" (Printexc.to_string exn))
284   in
285   let handle_error' f = fun () -> handle_error f in  (* used in callbacks *)
286   object (self)
287     initializer
288       ignore (win#browserUri#connect#activate (handle_error' (fun () ->
289         self#_loadUri win#browserUri#text)));
290       ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
291         self#_loadUri current_proof_uri)));
292       ignore (win#browserRefreshButton#connect#clicked
293         (handle_error' self#refresh));
294       ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
295       ignore (win#browserForwardButton#connect#clicked
296         (handle_error' self#forward));
297       ignore (win#toplevel#event#connect#delete (fun _ ->
298         let my_id = Oo.id self in
299         cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
300         if !cicBrowsers = [] &&
301           Helm_registry.get "matita.mode" = "cicbrowser"
302         then
303           GMain.quit ();
304         false));
305       mathView#set_href_callback (Some (fun uri ->
306         handle_error (fun () -> self#_loadUri uri)));
307       self#_loadUri ~add_to_history:false blank_uri;
308       toplevel#show ();
309
310     val disambiguator = MatitaDisambiguator.instance ()
311     val currentProof = MatitaProof.instance ()
312
313     val mutable current_uri = ""
314     val mutable current_infos = None
315     val mutable current_mathml = None
316
317     method private back () =
318       try
319         self#_loadUri ~add_to_history:false history#previous
320       with MatitaMisc.History_failure -> ()
321
322     method private forward () =
323       try
324         self#_loadUri ~add_to_history:false history#next
325       with MatitaMisc.History_failure -> ()
326
327       (* loads a uri which can be a cic uri or an about:* uri
328       * @param uri string *)
329     method private _loadUri ?(add_to_history = true) uri =
330       try
331         if current_uri <> uri || uri = current_proof_uri then begin
332           (match uri with
333           | uri when uri = blank_uri -> self#blank ()
334           | uri when uri = current_proof_uri -> self#home ()
335           | uri when Pcre.pmatch ~rex:term_RE uri ->
336               self#loadTerm (`String (Pcre.extract ~rex:term_RE uri).(1))
337           | uri when Pcre.pmatch ~rex:trailing_slash_RE uri -> self#loadDir uri
338           | _ -> self#loadUriManagerUri (UriManager.uri_of_string uri));
339           self#setUri uri;
340           if add_to_history then history#add uri
341         end
342       with
343       | UriManager.IllFormedUri _ -> fail (sprintf "invalid uri: %s" uri)
344       | CicEnvironment.Object_not_found _ ->
345           fail (sprintf "object not found: %s" uri)
346       | Browser_failure msg -> fail msg
347
348     method loadUri uri =
349       handle_error (fun () -> self#_loadUri ~add_to_history:true uri)
350
351     method private blank () =
352       mathView#load_root (MatitaMisc.empty_mathml ())#get_documentElement
353
354     method private home () =
355       if currentProof#onGoing () then
356         self#loadObj (cicCurrentProof currentProof#proof#proof)
357       else
358         raise (Browser_failure "no on going proof")
359
360       (** loads a cic uri from the environment
361       * @param uri UriManager.uri *)
362     method private loadUriManagerUri uri =
363       let uri = UriManager.strip_xpointer uri in
364       let (obj, _) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
365       self#loadObj obj
366
367     method private loadDir dir =
368       let mathml = MatitaMisc.empty_boxml () in
369       let content = Http_getter.ls dir in
370       let root = mathml#get_documentElement in
371       let new_box_elt name =
372         mathml#createElementNS ~namespaceURI:(Some Misc.boxml_ns)
373           ~qualifiedName:(Gdome.domString ("b:" ^ name))
374       in
375       let new_text content = mathml#createTextNode (Gdome.domString content) in
376       let b_v = new_box_elt "v" in
377       List.iter
378         (fun item ->
379           let b_text = new_box_elt "text" in
380           let uri, elt =
381             match item with
382             | Http_getter_types.Ls_section subdir ->
383                 (dir ^ subdir ^ "/"), (new_text (subdir ^ "/"))
384             | Http_getter_types.Ls_object obj ->
385                 (dir ^ obj.Http_getter_types.uri),
386                 (new_text obj.Http_getter_types.uri)
387           in
388           b_text#setAttributeNS ~namespaceURI:(Some Misc.xlink_ns)
389             ~qualifiedName:(Gdome.domString "xlink:href")
390             ~value:(Gdome.domString uri);
391           ignore (b_v#appendChild ~newChild:(b_text :> Gdome.node));
392           ignore (b_text#appendChild ~newChild:(elt :> Gdome.node)))
393         content;
394       ignore (root#appendChild ~newChild:(b_v :> Gdome.node));
395 (*       Misc.domImpl#saveDocumentToFile ~doc:mathml ~name:"pippo" (); *)
396       mathView#load_root ~root:root
397
398     method private setUri uri =
399         win#browserUri#set_text uri;
400         current_uri <- uri
401
402     method private loadObj obj =
403       let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *)
404       let (mathml, (_,(ids_to_terms, ids_to_father_ids, ids_to_conjectures,
405            ids_to_hypotheses,_,_))) =
406         ApplyTransformation.mml_of_cic_object obj
407       in
408       current_infos <- Some (ids_to_terms, ids_to_father_ids,
409         ids_to_conjectures, ids_to_hypotheses);
410       match current_mathml with
411       | Some current_mathml when use_diff ->
412           mathView#freeze;
413           XmlDiff.update_dom ~from:current_mathml mathml;
414           mathView#thaw
415       |  _ ->
416           mathView#load_root ~root:mathml#get_documentElement;
417           current_mathml <- Some mathml
418
419     method private _loadTerm s =
420       self#_loadTermAst (disambiguator#parserr#parseTerm (Stream.of_string s))
421
422     method private _loadTermAst ast =
423       let (_, _, term, _) =
424         MatitaCicMisc.disambiguate ~disambiguator ~currentProof ast
425       in
426       self#_loadTermCic term
427
428     method private _loadTermCic term =
429       let (context, metasenv) =
430         MatitaCicMisc.get_context_and_metasenv currentProof
431       in
432       let dummyno = CicMkImplicit.new_meta metasenv [] in
433       let sequent = (dummyno, context, term) in
434       mathView#load_sequent (sequent :: metasenv) dummyno
435
436     method loadTerm (src:MatitaTypes.term_source) =
437       handle_error (fun () ->
438         (match src with
439         | `Ast ast -> self#_loadTermAst ast
440         | `Cic cic -> self#_loadTermCic cic
441         | `String s -> self#_loadTerm s);
442         self#setUri "check")
443
444       (** {2 methods used by constructor only} *)
445
446     method win = win
447     method history = history
448     method currentUri = current_uri
449     method refresh () =
450       if current_uri = current_proof_uri then
451       self#_loadUri ~add_to_history:false current_proof_uri
452
453   end
454
455 let sequents_viewer ~(notebook:GPack.notebook)
456   ~(sequent_viewer:sequent_viewer) ~set_goal ()
457 =
458   new sequents_viewer ~notebook ~sequent_viewer ~set_goal ()
459
460 let cicBrowser () =
461   let size = BuildTimeConf.browser_history_size in
462   let rec aux history =
463     let browser = new cicBrowser ~history () in
464     let win = browser#win in
465     ignore (win#browserNewButton#connect#clicked (fun () ->
466       let history =
467         new MatitaMisc.browser_history ~memento:history#save size ""
468       in
469       let newBrowser = aux history in
470       newBrowser#loadUri browser#currentUri));
471 (*
472       (* attempt (failed) to close windows on CTRL-W ... *)
473     MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
474       GdkKeysyms._W (fun () -> win#toplevel#destroy ());
475 *)
476     cicBrowsers := browser :: !cicBrowsers;
477     (browser :> MatitaTypes.cicBrowser)
478   in
479   let history = new MatitaMisc.browser_history size blank_uri in
480   aux history
481
482 let refresh_all_browsers () = List.iter (fun b -> b#refresh ()) !cicBrowsers
483
484 class mathViewer =
485   object
486     method checkTerm (src:MatitaTypes.term_source) =
487       (cicBrowser ())#loadTerm src
488   end
489
490 let mathViewer () = new mathViewer
491 let instance = MatitaMisc.singleton mathViewer
492