]> 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 let current_goal_infos = ref None;;
56
57
58 (* MISC FUNCTIONS *)
59
60 let domImpl = Gdome.domImplementation ();;
61
62 let parseStyle name =
63  let style =
64   domImpl#createDocumentFromURI
65 (*
66    ~uri:("http://phd.cs.unibo.it:8081/getxslt?uri=" ^ name) ?mode:None
67 *)
68    ~uri:("styles/" ^ name) ()
69  in
70   Gdome_xslt.processStylesheet style
71 ;;
72
73 let d_c = parseStyle "drop_coercions.xsl";;
74 let tc1 = parseStyle "objtheorycontent.xsl";;
75 let hc2 = parseStyle "content_to_html.xsl";;
76 let l   = parseStyle "link.xsl";;
77
78 let c1 = parseStyle "rootcontent.xsl";;
79 let g  = parseStyle "genmmlid.xsl";;
80 let c2 = parseStyle "annotatedpres.xsl";;
81
82
83 let getterURL = Configuration.getter_url;;
84 let processorURL = Configuration.processor_url;;
85 (*
86 let processorURL = "http://phd.cs.unibo.it:8080/helm/servelt/uwobo/";;
87 let getterURL = "http://phd.cs.unibo.it:8081/";;
88 let processorURL = "http://localhost:8080/helm/servelt/uwobo/";;
89 let getterURL = "http://localhost:8081/";;
90 *)
91
92 let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
93 let mml_args =
94  ["processorURL", "'" ^ processorURL ^ "'" ;
95   "getterURL", "'" ^ getterURL ^ "'" ;
96   "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
97   "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
98   "UNICODEvsSYMBOL", "'symbol'" ;
99   "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
100   "encoding", "'iso-8859-1'" ;
101   "media-type", "'text/html'" ;
102   "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
103   "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
104   "naturalLanguage", "'yes'" ;
105   "annotations", "'no'" ;
106   "explodeall", "'true()'" ;
107   "topurl", "'http://phd.cs.unibo.it/helm'" ;
108   "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
109 ;;
110
111 let sequent_styles = [d_c ; c1 ; g ; c2 ; l];;
112 let sequent_args =
113  ["processorURL", "'" ^ processorURL ^ "'" ;
114   "getterURL", "'" ^ getterURL ^ "'" ;
115   "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
116   "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
117   "UNICODEvsSYMBOL", "'symbol'" ;
118   "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
119   "encoding", "'iso-8859-1'" ;
120   "media-type", "'text/html'" ;
121   "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
122   "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
123   "naturalLanguage", "'no'" ;
124   "annotations", "'no'" ;
125   "explodeall", "'true()'" ;
126   "topurl", "'http://phd.cs.unibo.it/helm'" ;
127   "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
128 ;;
129
130 let parse_file filename =
131  let inch = open_in filename in
132   let rec read_lines () =
133    try
134     let line = input_line inch in
135      line ^ read_lines ()
136    with
137     End_of_file -> ""
138   in
139    read_lines ()
140 ;;
141
142 let applyStylesheets input styles args =
143  List.fold_left (fun i style -> Gdome_xslt.applyStylesheet i style args)
144   input styles
145 ;;
146
147 let mml_of_cic_object uri annobj ids_to_inner_sorts ids_to_inner_types =
148  let xml =
149   Cic2Xml.print_object uri ids_to_inner_sorts annobj 
150  in
151  let xmlinnertypes =
152   Cic2Xml.print_inner_types uri ids_to_inner_sorts
153    ids_to_inner_types
154  in
155   let input = Xml2Gdome.document_of_xml domImpl xml in
156 (*CSC: We save the innertypes to disk so that we can retrieve them in the  *)
157 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
158 (*CSC: local.                                                              *)
159    Xml.pp xmlinnertypes (Some "/public/sacerdot/innertypes") ;
160    let output = applyStylesheets input mml_styles mml_args in
161     output
162 ;;
163
164
165 (* CALLBACKS *)
166
167 let refresh_proof (output : GMathView.math_view) =
168  let uri,currentproof =
169   match !ProofEngine.proof with
170      None -> assert false
171    | Some (uri,metasenv,bo,ty) ->
172       uri,(Cic.CurrentProof (UriManager.name_of_uri uri, 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 uri 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,ids_to_terms,ids_to_father_ids =
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          current_goal_infos := Some (ids_to_terms,ids_to_father_ids)
204 (*
205 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
206  ~name:"/public/sacerdot/guruguru1" ~indent:true ()) ;
207 ignore(domImpl#saveDocumentToFile ~doc:sequent_mml
208  ~name:"/public/sacerdot/guruguru2" ~indent:true ())
209 *)
210 ;;
211
212 let output_html outputhtml msg =
213  htmlheader_and_content := !htmlheader_and_content ^ msg ;
214  outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
215  outputhtml#set_topline (-1)
216 ;;
217
218 (***********************)
219 (*       TACTICS       *)
220 (***********************)
221
222 let call_tactic tactic rendering_window () =
223  let proofw = (rendering_window#proofw : GMathView.math_view) in
224  let output = (rendering_window#output : GMathView.math_view) in
225  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
226  let savedproof = !ProofEngine.proof in
227  let savedgoal  = !ProofEngine.goal in
228   begin
229    try
230     tactic () ;
231     refresh_sequent proofw ;
232     refresh_proof output
233    with
234     e ->
235      output_html outputhtml
236       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
237      ProofEngine.proof := savedproof ;
238      ProofEngine.goal := savedgoal ;
239   end
240 ;;
241
242 let call_tactic_with_input tactic rendering_window () =
243  let proofw = (rendering_window#proofw : 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 curi =
254     match !ProofEngine.proof with
255        None -> assert false
256      | Some (curi,_,_,_) -> curi
257    in
258    let context =
259     List.map
260      (function (_,n,_) -> n)
261      (match !ProofEngine.goal with
262          None -> assert false
263        | Some (_,(ctx,_)) -> ctx
264      )
265    in
266     try
267      while true do
268       match
269        CicTextualParserContext.main curi context CicTextualLexer.token lexbuf
270       with
271          None -> ()
272        | Some expr ->
273           tactic expr ;
274           refresh_sequent proofw ;
275           refresh_proof output
276      done
277     with
278        CicTextualParser0.Eof ->
279         inputt#delete_text 0 inputlen
280      | e ->
281 prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
282         output_html outputhtml
283          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>");
284         ProofEngine.proof := savedproof ;
285         ProofEngine.goal := savedgoal
286 ;;
287
288 let call_tactic_with_goal_input tactic rendering_window () =
289  let module L = LogicalOperations in
290  let module G = Gdome in
291   let proofw = (rendering_window#proofw : GMathView.math_view) in
292   let output = (rendering_window#output : GMathView.math_view) in
293   let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
294   let savedproof = !ProofEngine.proof in
295   let savedgoal  = !ProofEngine.goal in
296    match proofw#get_selection with
297      Some node ->
298       let xpath =
299        ((node : Gdome.element)#getAttributeNS
300          ~namespaceURI:helmns
301          ~localName:(G.domString "xref"))#to_string
302       in
303        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
304        else
305         begin
306          try
307           match !current_goal_infos with
308              Some (ids_to_terms, ids_to_father_ids) ->
309               let id = xpath in
310                tactic (Hashtbl.find ids_to_terms id) ;
311                refresh_sequent rendering_window#proofw ;
312                refresh_proof rendering_window#output
313            | None -> assert false (* "ERROR: No current term!!!" *)
314          with
315           e ->
316            prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
317            output_html outputhtml
318             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
319         end
320    | None ->
321       output_html outputhtml
322        ("<h1 color=\"red\">No term selected</h1>")
323 ;;
324
325 let call_tactic_with_input_and_goal_input tactic rendering_window () =
326  let module L = LogicalOperations in
327  let module G = Gdome in
328   let proofw = (rendering_window#proofw : GMathView.math_view) in
329   let output = (rendering_window#output : GMathView.math_view) in
330   let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
331   let inputt = (rendering_window#inputt : GEdit.text) in
332   let savedproof = !ProofEngine.proof in
333   let savedgoal  = !ProofEngine.goal in
334    match proofw#get_selection with
335      Some node ->
336       let xpath =
337        ((node : Gdome.element)#getAttributeNS
338          ~namespaceURI:helmns
339          ~localName:(G.domString "xref"))#to_string
340       in
341        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
342        else
343         begin
344          try
345           match !current_goal_infos with
346              Some (ids_to_terms, ids_to_father_ids) ->
347               let id = xpath in
348                (* Let's parse the input *)
349                let inputlen = inputt#length in
350                let input = inputt#get_chars 0 inputlen ^ "\n" in
351                 let lexbuf = Lexing.from_string input in
352                 let curi =
353                  match !ProofEngine.proof with
354                     None -> assert false
355                   | Some (curi,_,_,_) -> curi
356                 in
357                 let context =
358                  List.map
359                   (function (_,n,_) -> n)
360                   (match !ProofEngine.goal with
361                       None -> assert false
362                     | Some (_,(ctx,_)) -> ctx
363                   )
364                 in
365                  begin
366                   try
367                    while true do
368                     match
369                      CicTextualParserContext.main curi context
370                       CicTextualLexer.token lexbuf
371                     with
372                        None -> ()
373                      | Some expr ->
374                         tactic ~goal_input:(Hashtbl.find ids_to_terms id)
375                          ~input:expr ;
376                         refresh_sequent proofw ;
377                         refresh_proof output
378                    done
379                   with
380                      CicTextualParser0.Eof ->
381                       inputt#delete_text 0 inputlen
382                  end
383            | None -> assert false (* "ERROR: No current term!!!" *)
384          with
385           e ->
386 prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
387            output_html outputhtml
388             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
389         end
390    | None ->
391       output_html outputhtml
392        ("<h1 color=\"red\">No term selected</h1>")
393 ;;
394
395 let intros rendering_window = call_tactic ProofEngine.intros rendering_window;;
396 let exact rendering_window =
397  call_tactic_with_input ProofEngine.exact rendering_window
398 ;;
399 let apply rendering_window =
400  call_tactic_with_input ProofEngine.apply rendering_window
401 ;;
402 let elimintros rendering_window =
403  call_tactic_with_input ProofEngine.elim_intros rendering_window
404 ;;
405 let whd rendering_window =
406  call_tactic_with_goal_input ProofEngine.whd rendering_window
407 ;;
408 let reduce rendering_window =
409  call_tactic_with_goal_input ProofEngine.reduce rendering_window
410 ;;
411 let simpl rendering_window =
412  call_tactic_with_goal_input ProofEngine.simpl rendering_window
413 ;;
414 let fold rendering_window =
415  call_tactic_with_input ProofEngine.fold rendering_window
416 ;;
417 let cut rendering_window =
418  call_tactic_with_input ProofEngine.cut rendering_window
419 ;;
420 let change rendering_window =
421  call_tactic_with_input_and_goal_input ProofEngine.change rendering_window
422 ;;
423
424
425
426
427 (**********************)
428 (*   END OF TACTICS   *)
429 (**********************)
430
431 exception OpenConjecturesStillThere;;
432 exception WrongProof;;
433
434 let save rendering_window () =
435  match !ProofEngine.proof with
436     None -> assert false
437   | Some (uri,[],bo,ty) ->
438      if CicReduction.are_convertible (CicTypeChecker.type_of_aux' [] [] bo) ty then
439       begin
440        (*CSC: Wrong: [] is just plainly wrong *)
441        let proof = Cic.Definition (UriManager.name_of_uri uri,bo,ty,[]) in
442         let
443          (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
444           ids_to_inner_types)
445         =
446          Cic2acic.acic_object_of_cic_object proof
447         in
448          let mml =
449           mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types
450          in
451           (rendering_window#output : GMathView.math_view)#load_tree mml ;
452           current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
453       end
454      else
455       raise WrongProof
456   | _ -> raise OpenConjecturesStillThere
457 ;;
458
459 let proveit rendering_window () =
460  let module L = LogicalOperations in
461  let module G = Gdome in
462  match rendering_window#output#get_selection with
463    Some node ->
464     let xpath =
465      ((node : Gdome.element)#getAttributeNS
466      (*CSC: OCAML DIVERGE
467      ((element : G.element)#getAttributeNS
468      *)
469        ~namespaceURI:helmns
470        ~localName:(G.domString "xref"))#to_string
471     in
472      if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
473      else
474       begin
475        try
476         match !current_cic_infos with
477            Some (ids_to_terms, ids_to_father_ids) ->
478             let id = xpath in
479              if L.to_sequent id ids_to_terms ids_to_father_ids then
480               refresh_proof rendering_window#output ;
481              refresh_sequent rendering_window#proofw
482          | None -> assert false (* "ERROR: No current term!!!" *)
483        with
484         e -> print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
485       end
486  | None -> assert false (* "ERROR: No selection!!!" *)
487 ;;
488
489 exception NotADefinition;;
490
491 let open_ rendering_window () =
492  let inputt = (rendering_window#inputt : GEdit.text) in
493  let oldinputt = (rendering_window#oldinputt : GEdit.text) in
494  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
495  let output = (rendering_window#output : GMathView.math_view) in
496  let proofw = (rendering_window#proofw : GMathView.math_view) in
497   let inputlen = inputt#length in
498   let input = inputt#get_chars 0 inputlen ^ "\n" in
499    try
500     let uri = UriManager.uri_of_string ("cic:" ^ input) in
501      CicTypeChecker.typecheck uri ;
502      let metasenv,bo,ty =
503       match CicEnvironment.get_cooked_obj uri 0 with
504          Cic.Definition (_,bo,ty,_) -> [],bo,ty
505        | Cic.CurrentProof (_,metasenv,bo,ty) -> metasenv,bo,ty
506        | Cic.Axiom _
507        | Cic.Variable _
508        | Cic.InductiveDefinition _ -> raise NotADefinition
509      in
510       ProofEngine.proof :=
511        Some (uri, metasenv, bo, ty) ;
512       ProofEngine.goal := None ;
513       inputt#delete_text 0 inputlen ;
514       ignore(oldinputt#insert_text input oldinputt#length) ;
515       refresh_sequent proofw ;
516       refresh_proof output ;
517    with
518     e ->
519      output_html outputhtml
520       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
521 ;;
522
523 let state rendering_window () =
524  let inputt = (rendering_window#inputt : GEdit.text) in
525  let oldinputt = (rendering_window#oldinputt : GEdit.text) in
526  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
527  let output = (rendering_window#output : GMathView.math_view) in
528  let proofw = (rendering_window#proofw : GMathView.math_view) in
529   let inputlen = inputt#length in
530   let input = inputt#get_chars 0 inputlen ^ "\n" in
531    (* Do something interesting *)
532    let lexbuf = Lexing.from_string input in
533     try
534      while true do
535       (* Execute the actions *)
536       match CicTextualParser.main CicTextualLexer.token lexbuf with
537          None -> ()
538        | Some expr ->
539           try
540            let _  = CicTypeChecker.type_of_aux' [] [] expr in
541             ProofEngine.proof :=
542              Some (UriManager.uri_of_string "cic:/dummy.con",
543                     [1,expr], Cic.Meta 1, expr) ;
544             ProofEngine.goal := Some (1,([],expr)) ;
545             refresh_sequent proofw ;
546             refresh_proof output ;
547           with
548            e ->
549             print_endline ("? " ^ CicPp.ppterm expr) ;
550             raise e
551      done
552     with
553        CicTextualParser0.Eof ->
554         inputt#delete_text 0 inputlen ;
555         ignore(oldinputt#insert_text input oldinputt#length)
556      | e ->
557         print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
558 ;;
559
560 let choose_selection
561      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
562 =
563  let module G = Gdome in
564   let rec aux element =
565    if element#hasAttributeNS
566        ~namespaceURI:helmns
567        ~localName:(G.domString "xref")
568    then
569      mmlwidget#set_selection (Some element)
570    else
571       match element#get_parentNode with
572          None -> assert false
573        (*CSC: OCAML DIVERGES!
574        | Some p -> aux (new G.element_of_node p)
575        *)
576        | Some p -> aux (new Gdome.element_of_node p)
577   in
578    match element with
579      Some x -> aux x
580    | None   -> mmlwidget#set_selection None
581 ;;
582
583 (* STUFF TO BUILD THE GTK INTERFACE *)
584
585 (* Stuff for the widget settings *)
586
587 let export_to_postscript (output : GMathView.math_view) () =
588  output#export_to_postscript ~filename:"output.ps" ();
589 ;;
590
591 let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
592  button_set_kerning button_set_transparency button_export_to_postscript
593  button_t1 ()
594 =
595  let is_set = button_t1#active in
596   output#set_font_manager_type
597    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
598   if is_set then
599    begin
600     button_set_anti_aliasing#misc#set_sensitive true ;
601     button_set_kerning#misc#set_sensitive true ;
602     button_set_transparency#misc#set_sensitive true ;
603     button_export_to_postscript#misc#set_sensitive true ;
604    end
605   else
606    begin
607     button_set_anti_aliasing#misc#set_sensitive false ;
608     button_set_kerning#misc#set_sensitive false ;
609     button_set_transparency#misc#set_sensitive false ;
610     button_export_to_postscript#misc#set_sensitive false ;
611    end
612 ;;
613
614 let set_anti_aliasing output button_set_anti_aliasing () =
615  output#set_anti_aliasing button_set_anti_aliasing#active
616 ;;
617
618 let set_kerning output button_set_kerning () =
619  output#set_kerning button_set_kerning#active
620 ;;
621
622 let set_transparency output button_set_transparency () =
623  output#set_transparency button_set_transparency#active
624 ;;
625
626 let changefont output font_size_spinb () =
627  output#set_font_size font_size_spinb#value_as_int
628 ;;
629
630 let set_log_verbosity output log_verbosity_spinb () =
631  output#set_log_verbosity log_verbosity_spinb#value_as_int
632 ;;
633
634 class settings_window (output : GMathView.math_view) sw
635  button_export_to_postscript selection_changed_callback
636 =
637  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
638  let vbox =
639   GPack.vbox ~packing:settings_window#add () in
640  let table =
641   GPack.table
642    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
643    ~border_width:5 ~packing:vbox#add () in
644  let button_t1 =
645   GButton.toggle_button ~label:"activate t1 fonts"
646    ~packing:(table#attach ~left:0 ~top:0) () in
647  let button_set_anti_aliasing =
648   GButton.toggle_button ~label:"set_anti_aliasing"
649    ~packing:(table#attach ~left:0 ~top:1) () in
650  let button_set_kerning =
651   GButton.toggle_button ~label:"set_kerning"
652    ~packing:(table#attach ~left:1 ~top:1) () in
653  let button_set_transparency =
654   GButton.toggle_button ~label:"set_transparency"
655    ~packing:(table#attach ~left:2 ~top:1) () in
656  let table =
657   GPack.table
658    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
659    ~border_width:5 ~packing:vbox#add () in
660  let font_size_label =
661   GMisc.label ~text:"font size:"
662    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
663  let font_size_spinb =
664   let sadj =
665    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
666   in
667    GEdit.spin_button 
668     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
669  let log_verbosity_label =
670   GMisc.label ~text:"log verbosity:"
671    ~packing:(table#attach ~left:0 ~top:1) () in
672  let log_verbosity_spinb =
673   let sadj =
674    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
675   in
676    GEdit.spin_button 
677     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
678  let hbox =
679   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
680  let closeb =
681   GButton.button ~label:"Close"
682    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
683 object(self)
684  method show = settings_window#show
685  initializer
686   button_set_anti_aliasing#misc#set_sensitive false ;
687   button_set_kerning#misc#set_sensitive false ;
688   button_set_transparency#misc#set_sensitive false ;
689   (* Signals connection *)
690   ignore(button_t1#connect#clicked
691    (activate_t1 output button_set_anti_aliasing button_set_kerning
692     button_set_transparency button_export_to_postscript button_t1)) ;
693   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
694   ignore(button_set_anti_aliasing#connect#toggled
695    (set_anti_aliasing output button_set_anti_aliasing));
696   ignore(button_set_kerning#connect#toggled
697    (set_kerning output button_set_kerning)) ;
698   ignore(button_set_transparency#connect#toggled
699    (set_transparency output button_set_transparency)) ;
700   ignore(log_verbosity_spinb#connect#changed
701    (set_log_verbosity output log_verbosity_spinb)) ;
702   ignore(closeb#connect#clicked settings_window#misc#hide)
703 end;;
704
705 (* Main windows *)
706
707 class rendering_window output proofw (label : GMisc.label) =
708  let window =
709   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
710  let hbox0 =
711   GPack.hbox ~packing:window#add () in
712  let vbox =
713   GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
714  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
715  let scrolled_window0 =
716   GBin.scrolled_window ~border_width:10
717    ~packing:(vbox#pack ~expand:true ~padding:5) () in
718  let _ = scrolled_window0#add output#coerce in
719  let hbox1 =
720   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
721  let settingsb =
722   GButton.button ~label:"Settings"
723    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
724  let button_export_to_postscript =
725   GButton.button ~label:"export_to_postscript"
726   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
727  let saveb =
728   GButton.button ~label:"Save"
729    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
730  let closeb =
731   GButton.button ~label:"Close"
732    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
733  let hbox2 =
734   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
735  let proveitb =
736   GButton.button ~label:"Prove It"
737    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
738  let oldinputt = GEdit.text ~editable:false ~width:400 ~height:180
739    ~packing:(vbox#pack ~padding:5) () in
740  let hbox4 =
741   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
742  let stateb =
743   GButton.button ~label:"State"
744    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
745  let openb =
746   GButton.button ~label:"Open"
747    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
748  let inputt = GEdit.text ~editable:true ~width:400 ~height: 100
749    ~packing:(vbox#pack ~padding:5) () in
750  let vbox1 =
751   GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
752  let scrolled_window1 =
753   GBin.scrolled_window ~border_width:10
754    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
755  let _ = scrolled_window1#add proofw#coerce in
756  let hbox3 =
757   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
758  let exactb =
759   GButton.button ~label:"Exact"
760    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
761  let introsb =
762   GButton.button ~label:"Intros"
763    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
764  let applyb =
765   GButton.button ~label:"Apply"
766    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
767  let elimintrosb =
768   GButton.button ~label:"ElimIntros"
769    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
770  let whdb =
771   GButton.button ~label:"Whd"
772    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
773  let reduceb =
774   GButton.button ~label:"Reduce"
775    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
776  let simplb =
777   GButton.button ~label:"Simpl"
778    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
779  let foldb =
780   GButton.button ~label:"Fold"
781    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
782  let cutb =
783   GButton.button ~label:"Cut"
784    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
785  let changeb =
786   GButton.button ~label:"Change"
787    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
788  let outputhtml =
789   GHtml.xmhtml
790    ~source:"<html><body bgColor=\"white\"></body></html>"
791    ~width:400 ~height: 200
792    ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5)
793    ~show:true () in
794 object(self)
795  method outputhtml = outputhtml
796  method oldinputt = oldinputt
797  method inputt = inputt
798  method output = (output : GMathView.math_view)
799  method proofw = (proofw : GMathView.math_view)
800  method show () = window#show ()
801  initializer
802   button_export_to_postscript#misc#set_sensitive false ;
803
804   (* signal handlers here *)
805   ignore(output#connect#selection_changed
806    (function elem -> proofw#unload ; choose_selection output elem)) ;
807   ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
808   ignore(closeb#connect#clicked (fun _ -> GMain.Main.quit ())) ;
809   let settings_window = new settings_window output scrolled_window0
810    button_export_to_postscript (choose_selection output) in
811   ignore(settingsb#connect#clicked settings_window#show) ;
812   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
813   ignore(saveb#connect#clicked (save self)) ;
814   ignore(proveitb#connect#clicked (proveit self)) ;
815   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
816   ignore(stateb#connect#clicked (state self)) ;
817   ignore(openb#connect#clicked (open_ self)) ;
818   ignore(exactb#connect#clicked (exact self)) ;
819   ignore(applyb#connect#clicked (apply self)) ;
820   ignore(elimintrosb#connect#clicked (elimintros self)) ;
821   ignore(whdb#connect#clicked (whd self)) ;
822   ignore(reduceb#connect#clicked (reduce self)) ;
823   ignore(simplb#connect#clicked (simpl self)) ;
824   ignore(foldb#connect#clicked (fold self)) ;
825   ignore(cutb#connect#clicked (cut self)) ;
826   ignore(changeb#connect#clicked (change self)) ;
827   ignore(introsb#connect#clicked (intros self)) ;
828   Logger.log_callback :=
829    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
830 end;;
831
832 (* MAIN *)
833
834 let initialize_everything () =
835  let module U = Unix in
836   let output = GMathView.math_view ~width:400 ~height:280 ()
837   and proofw = GMathView.math_view ~width:400 ~height:275 ()
838   and label = GMisc.label ~text:"gTopLevel" () in
839     let rendering_window =
840      new rendering_window output proofw label
841     in
842      rendering_window#show () ;
843      GMain.Main.main ()
844 ;;
845
846 let _ =
847  CicCooking.init () ;
848  ignore (GtkMain.Main.init ()) ;
849  initialize_everything ()
850 ;;