]> matita.cs.unibo.it Git - helm.git/blob - helm/interface/mmlinterface.ml
bc72b09a725d5cd80a2090ffc813eb0c45db9383
[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 (* called when an hyperlink is clicked *)
208 let jump rendering_window node =
209  let module M = Minidom in
210   let s =
211    match M.node_get_attribute node (M.mDOMString_of_string "href") with
212       None   -> assert false
213     | Some s -> M.string_of_mDOMString s
214   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 ;;
224
225 let choose_selection rendering_window node =
226  let module M = Minidom in
227  let rec aux ~first_time node =
228   match M.node_get_attribute node (M.mDOMString_of_string "xref") with
229      None ->
230       let parent =
231        match M.node_get_parent node with
232           None -> assert false
233         | Some parent -> parent
234       in
235        aux ~first_time:false parent
236    | Some s ->
237       if not first_time then
238        !(rendering_window#output)#set_selection (Some node)
239  in
240   match node with
241      None      -> () (* No element selected *)
242    | Some node -> aux ~first_time:true node
243 ;;
244
245 let changefont rendering_window () =
246  !(rendering_window#output)#set_font_size rendering_window#spinb#value_as_int
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 () =
432  sw#remove !output#coerce ;
433  output :=
434  (GMathView.math_view ~packing:sw#add ~width:50 ~height:50
435   ~use_t1_lib:true ()) ;
436 (* ignore(!mathview#connect#jump jump) ;
437  ignore(!mathview#connect#clicked clicked) ;
438  ignore(!mathview#connect#selection_changed selection_changed) ;
439 *)
440 ;;
441
442
443 class settings_window output sw =
444  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
445  let table = GPack.table ~rows:5 ~columns:5 ~packing:settings_window#add () in
446  let button_t1 =
447   GButton.button ~label:"activate t1 fonts"
448    ~packing:(table#attach ~left:0 ~top:0) () in
449  let font_size_spinb =
450   let sadj =
451    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
452   in
453    GEdit.spin_button 
454     ~adjustment:sadj ~packing:(table#attach ~left:4 ~top:2) () in
455  let button_set_anti_aliasing = GButton.button ~label:"set_anti_aliasing" ~packing:(table#attach ~left:1 ~top:3) () in
456  let button_set_kerning = GButton.button ~label:"set_kerning" ~packing:(table#attach ~left:3 ~top:3) () in
457  let button_set_log_verbosity = GButton.button ~label:"set_log_verbosity" ~packing:(table#attach ~left:0 ~top:4) () in
458 object(self)
459  method show = settings_window#show
460  initializer
461   ignore(button_t1#connect#clicked (activate_t1 output sw)) ;
462   (*ignore(font_size_spinb#connect#changed (changefont self)) ;*)
463 (*
464   (* Signals connection *)
465   ignore(button_set_anti_aliasing#connect#clicked (set_anti_aliasing mathview)) ;
466   ignore(button_set_kerning#connect#clicked (set_kerning mathview)) ;
467   ignore(button_set_log_verbosity#connect#clicked (set_log_verbosity mathview)) ;
468 *) ()
469 end;;
470
471 (* Main windows *)
472
473 class annotation_window output label =
474  let window_to_annotate =
475   GWindow.window ~title:"Annotating environment" ~border_width:2 () in
476  let hbox1 =
477   GPack.hbox ~packing:window_to_annotate#add () in
478  let vbox1 =
479   GPack.vbox ~packing:(hbox1#pack ~padding:5) () in
480  let hbox2 =
481   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
482  let radio_some = GButton.radio_button ~label:"Annotation below"
483   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
484  let radio_none = GButton.radio_button ~label:"No annotation"
485   ~group:radio_some#group
486   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5)
487   ~active:true () in
488  let annotation = GEdit.text ~editable:true ~width:400 ~height:180
489   ~packing:(vbox1#pack ~padding:5) () in
490  let table =
491   GPack.table ~rows:3 ~columns:3 ~packing:(vbox1#pack ~padding:5) () in
492  let annotation_hints =
493   Array.init 9
494    (function i ->
495      GButton.button ~label:("Hint " ^ string_of_int i)
496       ~packing:(table#attach ~left:(i mod 3) ~top:(i / 3)) ()
497    ) in
498  let vbox2 =
499   GPack.vbox ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
500  let confirmb =
501   GButton.button ~label:"O.K."
502    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
503  let abortb =
504   GButton.button ~label:"Abort"
505    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
506 object (self)
507  method window_to_annotate = window_to_annotate
508  method annotation = annotation
509  method radio_some = radio_some
510  method radio_none = radio_none
511  method annotation_hints = annotation_hints
512  method output = (output : GMathView.math_view ref)
513  method show () = window_to_annotate#show ()
514  initializer
515   (* signal handlers here *)
516   ignore (window_to_annotate#event#connect#delete
517    (fun _ ->
518      window_to_annotate#misc#hide () ;
519      GMain.Grab.remove (window_to_annotate#coerce) ; 
520      true
521    )) ;
522   ignore (confirmb#connect#clicked
523    (fun () ->
524      window_to_annotate#misc#hide () ;
525      save_annotation annotation ;
526      GMain.Grab.remove (window_to_annotate#coerce) ;
527      let new_current_uri =
528       (snd (Getter.get_ann_file_name_and_uri (get_current_uri ())))
529      in
530       visited_uris := new_current_uri::(List.tl !visited_uris) ;
531        label#set_text (UriManager.string_of_uri new_current_uri) ;
532        !output#load (parse_no_cache new_current_uri)
533    )) ;
534   ignore (abortb#connect#clicked
535    (fun () ->
536      window_to_annotate#misc#hide () ;
537      GMain.Grab.remove (window_to_annotate#coerce)
538    ));
539   ignore (radio_some#connect#clicked
540    (fun () -> annotation#misc#set_sensitive true ; radio_some_status := true)) ;
541   ignore (radio_none #connect#clicked
542    (fun () ->
543      annotation#misc#set_sensitive false;
544      radio_some_status := false)
545    )
546 end;;
547
548 class rendering_window annotation_window output (label : GMisc.label) =
549  let window =
550   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
551  let vbox =
552   GPack.vbox ~packing:window#add () in
553  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
554  let paned =
555   GPack.paned `HORIZONTAL ~packing:(vbox#pack ~padding:5) () in
556  let scrolled_window0 =
557   GBin.scrolled_window ~border_width:10 ~packing:paned#add1 () in
558  let _ = scrolled_window0#add !output#coerce in
559  let scrolled_window =
560   GBin.scrolled_window
561    ~border_width:10 ~packing:paned#add2 ~width:240 ~height:100 () in
562  let errors = GEdit.text ~packing:scrolled_window#add_with_viewport () in
563  let hbox =
564   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
565  let prevb =
566   GButton.button ~label:"Prev"
567    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
568  let nextb =
569   GButton.button ~label:"Next"
570    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
571  let checkb =
572   GButton.button ~label:"Check"
573    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
574  let annotateb =
575   GButton.button ~label:"Annotate"
576    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
577  let settingsb =
578   GButton.button ~label:"Settings"
579    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
580  let button_export_to_postscript =
581   GButton.button ~label:"export_to_postscript"
582   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
583  let closeb =
584   GButton.button ~label:"Close"
585    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
586  let settings_window = new settings_window output scrolled_window0 in
587 object(self)
588  method nextb = nextb
589  method prevb = prevb
590  method label = label
591  method output = (output : GMathView.math_view ref)
592  method errors = errors
593  method show () = window#show ()
594  initializer
595   nextb#misc#set_sensitive false ;
596   prevb#misc#set_sensitive false ;
597
598   (* signal handlers here *)
599   ignore(!output#connect#jump (jump self)) ;
600   ignore(!output#connect#selection_changed (choose_selection self)) ;
601   ignore(nextb#connect#clicked (next self)) ;
602   ignore(prevb#connect#clicked (prev self)) ;
603   ignore(checkb#connect#clicked (check self)) ;
604   ignore(closeb#connect#clicked window#misc#hide) ;
605   ignore(annotateb#connect#clicked (annotateb_pressed self annotation_window)) ;
606   ignore(settingsb#connect#clicked settings_window#show) ;
607   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
608   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
609 end;;
610
611 class theory_rendering_window rendering_window =
612  let window =
613   GWindow.window ~title:"MathML theory viewer" ~border_width:2 () in
614  let vbox =
615   GPack.vbox ~packing:window#add () in
616  let label =
617   GMisc.label ~text:"???"
618    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
619  let paned =
620   GPack.paned `HORIZONTAL ~packing:(vbox#pack ~padding:5) () in
621  let scrolled_window0 =
622   GBin.scrolled_window ~border_width:10 ~packing:paned#add1 () in
623  let output =
624   ref (GMathView.math_view ~use_t1_lib:true ~width:400 ~height:380
625    ~packing:scrolled_window0#add ()) in
626  let scrolled_window =
627   GBin.scrolled_window
628    ~border_width:10 ~packing:paned#add2 ~width:240 ~height:100 () in
629  let errors = GEdit.text ~packing:scrolled_window#add_with_viewport () in
630  let hbox =
631   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
632  let prevb =
633   GButton.button ~label:"Prev"
634    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
635  let nextb =
636   GButton.button ~label:"Next"
637    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
638  let checkb =
639   GButton.button ~label:"Check"
640    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
641  let settingsb =
642   GButton.button ~label:"Settings"
643    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
644  let button_export_to_postscript =
645   GButton.button ~label:"export_to_postscript"
646   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
647  let closeb =
648   GButton.button ~label:"Close"
649    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
650  let settings_window = new settings_window output scrolled_window0 in
651 object(self)
652  method nextb = nextb
653  method prevb = prevb
654  method label = label
655  method output = (output : GMathView.math_view ref)
656  method errors = errors
657  method show () = window#show ()
658  initializer
659   nextb#misc#set_sensitive false ;
660   prevb#misc#set_sensitive false ;
661
662   (* signal handlers here *)
663   ignore(!output#connect#jump (jump rendering_window)) ;
664   ignore(!output#connect#selection_changed (choose_selection self)) ;
665   ignore(nextb#connect#clicked (theory_next self)) ;
666   ignore(prevb#connect#clicked (theory_prev self)) ;
667   ignore(checkb#connect#clicked (theory_check self)) ;
668   ignore(settingsb#connect#clicked settings_window#show) ;
669   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
670   ignore(closeb#connect#clicked window#misc#hide) ;
671   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
672 end;;
673
674 (* CSC: fare in modo che i due alberi vengano svuotati invece che distrutti *)
675 class selection_window theory_rendering_window rendering_window =
676   let label = "cic:/" in
677   let theorylabel = "theory:/" in
678   let win = GWindow.window ~title:"Known uris" ~border_width:2 () in
679   let vbox = GPack.vbox ~packing:win#add () in
680   let hbox1 = GPack.hbox ~packing:(vbox#pack ~padding:5) () in
681   let sw1 = GBin.scrolled_window ~width:250 ~height:600
682    ~packing:(hbox1#pack ~padding:5) () in
683   let tree1 =
684    GTree.tree ~selection_mode:`BROWSE ~packing:sw1#add_with_viewport () in
685   let tree_item1 =
686    GTree.tree_item ~label:theorylabel ~packing:tree1#append () in
687   let sw = GBin.scrolled_window ~width:250 ~height:600
688    ~packing:(hbox1#pack ~padding:5) () in
689   let tree =
690    GTree.tree ~selection_mode:`BROWSE ~packing:sw#add_with_viewport () in
691   let tree_item =
692    GTree.tree_item ~label:label ~packing:tree#append () in
693   let hbox =
694    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
695   let updateb =
696    GButton.button ~label:"Update"
697     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
698   let quitb =
699    GButton.button ~label:"Quit"
700     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
701 object (self)
702   method show () = win#show ()
703   initializer
704     mktree theory_selection_changed theory_rendering_window tree_item1
705      (Dir ("theory:/",theoryuritree));
706     mktree selection_changed rendering_window tree_item
707      (Dir ("cic:/",uritree));
708
709     (* signal handlers here *)
710     ignore (tree_item1#connect#select
711      ~callback:(theory_selection_changed theory_rendering_window None)) ;
712     ignore (tree_item#connect#select
713      ~callback:(selection_changed rendering_window None)) ;
714     ignore (win#connect#destroy ~callback:GMain.Main.quit) ;
715     ignore (quitb#connect#clicked GMain.Main.quit) ;
716     ignore(updateb#connect#clicked (updateb_pressed
717      theory_rendering_window rendering_window (ref sw1, ref sw, hbox1) mktree))
718 end;;
719
720
721 (* MAIN *)
722
723 let _ =
724  build_uri_tree () ;
725  let output =
726   ref (GMathView.math_view ~use_t1_lib:false ~width:400 ~height:380 ())
727  and label = GMisc.label ~text:"???" () in
728   let annotation_window = new annotation_window output label in
729   let rendering_window = new rendering_window annotation_window output label in
730   let theory_rendering_window = new theory_rendering_window rendering_window in
731   let selection_window =
732    new selection_window theory_rendering_window rendering_window
733   in
734    selection_window#show () ;
735    GMain.Main.main ()
736 ;;