]> matita.cs.unibo.it Git - helm.git/blob - helm/interface/mmlinterface.ml
mmlinterface.ml : updated to the new binding
[helm.git] / helm / interface / mmlinterface.ml
1 (******************************************************************************)
2 (*                                                                            *)
3 (*                               PROJECT HELM                                 *)
4 (*                                                                            *)
5 (*                Claudio Sacerdoti Coen <sacerdot@cs.unibo.it>               *)
6 (*                                 24/01/2000                                 *)
7 (*                                                                            *)
8 (* This is a simple gtk interface to the Coq-like pretty printer cicPp for    *)
9 (* cic terms exported in xml. It uses directly the modules cicPp and          *)
10 (* cicCcache and indirectly all the other modules (cicParser, cicParser2,     *)
11 (* cicParser3, getter).                                                       *)
12 (* The syntax is  "gtkInterface[.opt] filename1 ... filenamen" where          *)
13 (* filenamei is the path-name of an xml file describing a cic term.           *)
14 (* The terms are loaded in cache and then pretty-printed one at a time and    *)
15 (* only once, when the user wants to look at it: if the user wants to look at *)
16 (* a term again, then the pretty-printed term is showed again, but not        *)
17 (* recomputed                                                                 *)
18 (*                                                                            *)
19 (******************************************************************************)
20
21 (* DEFINITION OF THE URI TREE AND USEFUL FUNCTIONS ON IT *)
22
23 type item =
24    Dir of string * item list ref
25  | File of string * UriManager.uri
26 ;;
27
28 let uritree = ref []
29 let theoryuritree = ref []
30
31 let get_name =
32  function
33     Dir (name,_) -> name
34   | File (name,_) -> name
35 ;;
36
37 let get_uri =
38  function
39     Dir _ -> None
40   | File (_,uri) -> Some uri
41 ;;
42
43 (* STUFF TO BUILD THE URI TREE *)
44
45 exception EmptyUri
46 exception DuplicatedUri
47 exception ConflictingUris
48
49 let insert_in_uri_tree uri =
50  let rec aux l =
51   function
52      [name] ->
53       (try
54         let _ = List.find (fun item -> name = get_name item) !l in
55          raise DuplicatedUri
56        with
57         Not_found -> l := (File (name,uri))::!l
58       )
59    | name::tl ->
60       (try
61         match List.find (fun item -> name = get_name item) !l with
62            Dir (_,children) -> aux children tl
63          | File _ -> raise ConflictingUris
64        with
65         Not_found ->
66          let children = ref [] in
67           l := (Dir (name,children))::!l ;
68           aux children tl
69       )
70    | [] -> raise EmptyUri
71  in
72   aux
73 ;;
74
75 (* Imperative procedure that builds the two uri trees *)
76 let build_uri_tree () =
77  let dbh = Dbm.opendbm Configuration.uris_dbm [Dbm.Dbm_rdonly] 0 in
78    Dbm.iter 
79     (fun uri _ ->
80       let cicregexp = Str.regexp "cic:"
81       and theoryregexp = Str.regexp "theory:" in
82        if Str.string_match cicregexp uri 0 then
83         let s = Str.replace_first cicregexp "" uri in
84          let l = Str.split (Str.regexp "/") s in
85           insert_in_uri_tree (UriManager.uri_of_string uri) uritree l
86        else if Str.string_match theoryregexp uri 0 then
87         let s = Str.replace_first theoryregexp "" uri in
88          let l = Str.split (Str.regexp "/") s in
89           insert_in_uri_tree (UriManager.uri_of_string uri) theoryuritree l
90     ) dbh ;
91    Dbm.close dbh
92 ;;
93
94 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
95
96 let annotated_obj = ref None;;      (* reference to a couple option where    *)
97                                     (* the first component is the current    *)
98                                     (* annotated object and the second is    *)
99                                     (* the map from ids to annotated targets *)
100 let ann = ref (ref None);;          (* current annotation *)
101 let radio_some_status = ref false;; (* is the radio_some button selected? *)
102
103 let theory_visited_uris = ref [];;
104 let theory_to_visit_uris = ref [];;
105 let visited_uris = ref [];;
106 let to_visit_uris = ref [];;
107
108 (* CALLBACKS *)
109
110 exception NoCurrentUri;;
111 exception NoNextOrPrevUri;;
112 exception GtkInterfaceInternalError;;
113
114 let theory_get_current_uri () =
115  match !theory_visited_uris with
116     [] -> raise NoCurrentUri
117   | uri::_ -> uri
118 ;;
119
120 let get_current_uri () =
121  match !visited_uris with
122     [] -> raise NoCurrentUri
123   | uri::_ -> uri
124 ;;
125
126 let get_annotated_obj () =
127  match !annotated_obj with
128     None   ->
129      let (annobj, ids_to_targets,_) =
130       (CicCache.get_annobj (get_current_uri ()))
131      in
132       annotated_obj := Some (annobj, ids_to_targets) ;
133       (annobj, ids_to_targets)
134   | Some annobj -> annobj
135 ;;
136
137 let filename_of_uri uri =
138  Getter.get uri
139 ;;
140
141 let theory_update_output rendering_window uri =
142  rendering_window#label#set_text (UriManager.string_of_uri uri) ;
143  ignore (rendering_window#errors#delete_text 0 rendering_window#errors#length) ;
144   let mmlfile = XsltProcessor.process uri true "theory" in
145    rendering_window#output#load mmlfile
146 ;;
147
148 let update_output rendering_window uri =
149  rendering_window#label#set_text (UriManager.string_of_uri uri) ;
150  ignore (rendering_window#errors#delete_text 0 rendering_window#errors#length) ;
151   let mmlfile = XsltProcessor.process uri true "cic" in
152    rendering_window#output#load mmlfile
153 ;;
154
155 let theory_next rendering_window () =
156  match !theory_to_visit_uris with
157     [] -> raise NoNextOrPrevUri
158   | uri::tl ->
159      theory_to_visit_uris := tl ;
160      theory_visited_uris := uri::!theory_visited_uris ;
161      theory_update_output rendering_window uri ;
162      rendering_window#prevb#misc#set_sensitive true ;
163      if tl = [] then
164       rendering_window#nextb#misc#set_sensitive false
165 ;;
166
167 let next rendering_window () =
168  match !to_visit_uris with
169     [] -> raise NoNextOrPrevUri
170   | uri::tl ->
171      to_visit_uris := tl ;
172      visited_uris := uri::!visited_uris ;
173      annotated_obj := None ;
174      update_output rendering_window uri ;
175      rendering_window#prevb#misc#set_sensitive true ;
176      if tl = [] then
177       rendering_window#nextb#misc#set_sensitive false
178 ;;
179
180 let theory_prev rendering_window () =
181  match !theory_visited_uris with
182     [] -> raise NoCurrentUri
183   | [_] -> raise NoNextOrPrevUri
184   | uri::(uri'::tl as newvu) ->
185      theory_visited_uris := newvu ;
186      theory_to_visit_uris := uri::!theory_to_visit_uris ;
187      theory_update_output rendering_window uri' ;
188      rendering_window#nextb#misc#set_sensitive true ;
189      if tl = [] then
190       rendering_window#prevb#misc#set_sensitive false
191 ;;
192
193 let prev rendering_window () =
194  match !visited_uris with
195     [] -> raise NoCurrentUri
196   | [_] -> raise NoNextOrPrevUri
197   | uri::(uri'::tl as newvu) ->
198      visited_uris := newvu ;
199      to_visit_uris := uri::!to_visit_uris ;
200      annotated_obj := None ;
201      update_output rendering_window uri' ;
202      rendering_window#nextb#misc#set_sensitive true ;
203      if tl = [] then
204       rendering_window#prevb#misc#set_sensitive false
205 ;;
206
207 exception SomethingWrong
208
209 (* called when an hyperlink is clicked *)
210 let jump rendering_window (node : Ominidom.o_mDOMNode) =
211  let module O = Ominidom in
212   match (node#get_attribute (O.o_mDOMString_of_string "href")) with
213   | Some str ->
214    let s = str#get_string in
215    let uri = UriManager.uri_of_string s in
216     rendering_window#show () ;
217     rendering_window#prevb#misc#set_sensitive true ;
218     rendering_window#nextb#misc#set_sensitive false ;
219     visited_uris := uri::!visited_uris ;
220     to_visit_uris := [] ;
221     annotated_obj := None ;
222     update_output rendering_window uri
223   | None -> raise SomethingWrong
224 ;;
225
226 let choose_selection rendering_window (node : Ominidom.o_mDOMNode option) =
227  let module O = Ominidom in
228   let rec aux node =
229    match node#get_attribute (O.o_mDOMString_of_string "xref") with
230    | Some _ -> rendering_window#output#set_selection (Some node)
231    | None   -> aux (node#get_parent)
232   in
233   match node with
234   | Some x -> aux x
235   | None   -> rendering_window#output#set_selection None
236 ;;
237
238
239 let theory_selection_changed rendering_window uri () =
240  match uri with
241     None -> ()
242   | Some uri' ->
243      if !theory_visited_uris <> [] then
244       rendering_window#prevb#misc#set_sensitive true ;
245      rendering_window#nextb#misc#set_sensitive false ;
246      theory_visited_uris := uri'::!theory_visited_uris ;
247      theory_to_visit_uris := [] ;
248      rendering_window#show () ;
249      theory_update_output rendering_window uri'
250 ;;
251
252 let selection_changed rendering_window uri () =
253  match uri with
254     None -> ()
255   | Some uri' ->
256      if !visited_uris <> [] then
257       rendering_window#prevb#misc#set_sensitive true ;
258      rendering_window#nextb#misc#set_sensitive false ;
259      visited_uris := uri'::!visited_uris ;
260      to_visit_uris := [] ;
261      annotated_obj := None ;
262      rendering_window#show () ;
263      update_output rendering_window uri'
264 ;;
265
266 (* CSC: unificare con la creazione la prima volta *)
267 let rec updateb_pressed theory_rendering_window rendering_window
268  (sw1, sw ,(hbox : GPack.box)) mktree ()
269 =
270  Getter.update () ;
271  (* let's empty the uri trees and rebuild them *)
272  uritree := [] ;
273  theoryuritree := [] ;
274  build_uri_tree () ;
275  hbox#remove !sw1#coerce ;
276  hbox#remove !sw#coerce ;
277
278  let sw3 =
279   GBin.scrolled_window ~width:250 ~height:600
280    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
281  let tree1 =
282   GTree.tree ~selection_mode:`BROWSE ~packing:sw3#add_with_viewport () in
283  let tree_item1 = GTree.tree_item ~label:"theory:/" ~packing:tree1#append () in
284   sw1 := sw3 ;
285   ignore(tree_item1#connect#select
286    (theory_selection_changed theory_rendering_window None)) ;
287   mktree theory_selection_changed theory_rendering_window tree_item1
288    (Dir ("theory:/",theoryuritree)) ;
289
290  let sw2 =
291   GBin.scrolled_window ~width:250 ~height:600
292    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
293  let tree =
294   GTree.tree ~selection_mode:`BROWSE ~packing:sw2#add_with_viewport () in
295  let tree_item = GTree.tree_item ~label:"cic:/" ~packing:tree#append () in
296   sw := sw2 ;
297   ignore(tree_item#connect#select (selection_changed rendering_window None)) ;
298   mktree selection_changed rendering_window tree_item (Dir ("cic:/",uritree))
299 ;;
300
301 let theory_check rendering_window () =
302   let output =
303   try
304    TheoryTypeChecker.typecheck (theory_get_current_uri ());
305    "Type Checking was successful"
306   with
307    TheoryTypeChecker.NotWellTyped s ->
308     "Type Checking was NOT successful:\n\t" ^ s
309  in
310   (* next "cast" can't got rid of, but I don't know why *)
311   let errors = (rendering_window#errors : GEdit.text) in
312   let _ = errors#delete_text 0 errors#length  in
313    errors#insert output
314 ;;
315
316 let check rendering_window () =
317   let output =
318   try
319    CicTypeChecker.typecheck (get_current_uri ());
320    "Type Checking was successful"
321   with
322    CicTypeChecker.NotWellTyped s -> "Type Checking was NOT successful:\n\t" ^ s
323  in
324   (* next "cast" can't got rid of, but I don't know why *)
325   let errors = (rendering_window#errors : GEdit.text) in
326   let _ = errors#delete_text 0 errors#length  in
327    errors#insert output
328 ;;
329
330 let annotateb_pressed rendering_window annotation_window () =
331  let module O = Ominidom in
332  match rendering_window#output#get_selection with
333  | Some node ->
334   begin
335    match (node#get_attribute (O.o_mDOMString_of_string "xref")) with
336    | Some xpath ->
337      let annobj = get_annotated_obj ()
338      (* next "cast" can't got rid of, but I don't know why *)
339      and annotation = (annotation_window#annotation : GEdit.text) in
340       ann := CicXPath.get_annotation annobj (xpath#get_string) ;
341       CicAnnotationHinter.create_hints annotation_window annobj (xpath#get_string) ;
342       annotation#delete_text 0 annotation#length ;
343       begin
344        match !(!ann) with
345            None      ->
346             annotation#misc#set_sensitive false ;
347             annotation_window#radio_none#set_active true ;
348             radio_some_status := false
349          | Some ann' ->
350             annotation#insert ann' ;
351             annotation#misc#set_sensitive true ;
352             annotation_window#radio_some#set_active true ;
353             radio_some_status := true
354       end ;
355       GMain.Grab.add (annotation_window#window_to_annotate#coerce) ;
356       annotation_window#show () ;
357    | None ->
358        (* next "cast" can't got rid of, but I don't know why *)
359        let errors = (rendering_window#errors : GEdit.text) in
360         errors#insert ("\nNo xref found\n")
361   end
362  | None -> (rendering_window#errors : GEdit.text)#insert "\nNo selection!\n"
363 ;;
364
365 (* called when the annotation is confirmed *)
366 let save_annotation annotation =
367  if !radio_some_status then
368   !ann := Some (annotation#get_chars 0 annotation#length)
369  else
370   !ann := None ;
371  match !annotated_obj with
372     None -> raise GtkInterfaceInternalError
373   | Some (annobj,_) ->
374      let uri = get_current_uri () in
375       let annxml = Annotation2Xml.pp_annotation annobj uri in
376        Xml.pp annxml (Some (fst (Getter.get_ann_file_name_and_uri uri)))
377 ;;
378
379 let parse_no_cache uri =
380  let module U = UriManager in
381   XsltProcessor.process uri false "cic"
382 ;;
383
384
385 (* STUFF TO BUILD THE GTK INTERFACE *)
386
387 (* Stuff to build the tree window *)
388
389 (* selection_changed is actually selection_changed or theory_selection_changed*)
390 let mktree selection_changed rendering_window =
391  let rec aux treeitem =
392   function
393      Dir (dirname, content) ->
394       let subtree = GTree.tree () in
395        treeitem#set_subtree subtree ;
396         List.iter
397          (fun ti ->
398            let label = get_name ti
399            and uri = get_uri ti in
400             let treeitem2 = GTree.tree_item ~label:label () in
401              subtree#append treeitem2 ;
402              ignore(treeitem2#connect#select
403               (selection_changed rendering_window uri)) ;
404              aux treeitem2 ti
405          ) (List.sort compare !content)
406    | _ -> ()
407  in
408   aux 
409 ;;
410
411 (* Stuff for the widget settings *)
412
413 let export_to_postscript (output : GMathView.math_view) () =
414  output#export_to_postscript ~filename:"output.ps" ();
415 ;;
416
417 let activate_t1 output button_set_anti_aliasing button_set_kerning 
418  button_export_to_postscript button_t1 ()
419 =
420  let is_set = button_t1#active in
421   output#set_font_manager_type
422    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
423   if is_set then
424    begin
425     button_set_anti_aliasing#misc#set_sensitive true ;
426     button_set_kerning#misc#set_sensitive true ;
427     button_export_to_postscript#misc#set_sensitive true ;
428    end
429   else
430    begin
431     button_set_anti_aliasing#misc#set_sensitive false ;
432     button_set_kerning#misc#set_sensitive false ;
433     button_export_to_postscript#misc#set_sensitive false ;
434    end
435 ;;
436
437 let set_anti_aliasing output button_set_anti_aliasing () =
438  output#set_anti_aliasing button_set_anti_aliasing#active
439 ;;
440
441 let set_kerning output button_set_kerning () =
442  output#set_kerning button_set_kerning#active
443 ;;
444
445 let changefont output font_size_spinb () =
446  output#set_font_size font_size_spinb#value_as_int
447 ;;
448
449 let set_log_verbosity output log_verbosity_spinb () =
450  output#set_log_verbosity log_verbosity_spinb#value_as_int
451 ;;
452
453 class settings_window output sw button_export_to_postscript jump_callback
454  selection_changed_callback
455 =
456  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
457  let vbox =
458   GPack.vbox ~packing:settings_window#add () in
459  let table =
460   GPack.table
461    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
462    ~border_width:5 ~packing:vbox#add () in
463  let button_t1 =
464   GButton.toggle_button ~label:"activate t1 fonts"
465    ~packing:(table#attach ~left:0 ~top:0) () in
466  let button_set_anti_aliasing =
467   GButton.toggle_button ~label:"set_anti_aliasing"
468    ~packing:(table#attach ~left:1 ~top:0) () in
469  let button_set_kerning =
470   GButton.toggle_button ~label:"set_kerning"
471    ~packing:(table#attach ~left:2 ~top:0) () in
472  let table =
473   GPack.table
474    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
475    ~border_width:5 ~packing:vbox#add () in
476  let font_size_label =
477   GMisc.label ~text:"font size:"
478    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
479  let font_size_spinb =
480   let sadj =
481    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
482   in
483    GEdit.spin_button 
484     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
485  let log_verbosity_label =
486   GMisc.label ~text:"log verbosity:"
487    ~packing:(table#attach ~left:0 ~top:1) () in
488  let log_verbosity_spinb =
489   let sadj =
490    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
491   in
492    GEdit.spin_button 
493     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
494  let hbox =
495   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
496  let closeb =
497   GButton.button ~label:"Close"
498    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
499 object(self)
500  method show = settings_window#show
501  initializer
502   button_set_anti_aliasing#misc#set_sensitive false ;
503   button_set_kerning#misc#set_sensitive false ;
504   (* Signals connection *)
505   ignore(button_t1#connect#clicked
506    (activate_t1 output button_set_anti_aliasing button_set_kerning
507     button_export_to_postscript button_t1)) ;
508   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
509   ignore(button_set_anti_aliasing#connect#toggled
510    (set_anti_aliasing output button_set_anti_aliasing));
511   ignore(button_set_kerning#connect#toggled
512    (set_kerning output button_set_kerning)) ;
513   ignore(log_verbosity_spinb#connect#changed
514    (set_log_verbosity output log_verbosity_spinb)) ;
515   ignore(closeb#connect#clicked settings_window#misc#hide)
516 end;;
517
518 (* Main windows *)
519
520 class annotation_window output label =
521  let window_to_annotate =
522   GWindow.window ~title:"Annotating environment" ~border_width:2 () in
523  let hbox1 =
524   GPack.hbox ~packing:window_to_annotate#add () in
525  let vbox1 =
526   GPack.vbox ~packing:(hbox1#pack ~padding:5) () in
527  let hbox2 =
528   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
529  let radio_some = GButton.radio_button ~label:"Annotation below"
530   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
531  let radio_none = GButton.radio_button ~label:"No annotation"
532   ~group:radio_some#group
533   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5)
534   ~active:true () in
535  let annotation = GEdit.text ~editable:true ~width:400 ~height:180
536   ~packing:(vbox1#pack ~padding:5) () in
537  let table =
538   GPack.table ~rows:3 ~columns:3 ~packing:(vbox1#pack ~padding:5) () in
539  let annotation_hints =
540   Array.init 9
541    (function i ->
542      GButton.button ~label:("Hint " ^ string_of_int i)
543       ~packing:(table#attach ~left:(i mod 3) ~top:(i / 3)) ()
544    ) in
545  let vbox2 =
546   GPack.vbox ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
547  let confirmb =
548   GButton.button ~label:"O.K."
549    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
550  let abortb =
551   GButton.button ~label:"Abort"
552    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
553 object (self)
554  method window_to_annotate = window_to_annotate
555  method annotation = annotation
556  method radio_some = radio_some
557  method radio_none = radio_none
558  method annotation_hints = annotation_hints
559  method output = (output : GMathView.math_view)
560  method show () = window_to_annotate#show ()
561  initializer
562   (* signal handlers here *)
563   ignore (window_to_annotate#event#connect#delete
564    (fun _ ->
565      window_to_annotate#misc#hide () ;
566      GMain.Grab.remove (window_to_annotate#coerce) ; 
567      true
568    )) ;
569   ignore (confirmb#connect#clicked
570    (fun () ->
571      window_to_annotate#misc#hide () ;
572      save_annotation annotation ;
573      GMain.Grab.remove (window_to_annotate#coerce) ;
574      let new_current_uri =
575       (snd (Getter.get_ann_file_name_and_uri (get_current_uri ())))
576      in
577       visited_uris := new_current_uri::(List.tl !visited_uris) ;
578        label#set_text (UriManager.string_of_uri new_current_uri) ;
579        let mmlfile = parse_no_cache new_current_uri in
580         output#load mmlfile
581    )) ;
582   ignore (abortb#connect#clicked
583    (fun () ->
584      window_to_annotate#misc#hide () ;
585      GMain.Grab.remove (window_to_annotate#coerce)
586    ));
587   ignore (radio_some#connect#clicked
588    (fun () -> annotation#misc#set_sensitive true ; radio_some_status := true)) ;
589   ignore (radio_none #connect#clicked
590    (fun () ->
591      annotation#misc#set_sensitive false;
592      radio_some_status := false)
593    )
594 end;;
595
596 class rendering_window annotation_window output (label : GMisc.label) =
597  let window =
598   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
599  let vbox =
600   GPack.vbox ~packing:window#add () in
601  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
602  let paned =
603   GPack.paned `HORIZONTAL ~packing:(vbox#pack ~expand:true ~padding:5) () in
604  let scrolled_window0 =
605   GBin.scrolled_window ~border_width:10 ~packing:paned#add1 () in
606  let _ = scrolled_window0#add output#coerce in
607  let scrolled_window =
608   GBin.scrolled_window
609    ~border_width:10 ~packing:paned#add2 ~width:240 ~height:100 () in
610  let errors = GEdit.text ~packing:scrolled_window#add_with_viewport () in
611  let hbox =
612   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
613  let prevb =
614   GButton.button ~label:"Prev"
615    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
616  let nextb =
617   GButton.button ~label:"Next"
618    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
619  let checkb =
620   GButton.button ~label:"Check"
621    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
622  let annotateb =
623   GButton.button ~label:"Annotate"
624    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
625  let settingsb =
626   GButton.button ~label:"Settings"
627    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
628  let button_export_to_postscript =
629   GButton.button ~label:"export_to_postscript"
630   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
631  let closeb =
632   GButton.button ~label:"Close"
633    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
634 object(self)
635  method nextb = nextb
636  method prevb = prevb
637  method label = label
638  method output = (output : GMathView.math_view)
639  method errors = errors
640  method show () = window#show ()
641  initializer
642   nextb#misc#set_sensitive false ;
643   prevb#misc#set_sensitive false ;
644   button_export_to_postscript#misc#set_sensitive false ;
645
646   (* signal handlers here *)
647   ignore(output#connect#jump (jump self)) ;
648   ignore(output#connect#selection_changed (choose_selection self)) ;
649   ignore(nextb#connect#clicked (next self)) ;
650   ignore(prevb#connect#clicked (prev self)) ;
651   ignore(checkb#connect#clicked (check self)) ;
652   ignore(closeb#connect#clicked window#misc#hide) ;
653   ignore(annotateb#connect#clicked (annotateb_pressed self annotation_window)) ;
654   let settings_window = new settings_window output scrolled_window0
655    button_export_to_postscript (jump self) (choose_selection self) in
656   ignore(settingsb#connect#clicked settings_window#show) ;
657   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
658   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
659 end;;
660
661 class theory_rendering_window rendering_window =
662  let window =
663   GWindow.window ~title:"MathML theory viewer" ~border_width:2 () in
664  let vbox =
665   GPack.vbox ~packing:window#add () in
666  let label =
667   GMisc.label ~text:"???"
668    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
669  let paned =
670   GPack.paned `HORIZONTAL ~packing:(vbox#pack ~expand:true ~padding:5) () in
671  let scrolled_window0 =
672   GBin.scrolled_window ~border_width:10 ~packing:paned#add1 () in
673  let output =
674   GMathView.math_view ~width:400 ~height:380 ~packing:scrolled_window0#add () in
675  let scrolled_window =
676   GBin.scrolled_window
677    ~border_width:10 ~packing:paned#add2 ~width:240 ~height:100 () in
678  let errors = GEdit.text ~packing:scrolled_window#add_with_viewport () in
679  let hbox =
680   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
681  let prevb =
682   GButton.button ~label:"Prev"
683    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
684  let nextb =
685   GButton.button ~label:"Next"
686    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
687  let checkb =
688   GButton.button ~label:"Check"
689    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
690  let settingsb =
691   GButton.button ~label:"Settings"
692    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
693  let button_export_to_postscript =
694   GButton.button ~label:"export_to_postscript"
695   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
696  let closeb =
697   GButton.button ~label:"Close"
698    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
699 object(self)
700  method nextb = nextb
701  method prevb = prevb
702  method label = label
703  method output = (output : GMathView.math_view)
704  method errors = errors
705  method show () = window#show ()
706  initializer
707   nextb#misc#set_sensitive false ;
708   prevb#misc#set_sensitive false ;
709   button_export_to_postscript#misc#set_sensitive false ;
710
711   (* signal handlers here *)
712   ignore(output#connect#jump (jump rendering_window)) ;
713   ignore(output#connect#selection_changed (choose_selection self)) ;
714   ignore(nextb#connect#clicked (theory_next self)) ;
715   ignore(prevb#connect#clicked (theory_prev self)) ;
716   ignore(checkb#connect#clicked (theory_check self)) ;
717   let settings_window = new settings_window output scrolled_window0
718    button_export_to_postscript (jump rendering_window)(choose_selection self) in
719   ignore(settingsb#connect#clicked settings_window#show) ;
720   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
721   ignore(closeb#connect#clicked window#misc#hide) ;
722   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
723 end;;
724
725 (* CSC: fare in modo che i due alberi vengano svuotati invece che distrutti *)
726 class selection_window theory_rendering_window rendering_window =
727   let label = "cic:/" in
728   let theorylabel = "theory:/" in
729   let win = GWindow.window ~title:"Known uris" ~border_width:2 () in
730   let vbox = GPack.vbox ~packing:win#add () in
731   let hbox1 = GPack.hbox ~packing:(vbox#pack ~padding:5) () in
732   let sw1 = GBin.scrolled_window ~width:250 ~height:600
733    ~packing:(hbox1#pack ~padding:5) () in
734   let tree1 =
735    GTree.tree ~selection_mode:`BROWSE ~packing:sw1#add_with_viewport () in
736   let tree_item1 =
737    GTree.tree_item ~label:theorylabel ~packing:tree1#append () in
738   let sw = GBin.scrolled_window ~width:250 ~height:600
739    ~packing:(hbox1#pack ~padding:5) () in
740   let tree =
741    GTree.tree ~selection_mode:`BROWSE ~packing:sw#add_with_viewport () in
742   let tree_item =
743    GTree.tree_item ~label:label ~packing:tree#append () in
744   let hbox =
745    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
746   let updateb =
747    GButton.button ~label:"Update"
748     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
749   let quitb =
750    GButton.button ~label:"Quit"
751     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
752 object (self)
753   method show () = win#show ()
754   initializer
755     mktree theory_selection_changed theory_rendering_window tree_item1
756      (Dir ("theory:/",theoryuritree));
757     mktree selection_changed rendering_window tree_item
758      (Dir ("cic:/",uritree));
759
760     (* signal handlers here *)
761     ignore (tree_item1#connect#select
762      ~callback:(theory_selection_changed theory_rendering_window None)) ;
763     ignore (tree_item#connect#select
764      ~callback:(selection_changed rendering_window None)) ;
765     ignore (win#connect#destroy ~callback:GMain.Main.quit) ;
766     ignore (quitb#connect#clicked GMain.Main.quit) ;
767     ignore(updateb#connect#clicked (updateb_pressed
768      theory_rendering_window rendering_window (ref sw1, ref sw, hbox1) mktree))
769 end;;
770
771
772 (* MAIN *)
773
774 let _ =
775  build_uri_tree () ;
776  let output = GMathView.math_view ~width:400 ~height:380 ()
777  and label = GMisc.label ~text:"???" () in
778   let annotation_window = new annotation_window output label in
779   let rendering_window = new rendering_window annotation_window output label in
780   let theory_rendering_window = new theory_rendering_window rendering_window in
781   let selection_window =
782    new selection_window theory_rendering_window rendering_window
783   in
784    selection_window#show () ;
785    GMain.Main.main ()
786 ;;