]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/gTopLevel.ml
* Many improvements
[helm.git] / helm / gTopLevel / gTopLevel.ml
1 (* Copyright (C) 2000, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 (******************************************************************************)
27 (*                                                                            *)
28 (*                               PROJECT HELM                                 *)
29 (*                                                                            *)
30 (*                Claudio Sacerdoti Coen <sacerdot@cs.unibo.it>               *)
31 (*                                 06/01/2002                                 *)
32 (*                                                                            *)
33 (*                                                                            *)
34 (******************************************************************************)
35
36 (* GLOBAL CONSTANTS *)
37
38 let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
39
40 let htmlheader =
41  "<html>" ^
42  " <body bgColor=\"white\">"
43 ;;
44
45 let htmlfooter =
46  " </body>" ^
47  "</html>"
48 ;;
49
50 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
51
52 let htmlheader_and_content = ref htmlheader;;
53
54 let current_cic_infos = ref None;;
55
56
57 (* MISC FUNCTIONS *)
58
59 let domImpl = Gdome.domImplementation ();;
60
61 let parseStyle name =
62  let style =
63   domImpl#createDocumentFromURI
64 (*
65    ~uri:("http://phd.cs.unibo.it:8081/getxslt?uri=" ^ name) ?mode:None
66 *)
67    ~uri:("styles/" ^ name) ()
68  in
69   Gdome_xslt.processStylesheet style
70 ;;
71
72 let d_c = parseStyle "drop_coercions.xsl";;
73 let tc1 = parseStyle "objtheorycontent.xsl";;
74 let hc2 = parseStyle "content_to_html.xsl";;
75 let l   = parseStyle "link.xsl";;
76
77 let c1 = parseStyle "rootcontent.xsl";;
78 let g  = parseStyle "genmmlid.xsl";;
79 let c2 = parseStyle "annotatedpres.xsl";;
80
81
82 let getterURL = Configuration.getter_url;;
83 let processorURL = Configuration.processor_url;;
84 (*
85 let processorURL = "http://phd.cs.unibo.it:8080/helm/servelt/uwobo/";;
86 let getterURL = "http://phd.cs.unibo.it:8081/";;
87 let processorURL = "http://localhost:8080/helm/servelt/uwobo/";;
88 let getterURL = "http://localhost:8081/";;
89 *)
90
91 let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
92 let mml_args =
93  ["processorURL", "'" ^ processorURL ^ "'" ;
94   "getterURL", "'" ^ getterURL ^ "'" ;
95   "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
96   "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
97   "UNICODEvsSYMBOL", "'symbol'" ;
98   "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
99   "encoding", "'iso-8859-1'" ;
100   "media-type", "'text/html'" ;
101   "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
102   "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
103   "naturalLanguage", "'yes'" ;
104   "annotations", "'no'" ;
105   "explodeall", "'true()'" ;
106   "topurl", "'http://phd.cs.unibo.it/helm'" ;
107   "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
108 ;;
109
110 let sequent_styles = [d_c ; c1 ; g ; c2 ; l];;
111 let sequent_args =
112  ["processorURL", "'" ^ processorURL ^ "'" ;
113   "getterURL", "'" ^ getterURL ^ "'" ;
114   "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
115   "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
116   "UNICODEvsSYMBOL", "'symbol'" ;
117   "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
118   "encoding", "'iso-8859-1'" ;
119   "media-type", "'text/html'" ;
120   "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
121   "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
122   "naturalLanguage", "'no'" ;
123   "annotations", "'no'" ;
124   "explodeall", "'true()'" ;
125   "topurl", "'http://phd.cs.unibo.it/helm'" ;
126   "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
127 ;;
128
129 let parse_file filename =
130  let inch = open_in filename in
131   let rec read_lines () =
132    try
133     let line = input_line inch in
134      line ^ read_lines ()
135    with
136     End_of_file -> ""
137   in
138    read_lines ()
139 ;;
140
141 let applyStylesheets input styles args =
142  List.fold_left (fun i style -> Gdome_xslt.applyStylesheet i style args)
143   input styles
144 ;;
145
146 let mml_of_cic_object annobj ids_to_inner_sorts ids_to_inner_types =
147  let xml =
148   Cic2Xml.print_object
149    (UriManager.uri_of_string "cic:/dummy.con") ids_to_inner_sorts annobj 
150  in
151  let xmlinnertypes =
152   Cic2Xml.print_inner_types
153    (UriManager.uri_of_string "cic:/dummy.con") ids_to_inner_sorts
154    ids_to_inner_types
155  in
156   let input = Xml2Gdome.document_of_xml domImpl xml in
157 (*CSC: We save the innertypes to disk so that we can retrieve them in the  *)
158 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
159 (*CSC: local.                                                              *)
160    Xml.pp xmlinnertypes (Some "/public/sacerdot/innertypes") ;
161    let output = applyStylesheets input mml_styles mml_args in
162     output
163 ;;
164
165
166 (* CALLBACKS *)
167
168 let refresh_proof (output : GMathView.math_view) =
169  let currentproof =
170   match !ProofEngine.proof with
171      None -> assert false
172    | Some (metasenv,bo,ty) -> Cic.CurrentProof ("unnamed", metasenv, bo, ty)
173  in
174  let
175   (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,ids_to_inner_types)
176  =
177   Cic2acic.acic_object_of_cic_object currentproof
178  in
179   let mml = mml_of_cic_object acic ids_to_inner_sorts ids_to_inner_types in
180    output#load_tree mml ;
181    current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
182 ;;
183
184 let refresh_sequent (proofw : GMathView.math_view) =
185  match !ProofEngine.goal with
186     None -> proofw#unload
187   | Some (_,currentsequent) ->
188      let metasenv =
189       match !ProofEngine.proof with
190          None -> assert false
191        | Some (metasenv,_,_) -> metasenv
192      in
193       let sequent_gdome =
194        SequentPp.XmlPp.print_sequent metasenv currentsequent
195       in
196        let sequent_doc =
197         Xml2Gdome.document_of_xml domImpl sequent_gdome
198        in
199         let sequent_mml =
200          applyStylesheets sequent_doc sequent_styles sequent_args
201         in
202          proofw#load_tree ~dom:sequent_mml
203 (*
204 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
205  ~name:"/public/sacerdot/guruguru1" ~indent:true ()) ;
206 ignore(domImpl#saveDocumentToFile ~doc:sequent_mml
207  ~name:"/public/sacerdot/guruguru2" ~indent:true ())
208 *)
209 ;;
210
211 let output_html outputhtml msg =
212  htmlheader_and_content := !htmlheader_and_content ^ msg ;
213  outputhtml#source (!htmlheader_and_content ^ htmlfooter)
214 ;;
215
216 (***********************)
217 (*       TACTICS       *)
218 (***********************)
219
220 let call_tactic tactic rendering_window () =
221  let proofw = (rendering_window#proofw : GMathView.math_view) in
222  let output = (rendering_window#output : GMathView.math_view) in
223  let output = (rendering_window#output : GMathView.math_view) in
224  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
225  let savedproof = !ProofEngine.proof in
226  let savedgoal  = !ProofEngine.goal in
227   begin
228    try
229     tactic () ;
230     refresh_sequent proofw ;
231     refresh_proof output
232    with
233     e ->
234      output_html outputhtml
235       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
236      ProofEngine.proof := savedproof ;
237      ProofEngine.goal := savedgoal ;
238   end
239 ;;
240
241 let call_tactic_with_input tactic rendering_window () =
242  let proofw = (rendering_window#proofw : GMathView.math_view) in
243  let output = (rendering_window#output : GMathView.math_view) in
244  let output = (rendering_window#output : GMathView.math_view) in
245  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
246  let inputt = (rendering_window#inputt : GEdit.text) in
247  let savedproof = !ProofEngine.proof in
248  let savedgoal  = !ProofEngine.goal in
249 (*CSC: Gran cut&paste da sotto... *)
250   let inputlen = inputt#length in
251   let input = inputt#get_chars 0 inputlen ^ "\n" in
252    let lexbuf = Lexing.from_string input in
253    let context =
254     List.map
255      (function (_,n,_) -> n)
256      (match !ProofEngine.goal with
257          None -> assert false
258        | Some (_,(ctx,_)) -> ctx
259      )
260    in
261     try
262      while true do
263       match
264        CicTextualParserContext.main context CicTextualLexer.token lexbuf
265       with
266          None -> ()
267        | Some expr ->
268           tactic expr ;
269           refresh_sequent proofw ;
270           refresh_proof output
271      done
272     with
273        CicTextualParser0.Eof ->
274         inputt#delete_text 0 inputlen
275      | e ->
276 prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
277         output_html outputhtml
278          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>");
279         ProofEngine.proof := savedproof ;
280         ProofEngine.goal := savedgoal
281 ;;
282
283 let intros rendering_window = call_tactic ProofEngine.intros rendering_window;;
284 let exact rendering_window =
285  call_tactic_with_input ProofEngine.exact rendering_window
286 ;;
287 let apply rendering_window =
288  call_tactic_with_input ProofEngine.apply rendering_window
289 ;;
290
291 (**********************)
292 (*   END OF TACTICS   *)
293 (**********************)
294
295 exception OpenConjecturesStillThere;;
296 exception WrongProof;;
297
298 let save rendering_window () =
299  match !ProofEngine.proof with
300     None -> assert false
301   | Some ([],bo,ty) ->
302      if CicReduction.are_convertible (CicTypeChecker.type_of_aux' [] [] bo) ty then
303       begin
304        (*CSC: Wrong: [] is just plainly wrong *)
305        let proof = Cic.Definition ("unnamed",bo,ty,[]) in
306         let
307          (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
308           ids_to_inner_types)
309         =
310          Cic2acic.acic_object_of_cic_object proof
311         in
312          let mml =
313           mml_of_cic_object acic ids_to_inner_sorts ids_to_inner_types
314          in
315           (rendering_window#output : GMathView.math_view)#load_tree mml ;
316           current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
317       end
318      else
319       raise WrongProof
320   | _ -> raise OpenConjecturesStillThere
321 ;;
322
323 let proveit rendering_window () =
324  let module L = LogicalOperations in
325  let module G = Gdome in
326  match rendering_window#output#get_selection with
327    Some node ->
328     let xpath =
329      ((node : Gdome.element)#getAttributeNS
330      (*CSC: OCAML DIVERGE
331      ((element : G.element)#getAttributeNS
332      *)
333        ~namespaceURI:helmns
334        ~localName:(G.domString "xref"))#to_string
335     in
336      if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
337      else
338       begin
339        try
340         match !current_cic_infos with
341            Some (ids_to_terms, ids_to_father_ids) ->
342             let id = xpath in
343              if L.to_sequent id ids_to_terms ids_to_father_ids then
344               refresh_proof rendering_window#output ;
345              refresh_sequent rendering_window#proofw
346          | None -> assert false (* "ERROR: No current term!!!" *)
347        with
348         e -> print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
349       end
350  | None -> assert false (* "ERROR: No selection!!!" *)
351 ;;
352
353 let state rendering_window () =
354  let inputt = (rendering_window#inputt : GEdit.text) in
355  let oldinputt = (rendering_window#oldinputt : GEdit.text) in
356  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
357  let output = (rendering_window#output : GMathView.math_view) in
358  let proofw = (rendering_window#proofw : GMathView.math_view) in
359   let inputlen = inputt#length in
360   let input = inputt#get_chars 0 inputlen ^ "\n" in
361    (* Do something interesting *)
362    let lexbuf = Lexing.from_string input in
363     try
364      while true do
365       (* Execute the actions *)
366       match CicTextualParser.main CicTextualLexer.token lexbuf with
367          None -> ()
368        | Some expr ->
369           try
370            let _  = CicTypeChecker.type_of_aux' [] [] expr in
371             ProofEngine.proof := Some ([1,expr], Cic.Meta 1, expr) ;
372             ProofEngine.goal := Some (1,([],expr)) ;
373             refresh_sequent proofw ;
374             refresh_proof output ;
375           with
376            e ->
377             print_endline ("? " ^ CicPp.ppterm expr) ;
378             raise e
379      done
380     with
381        CicTextualParser0.Eof ->
382         inputt#delete_text 0 inputlen ;
383         ignore(oldinputt#insert_text input oldinputt#length) ;
384      | e ->
385         print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
386 ;;
387
388 let choose_selection
389      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
390 =
391  let module G = Gdome in
392   let rec aux element =
393    if element#hasAttributeNS
394        ~namespaceURI:helmns
395        ~localName:(G.domString "xref")
396    then
397      mmlwidget#set_selection (Some element)
398    else
399       match element#get_parentNode with
400          None -> assert false
401        (*CSC: OCAML DIVERGES!
402        | Some p -> aux (new G.element_of_node p)
403        *)
404        | Some p -> aux (new Gdome.element_of_node p)
405   in
406    match element with
407      Some x -> aux x
408    | None   -> mmlwidget#set_selection None
409 ;;
410
411 (* STUFF TO BUILD THE GTK INTERFACE *)
412
413 (* Stuff for the widget settings *)
414
415 let export_to_postscript (output : GMathView.math_view) () =
416  output#export_to_postscript ~filename:"output.ps" ();
417 ;;
418
419 let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
420  button_set_kerning button_set_transparency button_export_to_postscript
421  button_t1 ()
422 =
423  let is_set = button_t1#active in
424   output#set_font_manager_type
425    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
426   if is_set then
427    begin
428     button_set_anti_aliasing#misc#set_sensitive true ;
429     button_set_kerning#misc#set_sensitive true ;
430     button_set_transparency#misc#set_sensitive true ;
431     button_export_to_postscript#misc#set_sensitive true ;
432    end
433   else
434    begin
435     button_set_anti_aliasing#misc#set_sensitive false ;
436     button_set_kerning#misc#set_sensitive false ;
437     button_set_transparency#misc#set_sensitive false ;
438     button_export_to_postscript#misc#set_sensitive false ;
439    end
440 ;;
441
442 let set_anti_aliasing output button_set_anti_aliasing () =
443  output#set_anti_aliasing button_set_anti_aliasing#active
444 ;;
445
446 let set_kerning output button_set_kerning () =
447  output#set_kerning button_set_kerning#active
448 ;;
449
450 let set_transparency output button_set_transparency () =
451  output#set_transparency button_set_transparency#active
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 : GMathView.math_view) sw
463  button_export_to_postscript selection_changed_callback
464 =
465  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
466  let vbox =
467   GPack.vbox ~packing:settings_window#add () in
468  let table =
469   GPack.table
470    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
471    ~border_width:5 ~packing:vbox#add () in
472  let button_t1 =
473   GButton.toggle_button ~label:"activate t1 fonts"
474    ~packing:(table#attach ~left:0 ~top:0) () in
475  let button_set_anti_aliasing =
476   GButton.toggle_button ~label:"set_anti_aliasing"
477    ~packing:(table#attach ~left:0 ~top:1) () in
478  let button_set_kerning =
479   GButton.toggle_button ~label:"set_kerning"
480    ~packing:(table#attach ~left:1 ~top:1) () in
481  let button_set_transparency =
482   GButton.toggle_button ~label:"set_transparency"
483    ~packing:(table#attach ~left:2 ~top:1) () in
484  let table =
485   GPack.table
486    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
487    ~border_width:5 ~packing:vbox#add () in
488  let font_size_label =
489   GMisc.label ~text:"font size:"
490    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
491  let font_size_spinb =
492   let sadj =
493    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
494   in
495    GEdit.spin_button 
496     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
497  let log_verbosity_label =
498   GMisc.label ~text:"log verbosity:"
499    ~packing:(table#attach ~left:0 ~top:1) () in
500  let log_verbosity_spinb =
501   let sadj =
502    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
503   in
504    GEdit.spin_button 
505     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
506  let hbox =
507   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
508  let closeb =
509   GButton.button ~label:"Close"
510    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
511 object(self)
512  method show = settings_window#show
513  initializer
514   button_set_anti_aliasing#misc#set_sensitive false ;
515   button_set_kerning#misc#set_sensitive false ;
516   button_set_transparency#misc#set_sensitive false ;
517   (* Signals connection *)
518   ignore(button_t1#connect#clicked
519    (activate_t1 output button_set_anti_aliasing button_set_kerning
520     button_set_transparency button_export_to_postscript button_t1)) ;
521   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
522   ignore(button_set_anti_aliasing#connect#toggled
523    (set_anti_aliasing output button_set_anti_aliasing));
524   ignore(button_set_kerning#connect#toggled
525    (set_kerning output button_set_kerning)) ;
526   ignore(button_set_transparency#connect#toggled
527    (set_transparency output button_set_transparency)) ;
528   ignore(log_verbosity_spinb#connect#changed
529    (set_log_verbosity output log_verbosity_spinb)) ;
530   ignore(closeb#connect#clicked settings_window#misc#hide)
531 end;;
532
533 (* Main windows *)
534
535 class rendering_window output proofw (label : GMisc.label) =
536  let window =
537   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
538  let hbox0 =
539   GPack.hbox ~packing:window#add () in
540  let vbox =
541   GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
542  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
543  let scrolled_window0 =
544   GBin.scrolled_window ~border_width:10
545    ~packing:(vbox#pack ~expand:true ~padding:5) () in
546  let _ = scrolled_window0#add output#coerce in
547  let hbox1 =
548   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
549  let settingsb =
550   GButton.button ~label:"Settings"
551    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
552  let button_export_to_postscript =
553   GButton.button ~label:"export_to_postscript"
554   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
555  let saveb =
556   GButton.button ~label:"Save"
557    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
558  let closeb =
559   GButton.button ~label:"Close"
560    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
561  let hbox2 =
562   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
563  let proveitb =
564   GButton.button ~label:"Prove It"
565    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
566  let oldinputt = GEdit.text ~editable:false ~width:400 ~height:180
567    ~packing:(vbox#pack ~padding:5) () in
568  let stateb =
569   GButton.button ~label:"State"
570    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
571  let inputt = GEdit.text ~editable:true ~width:400 ~height: 100
572    ~packing:(vbox#pack ~padding:5) () in
573  let vbox1 =
574   GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
575  let scrolled_window1 =
576   GBin.scrolled_window ~border_width:10
577    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
578  let _ = scrolled_window1#add proofw#coerce in
579  let hbox3 =
580   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
581  let exactb =
582   GButton.button ~label:"Exact"
583    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
584  let introsb =
585   GButton.button ~label:"Intros"
586    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
587  let applyb =
588   GButton.button ~label:"Apply"
589    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
590  let outputhtml =
591   GHtml.xmhtml
592    ~source:"<html><body bgColor=\"white\"></body></html>"
593    ~width:400 ~height: 200
594    ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5)
595    ~show:true () in
596 object(self)
597  method outputhtml = outputhtml
598  method oldinputt = oldinputt
599  method inputt = inputt
600  method output = (output : GMathView.math_view)
601  method proofw = (proofw : GMathView.math_view)
602  method show () = window#show ()
603  initializer
604   button_export_to_postscript#misc#set_sensitive false ;
605
606   (* signal handlers here *)
607   ignore(output#connect#selection_changed
608    (function elem -> proofw#unload ; choose_selection output elem)) ;
609   ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
610   ignore(closeb#connect#clicked (fun _ -> GMain.Main.quit ())) ;
611   let settings_window = new settings_window output scrolled_window0
612    button_export_to_postscript (choose_selection output) in
613   ignore(settingsb#connect#clicked settings_window#show) ;
614   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
615   ignore(saveb#connect#clicked (save self)) ;
616   ignore(proveitb#connect#clicked (proveit self)) ;
617   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
618   ignore(stateb#connect#clicked (state self)) ;
619   ignore(exactb#connect#clicked (exact self)) ;
620   ignore(applyb#connect#clicked (apply self)) ;
621   ignore(introsb#connect#clicked (intros self)) ;
622   Logger.log_callback :=
623    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
624 end;;
625
626 (* MAIN *)
627
628 let initialize_everything () =
629  let module U = Unix in
630   let output = GMathView.math_view ~width:400 ~height:280 ()
631   and proofw = GMathView.math_view ~width:400 ~height:275 ()
632   and label = GMisc.label ~text:"gTopLevel" () in
633     let rendering_window =
634      new rendering_window output proofw label
635     in
636      rendering_window#show () ;
637      GMain.Main.main ()
638 ;;
639
640 let _ =
641  CicCooking.init () ;
642  initialize_everything ()
643 ;;