]> matita.cs.unibo.it Git - helm.git/blob - helm/interface/mmlinterface.ml
- the mathql interpreter is not helm-dependent any more
[helm.git] / helm / interface / mmlinterface.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 couple option where    *)
49                                     (* the first component is the current    *)
50                                     (* annotated object and the second is    *)
51                                     (* the map from ids to annotated targets *)
52 let ann = ref (ref None);;          (* current annotation *)
53 let radio_some_status = ref false;; (* is the radio_some button selected? *)
54 let current_url = ref "";;
55
56 (* MISC FUNCTIONS *)
57
58 let pathname_of_annuri uristring =
59  Configuration.annotations_dir ^
60   Str.replace_first (Str.regexp "^cic:") "" uristring
61 ;;
62
63 let make_dirs dirpath =
64  ignore (Unix.system ("mkdir -p " ^ dirpath))
65 ;;
66
67 exception No_param_dot_CICURI_or_param_dot_annotations_found_in of string;;
68 exception Bad_formed_url of string;;
69
70 let uri_from_url url =
71  let module N = Neturl in
72  let founduri = ref None in
73  let foundann = ref None in
74   let rec find_uri =
75    function
76       [] -> raise (No_param_dot_CICURI_or_param_dot_annotations_found_in url)
77     | he::tl ->
78        match Str.split (Str.regexp "=") he with
79           ["param.CICURI";uri] ->
80             if !founduri <> None then
81              raise (Bad_formed_url url)
82             else
83              begin
84               founduri := Some uri ;
85               if !foundann = None then
86                find_uri tl
87              end
88         | ["param.annotations";ann] ->
89             if !foundann <> None then
90              raise (Bad_formed_url url)
91             else
92              begin
93               foundann :=
94                Some
95                 (match ann with
96                     "yes" -> ".ann"
97                   | "NO"  -> ""
98                   | _     -> raise (Bad_formed_url url)
99                 ) ;
100               if !founduri = None then
101                find_uri tl
102              end
103         | _ -> find_uri tl
104   in
105    find_uri
106     (Str.split (Str.regexp "&")
107      (N.url_query ~encoded:true (N.url_of_string N.ip_url_syntax url))) ;
108    match !founduri,!foundann with
109       (Some uri),(Some ann) -> uri ^ ann
110     | _         , _         ->
111        raise (No_param_dot_CICURI_or_param_dot_annotations_found_in url)
112 ;;
113
114 let get_current_uri () =
115  UriManager.uri_of_string (uri_from_url !current_url)
116 ;;
117
118 (* CALLBACKS *)
119
120 let get_annotated_obj () =
121  match !annotated_obj with
122     None   ->
123      let annobj =
124       (CicCache.get_annobj (get_current_uri ()))
125      in
126       annotated_obj := Some annobj ;
127       annobj
128   | Some annobj -> annobj
129 ;;
130
131 let update_output rendering_window url =
132  rendering_window#label#set_text (uri_from_url url) ;
133  rendering_window#output#load url
134 ;;
135
136 (* called when an hyperlink is clicked *)
137 let jump rendering_window (node : Ominidom.o_mDOMNode) =
138  let module O = Ominidom in
139  let module U = Unix in
140   match (node#get_attribute (O.o_mDOMString_of_string "href")) with
141     Some str ->
142      let frameseturl = str#get_string in
143      let devnull = U.openfile "/dev/null" [U.O_RDWR] 0o600 in
144       ignore
145        (U.create_process "netscape-remote"
146          [|"netscape-remote" ; "-noraise" ; "-remote" ;
147            "openURL(" ^ frameseturl ^ ",cic)"
148          |] devnull devnull devnull)
149   | None -> assert false
150 ;;
151
152 (* called by the remote control *)
153 let remotejump rendering_window url =
154  current_url := url ;
155  update_output rendering_window url
156 ;;
157
158 let choose_selection rendering_window (node : Ominidom.o_mDOMNode option) =
159  let module O = Ominidom in
160   let rec aux node =
161    match node#get_attribute (O.o_mDOMString_of_string "xref") with
162      Some _ -> rendering_window#output#set_selection (Some node)
163    | None   -> aux (node#get_parent)
164   in
165    match node with
166      Some x -> aux x
167    | None   -> rendering_window#output#set_selection None
168 ;;
169
170 let annotateb_pressed rendering_window annotation_window () =
171  let module O = Ominidom in
172  match rendering_window#output#get_selection with
173    Some node ->
174     begin
175      match (node#get_attribute (O.o_mDOMString_of_string "xref")) with
176         Some xpath ->
177          let annobj = get_annotated_obj ()
178          and annotation = (annotation_window#annotation : GEdit.text) in
179           ann := CicXPath.get_annotation annobj (xpath#get_string) ;
180           CicAnnotationHinter.create_hints annotation_window annobj
181            (xpath#get_string) ;
182           annotation#delete_text 0 annotation#length ;
183           begin
184            match !(!ann) with
185                None      ->
186                 annotation#misc#set_sensitive false ;
187                 annotation_window#radio_none#set_active true ;
188                 radio_some_status := false
189              | Some ann' ->
190                 annotation#insert ann' ;
191                 annotation#misc#set_sensitive true ;
192                 annotation_window#radio_some#set_active true ;
193                 radio_some_status := true
194           end ;
195           GMain.Grab.add (annotation_window#window_to_annotate#coerce) ;
196           annotation_window#show () ;
197      | None -> rendering_window#label#set_text ("ERROR: No xref found!!!\n")
198     end
199  | None -> rendering_window#label#set_text ("ERROR: No selection!!!\n")
200 ;;
201
202 (* called when the annotation is confirmed *)
203 let save_annotation annotation =
204  let module S = Str in
205  let module U = UriManager in
206   if !radio_some_status then
207    !ann := Some (annotation#get_chars 0 annotation#length)
208   else
209    !ann := None ;
210   match !annotated_obj with
211      None -> assert false
212    | Some (annobj,_) ->
213       let uri = get_current_uri () in
214        let annxml = Annotation2Xml.pp_annotation annobj uri in
215         make_dirs
216           (pathname_of_annuri (U.buri_of_uri uri)) ;
217         Xml.pp ~quiet:true annxml
218          (Some
219           (pathname_of_annuri (U.string_of_uri (U.annuri_of_uri uri)) ^
220            ".xml"
221           )
222          )
223 ;;
224
225 (* STUFF TO BUILD THE GTK INTERFACE *)
226
227 (* Stuff for the widget settings *)
228
229 let export_to_postscript (output : GMathView.math_view) () =
230  output#export_to_postscript ~filename:"output.ps" ();
231 ;;
232
233 let activate_t1 output button_set_anti_aliasing button_set_kerning 
234  button_export_to_postscript button_t1 ()
235 =
236  let is_set = button_t1#active in
237   output#set_font_manager_type
238    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
239   if is_set then
240    begin
241     button_set_anti_aliasing#misc#set_sensitive true ;
242     button_set_kerning#misc#set_sensitive true ;
243     button_export_to_postscript#misc#set_sensitive true ;
244    end
245   else
246    begin
247     button_set_anti_aliasing#misc#set_sensitive false ;
248     button_set_kerning#misc#set_sensitive false ;
249     button_export_to_postscript#misc#set_sensitive false ;
250    end
251 ;;
252
253 let set_anti_aliasing output button_set_anti_aliasing () =
254  output#set_anti_aliasing button_set_anti_aliasing#active
255 ;;
256
257 let set_kerning output button_set_kerning () =
258  output#set_kerning button_set_kerning#active
259 ;;
260
261 let changefont output font_size_spinb () =
262  output#set_font_size font_size_spinb#value_as_int
263 ;;
264
265 let set_log_verbosity output log_verbosity_spinb () =
266  output#set_log_verbosity log_verbosity_spinb#value_as_int
267 ;;
268
269 class settings_window output sw button_export_to_postscript jump_callback
270  selection_changed_callback
271 =
272  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
273  let vbox =
274   GPack.vbox ~packing:settings_window#add () in
275  let table =
276   GPack.table
277    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
278    ~border_width:5 ~packing:vbox#add () in
279  let button_t1 =
280   GButton.toggle_button ~label:"activate t1 fonts"
281    ~packing:(table#attach ~left:0 ~top:0) () in
282  let button_set_anti_aliasing =
283   GButton.toggle_button ~label:"set_anti_aliasing"
284    ~packing:(table#attach ~left:1 ~top:0) () in
285  let button_set_kerning =
286   GButton.toggle_button ~label:"set_kerning"
287    ~packing:(table#attach ~left:2 ~top:0) () in
288  let table =
289   GPack.table
290    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
291    ~border_width:5 ~packing:vbox#add () in
292  let font_size_label =
293   GMisc.label ~text:"font size:"
294    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
295  let font_size_spinb =
296   let sadj =
297    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
298   in
299    GEdit.spin_button 
300     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
301  let log_verbosity_label =
302   GMisc.label ~text:"log verbosity:"
303    ~packing:(table#attach ~left:0 ~top:1) () in
304  let log_verbosity_spinb =
305   let sadj =
306    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
307   in
308    GEdit.spin_button 
309     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
310  let hbox =
311   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
312  let closeb =
313   GButton.button ~label:"Close"
314    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
315 object(self)
316  method show = settings_window#show
317  initializer
318   button_set_anti_aliasing#misc#set_sensitive false ;
319   button_set_kerning#misc#set_sensitive false ;
320   (* Signals connection *)
321   ignore(button_t1#connect#clicked
322    (activate_t1 output button_set_anti_aliasing button_set_kerning
323     button_export_to_postscript button_t1)) ;
324   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
325   ignore(button_set_anti_aliasing#connect#toggled
326    (set_anti_aliasing output button_set_anti_aliasing));
327   ignore(button_set_kerning#connect#toggled
328    (set_kerning output button_set_kerning)) ;
329   ignore(log_verbosity_spinb#connect#changed
330    (set_log_verbosity output log_verbosity_spinb)) ;
331   ignore(closeb#connect#clicked settings_window#misc#hide)
332 end;;
333
334 (* Main windows *)
335
336 class annotation_window output label =
337  let window_to_annotate =
338   GWindow.window ~title:"Annotating environment" ~border_width:2 () in
339  let hbox1 =
340   GPack.hbox ~packing:window_to_annotate#add () in
341  let vbox1 =
342   GPack.vbox ~packing:(hbox1#pack ~padding:5) () in
343  let hbox2 =
344   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
345  let radio_some = GButton.radio_button ~label:"Annotation below"
346   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
347  let radio_none = GButton.radio_button ~label:"No annotation"
348   ~group:radio_some#group
349   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5)
350   ~active:true () in
351  let annotation = GEdit.text ~editable:true ~width:400 ~height:180
352   ~packing:(vbox1#pack ~padding:5) () in
353  let table =
354   GPack.table ~rows:3 ~columns:3 ~packing:(vbox1#pack ~padding:5) () in
355  let annotation_hints =
356   Array.init 9
357    (function i ->
358      GButton.button ~label:("Hint " ^ string_of_int i)
359       ~packing:(table#attach ~left:(i mod 3) ~top:(i / 3)) ()
360    ) in
361  let vbox2 =
362   GPack.vbox ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
363  let confirmb =
364   GButton.button ~label:"O.K."
365    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
366  let abortb =
367   GButton.button ~label:"Abort"
368    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
369 object (self)
370  method window_to_annotate = window_to_annotate
371  method annotation = annotation
372  method radio_some = radio_some
373  method radio_none = radio_none
374  method annotation_hints = annotation_hints
375  method output = (output : GMathView.math_view)
376  method show () = window_to_annotate#show ()
377  initializer
378   (* signal handlers here *)
379   ignore (window_to_annotate#event#connect#delete
380    (fun _ ->
381      window_to_annotate#misc#hide () ;
382      GMain.Grab.remove (window_to_annotate#coerce) ; 
383      true
384    )) ;
385   ignore (confirmb#connect#clicked
386    (fun () ->
387      window_to_annotate#misc#hide () ;
388      save_annotation annotation ;
389      GMain.Grab.remove (window_to_annotate#coerce) ;
390      let new_current_uri = UriManager.annuri_of_uri (get_current_uri ()) in
391       Getter.register new_current_uri
392        (Configuration.annotations_url ^
393          Str.replace_first (Str.regexp "^cic:") ""
394           (UriManager.string_of_uri new_current_uri) ^ ".xml"
395        ) ;
396 (*CSC: corretto, up to XsltProcessor.url_of_uri
397       let new_current_url = XsltProcessor.url_of_uri new_current_uri in
398        current_url := new_current_url ;
399        label#set_text (UriManager.string_of_uri new_current_uri) ;
400        output#load new_current_url
401 *) ()
402    )) ;
403   ignore (abortb#connect#clicked
404    (fun () ->
405      window_to_annotate#misc#hide () ;
406      GMain.Grab.remove (window_to_annotate#coerce)
407    ));
408   ignore (radio_some#connect#clicked
409    (fun () -> annotation#misc#set_sensitive true ; radio_some_status := true)) ;
410   ignore (radio_none #connect#clicked
411    (fun () ->
412      annotation#misc#set_sensitive false;
413      radio_some_status := false)
414    )
415 end;;
416
417 class rendering_window annotation_window output (label : GMisc.label) =
418  let window =
419   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
420  let vbox =
421   GPack.vbox ~packing:window#add () in
422  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
423  let scrolled_window0 =
424   GBin.scrolled_window ~border_width:10
425    ~packing:(vbox#pack ~expand:true ~padding:5) () in
426  let _ = scrolled_window0#add output#coerce in
427  let hbox =
428   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
429  let annotateb =
430   GButton.button ~label:"Annotate"
431    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
432  let settingsb =
433   GButton.button ~label:"Settings"
434    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
435  let button_export_to_postscript =
436   GButton.button ~label:"export_to_postscript"
437   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
438  let closeb =
439   GButton.button ~label:"Close"
440    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
441 object(self)
442  method label = label
443  method output = (output : GMathView.math_view)
444  method show () = window#show ()
445  initializer
446   button_export_to_postscript#misc#set_sensitive false ;
447
448   (* signal handlers here *)
449   ignore(output#connect#jump (jump self)) ;
450   ignore(output#connect#selection_changed (choose_selection self)) ;
451   ignore(closeb#connect#clicked (fun _ -> GMain.Main.quit ())) ;
452   ignore(annotateb#connect#clicked (annotateb_pressed self annotation_window)) ;
453   let settings_window = new settings_window output scrolled_window0
454    button_export_to_postscript (jump self) (choose_selection self) in
455   ignore(settingsb#connect#clicked settings_window#show) ;
456   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
457   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true ))
458 end;;
459
460 (* MAIN *)
461
462 let initialize_everything tmpfile url =
463  let module U = Unix in
464   (* Let's be ready to be remotely controlled *) 
465   let socket = U.socket ~domain:U.PF_INET ~kind:U.SOCK_DGRAM ~protocol:0 in
466   let address = U.ADDR_INET (U.inet_addr_of_string "127.000.000.001", 8778) in
467   let buffersize = 2048 in (* are 2048 chars enough? *)
468   let buffer = String.create buffersize in
469    try
470     U.bind socket address ;
471     U.set_nonblock socket ;
472     let output = GMathView.math_view ~width:400 ~height:380 ()
473     and label = GMisc.label ~text:"???" () in
474      let annotation_window = new annotation_window output label in
475      let rendering_window =
476       new rendering_window annotation_window output label
477      in
478      let exec_remote_request () =
479       try
480        remotejump rendering_window
481         (String.sub buffer 0 (U.recv socket buffer 0 buffersize []))
482       with
483          U.Unix_error (U.EAGAIN,_,_)
484        | U.Unix_error (U.EWOULDBLOCK,_,_) -> ()
485      in
486       ignore (GMain.Timeout.add ~ms:500
487        ~callback:(fun () -> exec_remote_request () ; true)) ;
488       rendering_window#show () ;
489       rendering_window#label#set_text (uri_from_url url) ;
490       rendering_window#output#load tmpfile ;
491       GMain.Main.main ()
492    with
493     U.Unix_error (_,"bind",_) ->
494      (* Another copy is already under execution ==> I am a remote control *)
495      ignore (U.sendto socket url 0 (String.length url) [] address)
496 ;;
497
498 let _ =
499  let filename = ref "" in
500  let usage_msg =
501    "\nusage: mmlinterface[.opt] file url\n\n List of options:"
502  in
503   Arg.parse []
504    (fun x ->
505      if x = "" then raise (Arg.Bad "Empty filename or URL not allowed") ;
506      if !filename = "" then
507       filename := x
508      else if !current_url = "" then
509       current_url := x
510      else
511       begin
512        prerr_string "More than two arguments provided\n" ;
513        Arg.usage [] usage_msg ;
514        exit (-1)
515       end
516    ) usage_msg ;
517    initialize_everything !filename !current_url
518 ;;