]> matita.cs.unibo.it Git - helm.git/blob - helm/interface/mmlinterface.ml
Bug fixew
[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 button_set_anti_aliasing button_set_kerning 
432  button_export_to_postscript sw button_t1 jump_callback
433  selection_changed_callback last_uri ()
434 =
435  let is_set = button_t1#active in
436   sw#remove !output#coerce ;
437   let font_size = !output#get_font_size in
438   let log_verbosity = !output#get_log_verbosity in
439   let anti_aliasing = button_set_anti_aliasing#active in
440   let kerning = button_set_kerning#active in
441    output :=
442    (GMathView.math_view ~packing:sw#add ~width:400 ~height:380
443     ~use_t1_lib:is_set ()) ;
444    !output#set_font_size font_size ;
445    !output#set_log_verbosity log_verbosity ;
446    if is_set then
447     begin
448      button_set_anti_aliasing#misc#set_sensitive true ;
449      button_set_kerning#misc#set_sensitive true ;
450      button_export_to_postscript#misc#set_sensitive true ;
451      !output#set_anti_aliasing anti_aliasing ;
452      !output#set_kerning kerning ;
453     end
454    else
455     begin
456      button_set_anti_aliasing#misc#set_sensitive false ;
457      button_set_kerning#misc#set_sensitive false ;
458      button_export_to_postscript#misc#set_sensitive false ;
459     end ;
460    !output#load !last_uri ;
461    ignore(!output#connect#jump jump_callback) ;
462    ignore(!output#connect#selection_changed selection_changed_callback) ;
463 ;;
464
465 let set_anti_aliasing output button_set_anti_aliasing () =
466  !output#set_anti_aliasing button_set_anti_aliasing#active
467 ;;
468
469 let set_kerning output button_set_kerning () =
470  !output#set_kerning button_set_kerning#active
471 ;;
472
473 let changefont output font_size_spinb () =
474  !output#set_font_size font_size_spinb#value_as_int
475 ;;
476
477 let set_log_verbosity output log_verbosity_spinb () =
478  !output#set_log_verbosity log_verbosity_spinb#value_as_int
479 ;;
480
481 class settings_window output sw button_export_to_postscript jump_callback
482  selection_changed_callback last_uri
483 =
484  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
485  let vbox =
486   GPack.vbox ~packing:settings_window#add () in
487  let table =
488   GPack.table
489    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
490    ~border_width:5 ~packing:vbox#add () in
491  let button_t1 =
492   GButton.toggle_button ~label:"activate t1 fonts"
493    ~packing:(table#attach ~left:0 ~top:0) () in
494  let button_set_anti_aliasing =
495   GButton.toggle_button ~label:"set_anti_aliasing"
496    ~packing:(table#attach ~left:1 ~top:0) () in
497  let button_set_kerning =
498   GButton.toggle_button ~label:"set_kerning"
499    ~packing:(table#attach ~left:2 ~top:0) () in
500  let table =
501   GPack.table
502    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
503    ~border_width:5 ~packing:vbox#add () in
504  let font_size_label =
505   GMisc.label ~text:"font size:"
506    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
507  let font_size_spinb =
508   let sadj =
509    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
510   in
511    GEdit.spin_button 
512     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
513  let log_verbosity_label =
514   GMisc.label ~text:"log verbosity:"
515    ~packing:(table#attach ~left:0 ~top:1) () in
516  let log_verbosity_spinb =
517   let sadj =
518    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
519   in
520    GEdit.spin_button 
521     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
522  let hbox =
523   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
524  let closeb =
525   GButton.button ~label:"Close"
526    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
527 object(self)
528  method show = settings_window#show
529  initializer
530   button_set_anti_aliasing#misc#set_sensitive false ;
531   button_set_kerning#misc#set_sensitive false ;
532   (* Signals connection *)
533   ignore(button_t1#connect#clicked
534    (activate_t1 output button_set_anti_aliasing button_set_kerning
535     button_export_to_postscript sw button_t1 jump_callback
536     selection_changed_callback last_uri)) ;
537   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
538   ignore(button_set_anti_aliasing#connect#toggled
539    (set_anti_aliasing output button_set_anti_aliasing));
540   ignore(button_set_kerning#connect#toggled
541    (set_kerning output button_set_kerning)) ;
542   ignore(log_verbosity_spinb#connect#changed
543    (set_log_verbosity output log_verbosity_spinb)) ;
544   ignore(closeb#connect#clicked settings_window#misc#hide)
545 end;;
546
547 (* Main windows *)
548
549 class annotation_window output label =
550  let window_to_annotate =
551   GWindow.window ~title:"Annotating environment" ~border_width:2 () in
552  let hbox1 =
553   GPack.hbox ~packing:window_to_annotate#add () in
554  let vbox1 =
555   GPack.vbox ~packing:(hbox1#pack ~padding:5) () in
556  let hbox2 =
557   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
558  let radio_some = GButton.radio_button ~label:"Annotation below"
559   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
560  let radio_none = GButton.radio_button ~label:"No annotation"
561   ~group:radio_some#group
562   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5)
563   ~active:true () in
564  let annotation = GEdit.text ~editable:true ~width:400 ~height:180
565   ~packing:(vbox1#pack ~padding:5) () in
566  let table =
567   GPack.table ~rows:3 ~columns:3 ~packing:(vbox1#pack ~padding:5) () in
568  let annotation_hints =
569   Array.init 9
570    (function i ->
571      GButton.button ~label:("Hint " ^ string_of_int i)
572       ~packing:(table#attach ~left:(i mod 3) ~top:(i / 3)) ()
573    ) in
574  let vbox2 =
575   GPack.vbox ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
576  let confirmb =
577   GButton.button ~label:"O.K."
578    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
579  let abortb =
580   GButton.button ~label:"Abort"
581    ~packing:(vbox2#pack ~expand:false ~fill:false ~padding:5) () in
582 object (self)
583  method window_to_annotate = window_to_annotate
584  method annotation = annotation
585  method radio_some = radio_some
586  method radio_none = radio_none
587  method annotation_hints = annotation_hints
588  method output = (output : GMathView.math_view ref)
589  method show () = window_to_annotate#show ()
590  initializer
591   (* signal handlers here *)
592   ignore (window_to_annotate#event#connect#delete
593    (fun _ ->
594      window_to_annotate#misc#hide () ;
595      GMain.Grab.remove (window_to_annotate#coerce) ; 
596      true
597    )) ;
598   ignore (confirmb#connect#clicked
599    (fun () ->
600      window_to_annotate#misc#hide () ;
601      save_annotation annotation ;
602      GMain.Grab.remove (window_to_annotate#coerce) ;
603      let new_current_uri =
604       (snd (Getter.get_ann_file_name_and_uri (get_current_uri ())))
605      in
606       visited_uris := new_current_uri::(List.tl !visited_uris) ;
607        label#set_text (UriManager.string_of_uri new_current_uri) ;
608        let mmlfile = parse_no_cache new_current_uri in
609         loaded_uri := mmlfile ;
610         !output#load mmlfile
611    )) ;
612   ignore (abortb#connect#clicked
613    (fun () ->
614      window_to_annotate#misc#hide () ;
615      GMain.Grab.remove (window_to_annotate#coerce)
616    ));
617   ignore (radio_some#connect#clicked
618    (fun () -> annotation#misc#set_sensitive true ; radio_some_status := true)) ;
619   ignore (radio_none #connect#clicked
620    (fun () ->
621      annotation#misc#set_sensitive false;
622      radio_some_status := false)
623    )
624 end;;
625
626 class rendering_window annotation_window output (label : GMisc.label) =
627  let window =
628   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
629  let vbox =
630   GPack.vbox ~packing:window#add () in
631  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
632  let paned =
633   GPack.paned `HORIZONTAL ~packing:(vbox#pack ~expand:true ~padding:5) () in
634  let scrolled_window0 =
635   GBin.scrolled_window ~border_width:10 ~packing:paned#add1 () in
636  let _ = scrolled_window0#add !output#coerce in
637  let scrolled_window =
638   GBin.scrolled_window
639    ~border_width:10 ~packing:paned#add2 ~width:240 ~height:100 () in
640  let errors = GEdit.text ~packing:scrolled_window#add_with_viewport () in
641  let hbox =
642   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
643  let prevb =
644   GButton.button ~label:"Prev"
645    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
646  let nextb =
647   GButton.button ~label:"Next"
648    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
649  let checkb =
650   GButton.button ~label:"Check"
651    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
652  let annotateb =
653   GButton.button ~label:"Annotate"
654    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
655  let settingsb =
656   GButton.button ~label:"Settings"
657    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
658  let button_export_to_postscript =
659   GButton.button ~label:"export_to_postscript"
660   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
661  let closeb =
662   GButton.button ~label:"Close"
663    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
664 object(self)
665  method nextb = nextb
666  method prevb = prevb
667  method label = label
668  method output = (output : GMathView.math_view ref)
669  method errors = errors
670  method show () = window#show ()
671  initializer
672   nextb#misc#set_sensitive false ;
673   prevb#misc#set_sensitive false ;
674   button_export_to_postscript#misc#set_sensitive false ;
675
676   (* signal handlers here *)
677   ignore(!output#connect#jump (jump self)) ;
678   ignore(!output#connect#selection_changed (choose_selection self)) ;
679   ignore(nextb#connect#clicked (next self)) ;
680   ignore(prevb#connect#clicked (prev self)) ;
681   ignore(checkb#connect#clicked (check self)) ;
682   ignore(closeb#connect#clicked window#misc#hide) ;
683   ignore(annotateb#connect#clicked (annotateb_pressed self annotation_window)) ;
684   let settings_window = new settings_window output scrolled_window0
685    button_export_to_postscript (jump self) (choose_selection self) loaded_uri in
686   ignore(settingsb#connect#clicked settings_window#show) ;
687   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
688   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
689 end;;
690
691 class theory_rendering_window rendering_window =
692  let window =
693   GWindow.window ~title:"MathML theory viewer" ~border_width:2 () in
694  let vbox =
695   GPack.vbox ~packing:window#add () in
696  let label =
697   GMisc.label ~text:"???"
698    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
699  let paned =
700   GPack.paned `HORIZONTAL ~packing:(vbox#pack ~expand:true ~padding:5) () in
701  let scrolled_window0 =
702   GBin.scrolled_window ~border_width:10 ~packing:paned#add1 () in
703  let output =
704   ref (GMathView.math_view ~use_t1_lib:false ~width:400 ~height:380
705    ~packing:scrolled_window0#add ()) in
706  let scrolled_window =
707   GBin.scrolled_window
708    ~border_width:10 ~packing:paned#add2 ~width:240 ~height:100 () in
709  let errors = GEdit.text ~packing:scrolled_window#add_with_viewport () in
710  let hbox =
711   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
712  let prevb =
713   GButton.button ~label:"Prev"
714    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
715  let nextb =
716   GButton.button ~label:"Next"
717    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
718  let checkb =
719   GButton.button ~label:"Check"
720    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
721  let settingsb =
722   GButton.button ~label:"Settings"
723    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
724  let button_export_to_postscript =
725   GButton.button ~label:"export_to_postscript"
726   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
727  let closeb =
728   GButton.button ~label:"Close"
729    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
730 object(self)
731  method nextb = nextb
732  method prevb = prevb
733  method label = label
734  method output = (output : GMathView.math_view ref)
735  method errors = errors
736  method show () = window#show ()
737  initializer
738   nextb#misc#set_sensitive false ;
739   prevb#misc#set_sensitive false ;
740   button_export_to_postscript#misc#set_sensitive false ;
741
742   (* signal handlers here *)
743   ignore(!output#connect#jump (jump rendering_window)) ;
744   ignore(!output#connect#selection_changed (choose_selection self)) ;
745   ignore(nextb#connect#clicked (theory_next self)) ;
746   ignore(prevb#connect#clicked (theory_prev self)) ;
747   ignore(checkb#connect#clicked (theory_check self)) ;
748   let settings_window = new settings_window output scrolled_window0
749    button_export_to_postscript (jump rendering_window) (choose_selection self)
750    theory_loaded_uri in
751   ignore(settingsb#connect#clicked settings_window#show) ;
752   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
753   ignore(closeb#connect#clicked window#misc#hide) ;
754   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
755 end;;
756
757 (* CSC: fare in modo che i due alberi vengano svuotati invece che distrutti *)
758 class selection_window theory_rendering_window rendering_window =
759   let label = "cic:/" in
760   let theorylabel = "theory:/" in
761   let win = GWindow.window ~title:"Known uris" ~border_width:2 () in
762   let vbox = GPack.vbox ~packing:win#add () in
763   let hbox1 = GPack.hbox ~packing:(vbox#pack ~padding:5) () in
764   let sw1 = GBin.scrolled_window ~width:250 ~height:600
765    ~packing:(hbox1#pack ~padding:5) () in
766   let tree1 =
767    GTree.tree ~selection_mode:`BROWSE ~packing:sw1#add_with_viewport () in
768   let tree_item1 =
769    GTree.tree_item ~label:theorylabel ~packing:tree1#append () in
770   let sw = GBin.scrolled_window ~width:250 ~height:600
771    ~packing:(hbox1#pack ~padding:5) () in
772   let tree =
773    GTree.tree ~selection_mode:`BROWSE ~packing:sw#add_with_viewport () in
774   let tree_item =
775    GTree.tree_item ~label:label ~packing:tree#append () in
776   let hbox =
777    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
778   let updateb =
779    GButton.button ~label:"Update"
780     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
781   let quitb =
782    GButton.button ~label:"Quit"
783     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
784 object (self)
785   method show () = win#show ()
786   initializer
787     mktree theory_selection_changed theory_rendering_window tree_item1
788      (Dir ("theory:/",theoryuritree));
789     mktree selection_changed rendering_window tree_item
790      (Dir ("cic:/",uritree));
791
792     (* signal handlers here *)
793     ignore (tree_item1#connect#select
794      ~callback:(theory_selection_changed theory_rendering_window None)) ;
795     ignore (tree_item#connect#select
796      ~callback:(selection_changed rendering_window None)) ;
797     ignore (win#connect#destroy ~callback:GMain.Main.quit) ;
798     ignore (quitb#connect#clicked GMain.Main.quit) ;
799     ignore(updateb#connect#clicked (updateb_pressed
800      theory_rendering_window rendering_window (ref sw1, ref sw, hbox1) mktree))
801 end;;
802
803
804 (* MAIN *)
805
806 let _ =
807  build_uri_tree () ;
808  let output =
809   ref (GMathView.math_view ~use_t1_lib:false ~width:400 ~height:380 ())
810  and label = GMisc.label ~text:"???" () in
811   let annotation_window = new annotation_window output label in
812   let rendering_window = new rendering_window annotation_window output label in
813   let theory_rendering_window = new theory_rendering_window rendering_window in
814   let selection_window =
815    new selection_window theory_rendering_window rendering_window
816   in
817    selection_window#show () ;
818    GMain.Main.main ()
819 ;;