]> matita.cs.unibo.it Git - helm.git/blob - helm/annotationHelper/cicAnnotationHelper.ml
ocaml 3.09 transition
[helm.git] / helm / annotationHelper / cicAnnotationHelper.ml
1 (* Copyright (C) 2000, 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 (******************************************************************************)
27 (*                                                                            *)
28 (*                               PROJECT HELM                                 *)
29 (*                                                                            *)
30 (*                Claudio Sacerdoti Coen <sacerdot@cs.unibo.it>               *)
31 (*                                 03/04/2001                                 *)
32 (*                                                                            *)
33 (* This is a simple gtk interface to the Coq-like pretty printer cicPp for    *)
34 (* cic terms exported in xml. It uses directly the modules cicPp and          *)
35 (* cicCcache and indirectly all the other modules (cicParser, cicParser2,     *)
36 (* cicParser3, getter).                                                       *)
37 (* The syntax is  "gtkInterface[.opt] filename1 ... filenamen" where          *)
38 (* filenamei is the path-name of an xml file describing a cic term.           *)
39 (* The terms are loaded in cache and then pretty-printed one at a time and    *)
40 (* only once, when the user wants to look at it: if the user wants to look at *)
41 (* a term again, then the pretty-printed term is showed again, but not        *)
42 (* recomputed                                                                 *)
43 (*                                                                            *)
44 (******************************************************************************)
45
46 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
47
48 let annotated_obj = ref None;;      (* reference to a triple option where    *)
49                                     (* the first component is the current    *)
50                                     (* annotated object, the second is the   *)
51                                     (* map from ids to annotated targets and *)
52                                     (* the third is the map from ids to      *)
53                                     (* annotations.                          *)
54 let current_id = ref None;;         (* id of the element to annotate *)
55 let radio_some_status = ref false;; (* is the radio_some button selected? *)
56 let current_url = ref "";;
57
58 (* GLOBAL CONSTANTS *)
59
60 let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
61
62 (* MISC FUNCTIONS *)
63
64 let pathname_of_annuri uristring =
65  Configuration.annotations_dir ^
66   Str.replace_first (Str.regexp "^cic:") "" uristring
67 ;;
68
69 let make_dirs dirpath =
70  ignore (Unix.system ("mkdir -p " ^ dirpath))
71 ;;
72
73 module UrlManipulator =
74  struct
75   exception No_param_dot_CICURI_or_param_dot_annotations_found_in of string;;
76   exception No_param_found_in of string * string;;
77   exception Bad_formed_url of string;;
78
79   let uri_from_url url =
80    let module N = Neturl in
81    let founduri = ref None in
82    let foundann = ref None in
83     let rec find_uri =
84      function
85         [] -> raise (No_param_dot_CICURI_or_param_dot_annotations_found_in url)
86       | he::tl ->
87          match Str.split (Str.regexp "=") he with
88             ["param.CICURI";uri] ->
89               if !founduri <> None then
90                raise (Bad_formed_url url)
91               else
92                begin
93                 founduri := Some uri ;
94                 if !foundann = None then
95                  find_uri tl
96                end
97           | ["param.annotations";ann] ->
98               if !foundann <> None then
99                raise (Bad_formed_url url)
100               else
101                begin
102                 foundann :=
103                  Some
104                   (match ann with
105                       "yes" -> ".ann"
106                     | "no"  -> ""
107                     | _     -> raise (Bad_formed_url url)
108                   ) ;
109                 if !founduri = None then
110                  find_uri tl
111                end
112           | _ -> find_uri tl
113     in
114      find_uri
115       (Str.split (Str.regexp "&")
116        (N.url_query ~encoded:true (N.url_of_string N.ip_url_syntax url))) ;
117      match !founduri,!foundann with
118         (Some uri),(Some ann) -> uri ^ ann
119       | _         , _         ->
120          raise (No_param_dot_CICURI_or_param_dot_annotations_found_in url)
121   ;;
122
123   let extractParam param url =
124    let module N = Neturl in
125     let rec find_param =
126      function
127         [] -> raise (No_param_found_in (param,url))
128       | he::tl ->
129          match Str.split (Str.regexp "=") he with
130             [name;value] when name = param -> value
131           | _ -> find_param tl
132     in
133      find_param
134       (Str.split (Str.regexp "&")
135        (N.url_query ~encoded:true (N.url_of_string N.ip_url_syntax url)))
136   ;;
137
138   let set_annotations_to_yes query url =
139    let found =ref false in
140    let rec aux =
141     function
142        [] ->
143         if !found then ""
144         else raise (No_param_found_in ("param.annotations",url))
145      | he::tl ->
146         match Str.split (Str.regexp "=") he with
147            ["param.annotations" as s ; ann] ->
148              found := true ;
149              let auxtl = aux tl in
150               s ^ "=yes" ^
151                (if auxtl = "" then "" else "&" ^ auxtl)
152          | [name ; value] ->
153             let auxtl = aux tl in
154              name ^ "=" ^ value ^
155               (if auxtl = "" then "" else "&" ^ auxtl)
156          | [name] ->
157             let auxtl = aux tl in
158              name ^ "=" ^
159               (if auxtl = "" then "" else "&" ^ auxtl)
160          | _ -> raise (Bad_formed_url url)
161    in
162     aux (Str.split (Str.regexp "&") query)
163   ;;
164
165   let annurl_of_url url =
166    let module N = Neturl in
167     let nurl = N.url_of_string N.ip_url_syntax url in
168      let query = N.url_query ~encoded:true nurl in
169      let newquery = set_annotations_to_yes query url in
170       N.string_of_url (N.modify_url ~encoded:true ~query:newquery nurl)
171   ;;
172 end
173
174 let get_current_uri () =
175  UriManager.uri_of_string (UrlManipulator.uri_from_url !current_url)
176 ;;
177
178 (* CALLBACKS *)
179
180 let get_annotated_obj () =
181  match !annotated_obj with
182     None   ->
183      let annobj =
184       let (annobj,ids_to_annotations) =
185        match CicCache.get_annobj (get_current_uri ()) with
186           (annobj,None) -> annobj, Hashtbl.create 503
187         | (annobj, Some ids_to_annotations) -> (annobj,ids_to_annotations)
188       in
189        let ids_to_targets = CicXPath.get_ids_to_targets annobj in
190         (annobj,ids_to_targets,ids_to_annotations)
191      in
192       annotated_obj := Some annobj ;
193       annobj
194   | Some annobj -> annobj
195 ;;
196
197 let update_output rendering_window url =
198  rendering_window#label#set_text (UrlManipulator.uri_from_url url) ;
199  rendering_window#output#load url
200 ;;
201
202 let choose_selection rendering_window (element : Gdome.element option) =
203  let module G = Gdome in
204   let rec aux element =
205    if element#hasAttributeNS
206        ~namespaceURI:helmns
207        ~localName:(G.domString "xref")
208    then
209      rendering_window#output#set_selection (Some element)
210    else
211       match element#get_parentNode with
212          None -> assert false
213        (*CSC: OCAML DIVERGES!
214        | Some p -> aux (new G.element_of_node p)
215        *)
216        | Some p -> aux (new Gdome.element_of_node p)
217   in
218    match element with
219      Some x -> aux x
220    | None   -> rendering_window#output#set_selection None
221 ;;
222
223 let annotateb_pressed rendering_window annotation_window () =
224  let module G = Gdome in
225  match rendering_window#output#get_selection with
226    Some element ->
227     let xpath =
228      ((element : Gdome.element)#getAttributeNS
229      (*CSC: OCAML DIVERGE
230      ((element : G.element)#getAttributeNS
231      *)
232        ~namespaceURI:helmns
233        ~localName:(G.domString "xref"))#to_string
234     in
235      if xpath = "" then
236       rendering_window#label#set_text ("ERROR: No xref found!!!\n")
237      else
238       let annobj = get_annotated_obj () in
239       let (anno, ids_to_targets, ids_to_annotations) = annobj in
240       let annotation = (annotation_window#annotation : GEdit.text) in
241       let id = xpath in
242        current_id := Some id ;
243        let ann = CicXPath.get_annotation ids_to_annotations id in
244         CicAnnotationHinter.create_hints annotation_window ids_to_targets
245          xpath ;
246         annotation#delete_text 0 annotation#length ;
247         begin
248          match ann with
249              None      ->
250               annotation#misc#set_sensitive false ;
251               annotation_window#radio_none#set_active true ;
252               radio_some_status := false
253            | Some ann' ->
254               annotation#insert ann' ;
255               annotation#misc#set_sensitive true ;
256               annotation_window#radio_some#set_active true ;
257               radio_some_status := true
258         end ;
259         GMain.Grab.add (annotation_window#window_to_annotate#coerce) ;
260         annotation_window#show () ;
261  | None -> rendering_window#label#set_text ("ERROR: No selection!!!\n")
262 ;;
263
264 let change_annotation ids_to_annotations id ann =
265  begin
266   try
267    Hashtbl.remove ids_to_annotations id
268   with
269    Not_found -> ()
270  end ;
271  match ann with
272     None -> ()
273   | Some ann' -> Hashtbl.add ids_to_annotations id ann'
274 ;;
275
276 (* called when the annotation is confirmed *)
277 let save_annotation (annotation : GEdit.text) =
278  let module S = Str in
279  let module U = UriManager in
280   let (annobj,ids_to_annotations) =
281    match !annotated_obj with
282       None -> assert false
283     | Some (annobj,_,ids_to_annotations) -> annobj,ids_to_annotations
284   in
285    change_annotation ids_to_annotations
286     (match !current_id with
287         Some id -> id
288       | None -> assert false
289     )
290     (if !radio_some_status then
291       Some (annotation#get_chars 0 annotation#length)
292      else
293       None
294     ) ;
295    let uri = get_current_uri () in
296     let annxml =
297      CicAnnotation2Xml.pp_annotation annobj ids_to_annotations uri
298     in
299      make_dirs
300        (pathname_of_annuri (U.buri_of_uri uri)) ;
301      Xml.pp ~quiet:true annxml
302       (Some
303        (pathname_of_annuri (U.string_of_uri (U.annuri_of_uri uri)) ^
304         ".xml"
305        )
306       )
307 ;;
308
309 (* STUFF TO BUILD THE GTK INTERFACE *)
310
311 (* Stuff for the widget settings *)
312
313 let export_to_postscript (output : GMathView.math_view) () =
314  output#export_to_postscript ~filename:"output.ps" ();
315 ;;
316
317 let activate_t1 (output : GMathView.math_view)
318  button_set_anti_aliasing button_set_kerning 
319  button_set_transparency button_export_to_postscript button_t1 ()
320 =
321  let is_set = button_t1#active in
322   output#set_font_manager_type
323    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
324   if is_set then
325    begin
326     button_set_anti_aliasing#misc#set_sensitive true ;
327     button_set_kerning#misc#set_sensitive true ;
328     button_set_transparency#misc#set_sensitive true ;
329     button_export_to_postscript#misc#set_sensitive true ;
330    end
331   else
332    begin
333     button_set_anti_aliasing#misc#set_sensitive false ;
334     button_set_kerning#misc#set_sensitive false ;
335     button_set_transparency#misc#set_sensitive false ;
336     button_export_to_postscript#misc#set_sensitive false ;
337    end
338 ;;
339
340 let set_anti_aliasing output button_set_anti_aliasing () =
341  output#set_anti_aliasing button_set_anti_aliasing#active
342 ;;
343
344 let set_kerning output button_set_kerning () =
345  output#set_kerning button_set_kerning#active
346 ;;
347
348 let set_transparency output button_set_transparency () =
349  output#set_transparency button_set_transparency#active
350 ;;
351
352 let changefont output font_size_spinb () =
353  output#set_font_size font_size_spinb#value_as_int
354 ;;
355
356 let set_log_verbosity output log_verbosity_spinb () =
357  output#set_log_verbosity log_verbosity_spinb#value_as_int
358 ;;
359
360 class settings_window (output : GMathView.math_view)
361  sw button_export_to_postscript selection_changed_callback
362 =
363  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
364  let vbox =
365   GPack.vbox ~packing:settings_window#add () in
366  let table =
367   GPack.table
368    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
369    ~border_width:5 ~packing:vbox#add () in
370  let button_t1 =
371   GButton.toggle_button ~label:"activate t1 fonts"
372    ~packing:(table#attach ~left:0 ~top:0) () in
373  let button_set_anti_aliasing =
374   GButton.toggle_button ~label:"set_anti_aliasing"
375    ~packing:(table#attach ~left:0 ~top:1) () in
376  let button_set_kerning =
377   GButton.toggle_button ~label:"set_kerning"
378    ~packing:(table#attach ~left:1 ~top:1) () in
379  let button_set_transparency =
380   GButton.toggle_button ~label:"set_transparency"
381    ~packing:(table#attach ~left:2 ~top:1) () in
382  let table =
383   GPack.table
384    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
385    ~border_width:5 ~packing:vbox#add () in
386  let font_size_label =
387   GMisc.label ~text:"font size:"
388    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
389  let font_size_spinb =
390   let sadj =
391    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
392   in
393    GEdit.spin_button 
394     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
395  let log_verbosity_label =
396   GMisc.label ~text:"log verbosity:"
397    ~packing:(table#attach ~left:0 ~top:1) () in
398  let log_verbosity_spinb =
399   let sadj =
400    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
401   in
402    GEdit.spin_button 
403     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
404  let hbox =
405   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
406  let closeb =
407   GButton.button ~label:"Close"
408    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
409 object(self)
410  method show = settings_window#show
411  initializer
412   button_set_anti_aliasing#misc#set_sensitive false ;
413   button_set_kerning#misc#set_sensitive false ;
414   button_set_transparency#misc#set_sensitive false ;
415   (* Signals connection *)
416   ignore(button_t1#connect#clicked
417    ~callback:(activate_t1 output button_set_anti_aliasing button_set_kerning
418     button_set_transparency button_export_to_postscript button_t1)) ;
419   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
420   ignore(button_set_anti_aliasing#connect#toggled
421    (set_anti_aliasing output button_set_anti_aliasing));
422   ignore(button_set_kerning#connect#toggled
423    (set_kerning output button_set_kerning)) ;
424   ignore(button_set_transparency#connect#toggled
425    (set_transparency output button_set_transparency)) ;
426   ignore(log_verbosity_spinb#connect#changed
427    (set_log_verbosity output log_verbosity_spinb)) ;
428   ignore(closeb#connect#clicked ~callback:settings_window#misc#hide)
429 end;;
430
431 (* Main windows *)
432
433 class annotation_window output label =
434  let window_to_annotate =
435   GWindow.window ~title:"Annotating environment" ~border_width:2 () in
436  let hbox1 =
437   GPack.hbox ~packing:window_to_annotate#add () in
438  let vbox1 =
439   GPack.vbox ~packing:(hbox1#pack ~padding:5) () in
440  let hbox2 =
441   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
442  let radio_some = GButton.radio_button ~label:"Annotation below"
443   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
444  let radio_none = GButton.radio_button ~label:"No annotation"
445   ~group:radio_some#group
446   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5)
447   ~active:true () in
448  let annotation = GEdit.text ~editable:true ~width:400 ~height:180
449   ~packing:(vbox1#pack ~padding:5) () in
450  let table =
451   GPack.table ~rows:3 ~columns:3 ~packing:(vbox1#pack ~padding:5) () in
452  let annotation_hints =
453   Array.init 9
454    (function i ->
455      GButton.button ~label:("Hint " ^ string_of_int i)
456       ~packing:(table#attach ~left:(i mod 3) ~top:(i / 3)) ()
457    ) in
458  let vbox2 =
459   GPack.vbox ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
460  let confirmb =
461   GButton.button ~label:"O.K."
462    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
463  let abortb =
464   GButton.button ~label:"Abort"
465    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
466 object (self)
467  method window_to_annotate = window_to_annotate
468  method annotation = annotation
469  method radio_some = radio_some
470  method radio_none = radio_none
471  method annotation_hints = annotation_hints
472  method output = (output : GMathView.math_view)
473  method show () = window_to_annotate#show ()
474  initializer
475   (* signal handlers here *)
476   ignore (window_to_annotate#event#connect#delete
477    (fun _ ->
478      window_to_annotate#misc#hide () ;
479      GMain.Grab.remove (window_to_annotate#coerce) ; 
480      true
481    )) ;
482   ignore (confirmb#connect#clicked
483    ~callback:(fun () ->
484      window_to_annotate#misc#hide () ;
485      save_annotation annotation ;
486      GMain.Grab.remove (window_to_annotate#coerce) ;
487      let new_current_uri = UriManager.annuri_of_uri (get_current_uri ()) in
488       Getter.register new_current_uri
489        (Configuration.annotations_url ^
490          Str.replace_first (Str.regexp "^cic:") ""
491           (UriManager.string_of_uri new_current_uri) ^ ".xml"
492        ) ;
493       let new_current_url = UrlManipulator.annurl_of_url !current_url in
494        current_url := new_current_url ;
495        label#set_text (UriManager.string_of_uri new_current_uri) ;
496        output#load new_current_url
497    )) ;
498   ignore (abortb#connect#clicked
499    ~callback:(fun () ->
500      window_to_annotate#misc#hide () ;
501      GMain.Grab.remove (window_to_annotate#coerce)
502    ));
503   ignore (radio_some#connect#clicked
504    ~callback:(fun () -> annotation#misc#set_sensitive true ; radio_some_status := true)) ;
505   ignore (radio_none #connect#clicked
506    ~callback:(fun () ->
507      annotation#misc#set_sensitive false;
508      radio_some_status := false)
509    )
510 end;;
511
512 class rendering_window annotation_window output (label : GMisc.label) =
513  let window =
514   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
515  let vbox =
516   GPack.vbox ~packing:window#add () in
517  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
518  let scrolled_window0 =
519   GBin.scrolled_window ~border_width:10
520    ~packing:(vbox#pack ~expand:true ~padding:5) () in
521  let _ = scrolled_window0#add output#coerce in
522  let hbox =
523   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
524  let annotateb =
525   GButton.button ~label:"Annotate"
526    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
527  let settingsb =
528   GButton.button ~label:"Settings"
529    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
530  let button_export_to_postscript =
531   GButton.button ~label:"export_to_postscript"
532   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
533  let closeb =
534   GButton.button ~label:"Close"
535    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
536 object(self)
537  method label = label
538  method output = (output : GMathView.math_view)
539  method show () = window#show ()
540  initializer
541   button_export_to_postscript#misc#set_sensitive false ;
542
543   (* signal handlers here *)
544   ignore(output#connect#selection_changed (choose_selection self)) ;
545   ignore(closeb#connect#clicked ~callback:(fun _ -> GMain.Main.quit ())) ;
546   ignore(annotateb#connect#clicked
547    ~callback:(annotateb_pressed self annotation_window)) ;
548   let settings_window = new settings_window output scrolled_window0
549    button_export_to_postscript (choose_selection self) in
550   ignore(settingsb#connect#clicked ~callback:settings_window#show) ;
551   ignore(button_export_to_postscript#connect#clicked ~callback:(export_to_postscript output)) ;
552   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true ))
553 end;;
554
555 (* MAIN *)
556
557 let initialize_everything tmpfile url =
558  let module U = Unix in
559   let output = GMathView.math_view ~width:400 ~height:380 ()
560    and label = GMisc.label ~text:"???" () in
561     let annotation_window = new annotation_window output label in
562     let rendering_window =
563      new rendering_window annotation_window output label
564     in
565      rendering_window#show () ;
566      rendering_window#label#set_text (UrlManipulator.uri_from_url url) ;
567      rendering_window#output#load tmpfile ;
568      GMain.Main.main ()
569 ;;
570
571 let _ =
572  let filename = ref "" in
573  let usage_msg =
574    "\nusage: annotationHelper[.opt] file url\n\n List of options:"
575  in
576   Arg.parse []
577    (fun x ->
578      if x = "" then raise (Arg.Bad "Empty filename or URL not allowed") ;
579      if !filename = "" then
580       filename := x
581      else if !current_url = "" then
582       current_url := x
583      else
584       begin
585        prerr_string "More than two arguments provided\n" ;
586        Arg.usage [] usage_msg ;
587        exit (-1)
588       end
589    ) usage_msg ;
590    Getter.getter_url :=
591     Netencoding.Url.decode
592      (UrlManipulator.extractParam "param.getterURL" !current_url) ;
593    initialize_everything !filename !current_url
594 ;;