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