]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/gTopLevel.ml
* Scratch window added
[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 mml_of_cic_term term =
213  let context =
214   match !ProofEngine.goal with
215      None -> []
216    | Some (_,(context,_)) -> context
217  in
218   let metasenv =
219    match !ProofEngine.proof with
220       None -> []
221     | Some (_,metasenv,_,_) -> metasenv
222   in
223    let sequent_gdome,ids_to_terms,ids_to_father_ids =
224     SequentPp.XmlPp.print_sequent metasenv (context,term)
225    in
226     let sequent_doc =
227      Xml2Gdome.document_of_xml domImpl sequent_gdome
228     in
229      applyStylesheets sequent_doc sequent_styles sequent_args
230      (*CSC: magari prima o poi serve*)
231      (*current_scratch_infos := Some (ids_to_terms,ids_to_father_ids)*)
232 ;;
233
234 let output_html outputhtml msg =
235  htmlheader_and_content := !htmlheader_and_content ^ msg ;
236  outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
237  outputhtml#set_topline (-1)
238 ;;
239
240 (***********************)
241 (*       TACTICS       *)
242 (***********************)
243
244 let call_tactic tactic rendering_window () =
245  let proofw = (rendering_window#proofw : GMathView.math_view) in
246  let output = (rendering_window#output : GMathView.math_view) in
247  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
248  let savedproof = !ProofEngine.proof in
249  let savedgoal  = !ProofEngine.goal in
250   begin
251    try
252     tactic () ;
253     refresh_sequent proofw ;
254     refresh_proof output
255    with
256     e ->
257      output_html outputhtml
258       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
259      ProofEngine.proof := savedproof ;
260      ProofEngine.goal := savedgoal ;
261   end
262 ;;
263
264 let call_tactic_with_input tactic rendering_window () =
265  let proofw = (rendering_window#proofw : GMathView.math_view) in
266  let output = (rendering_window#output : GMathView.math_view) in
267  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
268  let inputt = (rendering_window#inputt : GEdit.text) in
269  let savedproof = !ProofEngine.proof in
270  let savedgoal  = !ProofEngine.goal in
271 (*CSC: Gran cut&paste da sotto... *)
272   let inputlen = inputt#length in
273   let input = inputt#get_chars 0 inputlen ^ "\n" in
274    let lexbuf = Lexing.from_string input in
275    let curi =
276     match !ProofEngine.proof with
277        None -> assert false
278      | Some (curi,_,_,_) -> curi
279    in
280    let context =
281     List.map
282      (function (_,n,_) -> n)
283      (match !ProofEngine.goal with
284          None -> assert false
285        | Some (_,(ctx,_)) -> ctx
286      )
287    in
288     try
289      while true do
290       match
291        CicTextualParserContext.main curi context CicTextualLexer.token lexbuf
292       with
293          None -> ()
294        | Some expr ->
295           tactic expr ;
296           refresh_sequent proofw ;
297           refresh_proof output
298      done
299     with
300        CicTextualParser0.Eof ->
301         inputt#delete_text 0 inputlen
302      | e ->
303 prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
304         output_html outputhtml
305          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>");
306         ProofEngine.proof := savedproof ;
307         ProofEngine.goal := savedgoal
308 ;;
309
310 let call_tactic_with_goal_input tactic rendering_window () =
311  let module L = LogicalOperations in
312  let module G = Gdome in
313   let proofw = (rendering_window#proofw : GMathView.math_view) in
314   let output = (rendering_window#output : GMathView.math_view) in
315   let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
316   let savedproof = !ProofEngine.proof in
317   let savedgoal  = !ProofEngine.goal in
318    match proofw#get_selection with
319      Some node ->
320       let xpath =
321        ((node : Gdome.element)#getAttributeNS
322          ~namespaceURI:helmns
323          ~localName:(G.domString "xref"))#to_string
324       in
325        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
326        else
327         begin
328          try
329           match !current_goal_infos with
330              Some (ids_to_terms, ids_to_father_ids) ->
331               let id = xpath in
332                tactic (Hashtbl.find ids_to_terms id) ;
333                refresh_sequent rendering_window#proofw ;
334                refresh_proof rendering_window#output
335            | None -> assert false (* "ERROR: No current term!!!" *)
336          with
337           e ->
338            prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
339            output_html outputhtml
340             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
341         end
342    | None ->
343       output_html outputhtml
344        ("<h1 color=\"red\">No term selected</h1>")
345 ;;
346
347 let call_tactic_with_input_and_goal_input tactic rendering_window () =
348  let module L = LogicalOperations in
349  let module G = Gdome in
350   let proofw = (rendering_window#proofw : GMathView.math_view) in
351   let output = (rendering_window#output : GMathView.math_view) in
352   let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
353   let inputt = (rendering_window#inputt : GEdit.text) in
354   let savedproof = !ProofEngine.proof in
355   let savedgoal  = !ProofEngine.goal in
356    match proofw#get_selection with
357      Some node ->
358       let xpath =
359        ((node : Gdome.element)#getAttributeNS
360          ~namespaceURI:helmns
361          ~localName:(G.domString "xref"))#to_string
362       in
363        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
364        else
365         begin
366          try
367           match !current_goal_infos with
368              Some (ids_to_terms, ids_to_father_ids) ->
369               let id = xpath in
370                (* Let's parse the input *)
371                let inputlen = inputt#length in
372                let input = inputt#get_chars 0 inputlen ^ "\n" in
373                 let lexbuf = Lexing.from_string input in
374                 let curi =
375                  match !ProofEngine.proof with
376                     None -> assert false
377                   | Some (curi,_,_,_) -> curi
378                 in
379                 let context =
380                  List.map
381                   (function (_,n,_) -> n)
382                   (match !ProofEngine.goal with
383                       None -> assert false
384                     | Some (_,(ctx,_)) -> ctx
385                   )
386                 in
387                  begin
388                   try
389                    while true do
390                     match
391                      CicTextualParserContext.main curi context
392                       CicTextualLexer.token lexbuf
393                     with
394                        None -> ()
395                      | Some expr ->
396                         tactic ~goal_input:(Hashtbl.find ids_to_terms id)
397                          ~input:expr ;
398                         refresh_sequent proofw ;
399                         refresh_proof output
400                    done
401                   with
402                      CicTextualParser0.Eof ->
403                       inputt#delete_text 0 inputlen
404                  end
405            | None -> assert false (* "ERROR: No current term!!!" *)
406          with
407           e ->
408 prerr_endline ("? " ^ Printexc.to_string e) ; flush stderr ;
409            output_html outputhtml
410             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
411         end
412    | None ->
413       output_html outputhtml
414        ("<h1 color=\"red\">No term selected</h1>")
415 ;;
416
417 let intros rendering_window = call_tactic ProofEngine.intros rendering_window;;
418 let exact rendering_window =
419  call_tactic_with_input ProofEngine.exact rendering_window
420 ;;
421 let apply rendering_window =
422  call_tactic_with_input ProofEngine.apply rendering_window
423 ;;
424 let elimintros rendering_window =
425  call_tactic_with_input ProofEngine.elim_intros rendering_window
426 ;;
427 let whd rendering_window =
428  call_tactic_with_goal_input ProofEngine.whd rendering_window
429 ;;
430 let reduce rendering_window =
431  call_tactic_with_goal_input ProofEngine.reduce rendering_window
432 ;;
433 let simpl rendering_window =
434  call_tactic_with_goal_input ProofEngine.simpl rendering_window
435 ;;
436 let fold rendering_window =
437  call_tactic_with_input ProofEngine.fold rendering_window
438 ;;
439 let cut rendering_window =
440  call_tactic_with_input ProofEngine.cut rendering_window
441 ;;
442 let change rendering_window =
443  call_tactic_with_input_and_goal_input ProofEngine.change rendering_window
444 ;;
445
446
447
448
449 (**********************)
450 (*   END OF TACTICS   *)
451 (**********************)
452
453 exception OpenConjecturesStillThere;;
454 exception WrongProof;;
455
456 let save rendering_window () =
457  match !ProofEngine.proof with
458     None -> assert false
459   | Some (uri,[],bo,ty) ->
460      if CicReduction.are_convertible (CicTypeChecker.type_of_aux' [] [] bo) ty then
461       begin
462        (*CSC: Wrong: [] is just plainly wrong *)
463        let proof = Cic.Definition (UriManager.name_of_uri uri,bo,ty,[]) in
464         let
465          (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
466           ids_to_inner_types)
467         =
468          Cic2acic.acic_object_of_cic_object proof
469         in
470          let mml =
471           mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types
472          in
473           (rendering_window#output : GMathView.math_view)#load_tree mml ;
474           current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
475       end
476      else
477       raise WrongProof
478   | _ -> raise OpenConjecturesStillThere
479 ;;
480
481 let proveit rendering_window () =
482  let module L = LogicalOperations in
483  let module G = Gdome in
484  match rendering_window#output#get_selection with
485    Some node ->
486     let xpath =
487      ((node : Gdome.element)#getAttributeNS
488      (*CSC: OCAML DIVERGE
489      ((element : G.element)#getAttributeNS
490      *)
491        ~namespaceURI:helmns
492        ~localName:(G.domString "xref"))#to_string
493     in
494      if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
495      else
496       begin
497        try
498         match !current_cic_infos with
499            Some (ids_to_terms, ids_to_father_ids) ->
500             let id = xpath in
501              if L.to_sequent id ids_to_terms ids_to_father_ids then
502               refresh_proof rendering_window#output ;
503              refresh_sequent rendering_window#proofw
504          | None -> assert false (* "ERROR: No current term!!!" *)
505        with
506         e -> print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
507       end
508  | None -> assert false (* "ERROR: No selection!!!" *)
509 ;;
510
511 exception NotADefinition;;
512
513 let open_ rendering_window () =
514  let inputt = (rendering_window#inputt : GEdit.text) in
515  let oldinputt = (rendering_window#oldinputt : GEdit.text) in
516  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
517  let output = (rendering_window#output : GMathView.math_view) in
518  let proofw = (rendering_window#proofw : GMathView.math_view) in
519   let inputlen = inputt#length in
520   let input = inputt#get_chars 0 inputlen ^ "\n" in
521    try
522     let uri = UriManager.uri_of_string ("cic:" ^ input) in
523      CicTypeChecker.typecheck uri ;
524      let metasenv,bo,ty =
525       match CicEnvironment.get_cooked_obj uri 0 with
526          Cic.Definition (_,bo,ty,_) -> [],bo,ty
527        | Cic.CurrentProof (_,metasenv,bo,ty) -> metasenv,bo,ty
528        | Cic.Axiom _
529        | Cic.Variable _
530        | Cic.InductiveDefinition _ -> raise NotADefinition
531      in
532       ProofEngine.proof :=
533        Some (uri, metasenv, bo, ty) ;
534       ProofEngine.goal := None ;
535       inputt#delete_text 0 inputlen ;
536       ignore(oldinputt#insert_text input oldinputt#length) ;
537       refresh_sequent proofw ;
538       refresh_proof output ;
539    with
540     e ->
541      output_html outputhtml
542       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
543 ;;
544
545 let state rendering_window () =
546  let inputt = (rendering_window#inputt : GEdit.text) in
547  let oldinputt = (rendering_window#oldinputt : GEdit.text) in
548  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
549  let output = (rendering_window#output : GMathView.math_view) in
550  let proofw = (rendering_window#proofw : GMathView.math_view) in
551   let inputlen = inputt#length in
552   let input = inputt#get_chars 0 inputlen ^ "\n" in
553    (* Do something interesting *)
554    let lexbuf = Lexing.from_string input in
555     try
556      while true do
557       (* Execute the actions *)
558       match CicTextualParser.main CicTextualLexer.token lexbuf with
559          None -> ()
560        | Some expr ->
561           try
562            let _  = CicTypeChecker.type_of_aux' [] [] expr in
563             ProofEngine.proof :=
564              Some (UriManager.uri_of_string "cic:/dummy.con",
565                     [1,expr], Cic.Meta 1, expr) ;
566             ProofEngine.goal := Some (1,([],expr)) ;
567             refresh_sequent proofw ;
568             refresh_proof output ;
569           with
570            e ->
571             print_endline ("? " ^ CicPp.ppterm expr) ;
572             raise e
573      done
574     with
575        CicTextualParser0.Eof ->
576         inputt#delete_text 0 inputlen ;
577         ignore(oldinputt#insert_text input oldinputt#length)
578      | e ->
579         print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
580 ;;
581
582 let check rendering_window scratch_window () =
583  let inputt = (rendering_window#inputt : GEdit.text) in
584  let oldinputt = (rendering_window#oldinputt : GEdit.text) in
585  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
586  let output = (rendering_window#output : GMathView.math_view) in
587  let proofw = (rendering_window#proofw : GMathView.math_view) in
588   let inputlen = inputt#length in
589   let input = inputt#get_chars 0 inputlen ^ "\n" in
590   let curi,metasenv =
591    match !ProofEngine.proof with
592       None -> assert false
593     | Some (curi,metasenv,_,_) -> curi,metasenv
594   in
595   let ciccontext,names_context =
596    let context =
597     match !ProofEngine.goal with
598        None -> assert false
599      | Some (_,(ctx,_)) -> ctx
600    in
601     ProofEngine.cic_context_of_context context,
602      List.map (function (_,n,_) -> n) context
603   in
604    (* Do something interesting *)
605    let lexbuf = Lexing.from_string input in
606     try
607      while true do
608       (* Execute the actions *)
609       match
610        CicTextualParserContext.main curi names_context CicTextualLexer.token
611         lexbuf
612       with
613          None -> ()
614        | Some expr ->
615           try
616            let ty  = CicTypeChecker.type_of_aux' metasenv ciccontext expr in
617             let mml = mml_of_cic_term ty in
618              scratch_window#show () ;
619              scratch_window#display ~dom:mml
620           with
621            e ->
622             print_endline ("? " ^ CicPp.ppterm expr) ;
623             raise e
624      done
625     with
626        CicTextualParser0.Eof ->
627         inputt#delete_text 0 inputlen ;
628         ignore(oldinputt#insert_text input oldinputt#length)
629      | e ->
630         print_endline ("Error: " ^ Printexc.to_string e) ; flush stdout
631 ;;
632
633 let choose_selection
634      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
635 =
636  let module G = Gdome in
637   let rec aux element =
638    if element#hasAttributeNS
639        ~namespaceURI:helmns
640        ~localName:(G.domString "xref")
641    then
642      mmlwidget#set_selection (Some element)
643    else
644       match element#get_parentNode with
645          None -> assert false
646        (*CSC: OCAML DIVERGES!
647        | Some p -> aux (new G.element_of_node p)
648        *)
649        | Some p -> aux (new Gdome.element_of_node p)
650   in
651    match element with
652      Some x -> aux x
653    | None   -> mmlwidget#set_selection None
654 ;;
655
656 (* STUFF TO BUILD THE GTK INTERFACE *)
657
658 (* Stuff for the widget settings *)
659
660 let export_to_postscript (output : GMathView.math_view) () =
661  output#export_to_postscript ~filename:"output.ps" ();
662 ;;
663
664 let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
665  button_set_kerning button_set_transparency button_export_to_postscript
666  button_t1 ()
667 =
668  let is_set = button_t1#active in
669   output#set_font_manager_type
670    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
671   if is_set then
672    begin
673     button_set_anti_aliasing#misc#set_sensitive true ;
674     button_set_kerning#misc#set_sensitive true ;
675     button_set_transparency#misc#set_sensitive true ;
676     button_export_to_postscript#misc#set_sensitive true ;
677    end
678   else
679    begin
680     button_set_anti_aliasing#misc#set_sensitive false ;
681     button_set_kerning#misc#set_sensitive false ;
682     button_set_transparency#misc#set_sensitive false ;
683     button_export_to_postscript#misc#set_sensitive false ;
684    end
685 ;;
686
687 let set_anti_aliasing output button_set_anti_aliasing () =
688  output#set_anti_aliasing button_set_anti_aliasing#active
689 ;;
690
691 let set_kerning output button_set_kerning () =
692  output#set_kerning button_set_kerning#active
693 ;;
694
695 let set_transparency output button_set_transparency () =
696  output#set_transparency button_set_transparency#active
697 ;;
698
699 let changefont output font_size_spinb () =
700  output#set_font_size font_size_spinb#value_as_int
701 ;;
702
703 let set_log_verbosity output log_verbosity_spinb () =
704  output#set_log_verbosity log_verbosity_spinb#value_as_int
705 ;;
706
707 class settings_window (output : GMathView.math_view) sw
708  button_export_to_postscript selection_changed_callback
709 =
710  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
711  let vbox =
712   GPack.vbox ~packing:settings_window#add () in
713  let table =
714   GPack.table
715    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
716    ~border_width:5 ~packing:vbox#add () in
717  let button_t1 =
718   GButton.toggle_button ~label:"activate t1 fonts"
719    ~packing:(table#attach ~left:0 ~top:0) () in
720  let button_set_anti_aliasing =
721   GButton.toggle_button ~label:"set_anti_aliasing"
722    ~packing:(table#attach ~left:0 ~top:1) () in
723  let button_set_kerning =
724   GButton.toggle_button ~label:"set_kerning"
725    ~packing:(table#attach ~left:1 ~top:1) () in
726  let button_set_transparency =
727   GButton.toggle_button ~label:"set_transparency"
728    ~packing:(table#attach ~left:2 ~top:1) () in
729  let table =
730   GPack.table
731    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
732    ~border_width:5 ~packing:vbox#add () in
733  let font_size_label =
734   GMisc.label ~text:"font size:"
735    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
736  let font_size_spinb =
737   let sadj =
738    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
739   in
740    GEdit.spin_button 
741     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
742  let log_verbosity_label =
743   GMisc.label ~text:"log verbosity:"
744    ~packing:(table#attach ~left:0 ~top:1) () in
745  let log_verbosity_spinb =
746   let sadj =
747    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
748   in
749    GEdit.spin_button 
750     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
751  let hbox =
752   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
753  let closeb =
754   GButton.button ~label:"Close"
755    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
756 object(self)
757  method show = settings_window#show
758  initializer
759   button_set_anti_aliasing#misc#set_sensitive false ;
760   button_set_kerning#misc#set_sensitive false ;
761   button_set_transparency#misc#set_sensitive false ;
762   (* Signals connection *)
763   ignore(button_t1#connect#clicked
764    (activate_t1 output button_set_anti_aliasing button_set_kerning
765     button_set_transparency button_export_to_postscript button_t1)) ;
766   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
767   ignore(button_set_anti_aliasing#connect#toggled
768    (set_anti_aliasing output button_set_anti_aliasing));
769   ignore(button_set_kerning#connect#toggled
770    (set_kerning output button_set_kerning)) ;
771   ignore(button_set_transparency#connect#toggled
772    (set_transparency output button_set_transparency)) ;
773   ignore(log_verbosity_spinb#connect#changed
774    (set_log_verbosity output log_verbosity_spinb)) ;
775   ignore(closeb#connect#clicked settings_window#misc#hide)
776 end;;
777
778 (* Scratch window *)
779
780 class scratch_window () =
781  let window =
782   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
783  let mmlwidget =
784   GMathView.math_view ~packing:(window#add) ~width:400 ~height:280 () in
785 object(self)
786  method display = mmlwidget#load_tree
787  method show = window#show
788  initializer
789   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true ))
790 end;;
791
792 (* Main window *)
793
794 class rendering_window output proofw (label : GMisc.label) =
795  let window =
796   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
797  let hbox0 =
798   GPack.hbox ~packing:window#add () in
799  let vbox =
800   GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
801  let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
802  let scrolled_window0 =
803   GBin.scrolled_window ~border_width:10
804    ~packing:(vbox#pack ~expand:true ~padding:5) () in
805  let _ = scrolled_window0#add output#coerce in
806  let hbox1 =
807   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
808  let settingsb =
809   GButton.button ~label:"Settings"
810    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
811  let button_export_to_postscript =
812   GButton.button ~label:"export_to_postscript"
813   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
814  let saveb =
815   GButton.button ~label:"Save"
816    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
817  let closeb =
818   GButton.button ~label:"Close"
819    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
820  let hbox2 =
821   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
822  let proveitb =
823   GButton.button ~label:"Prove It"
824    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
825  let oldinputt = GEdit.text ~editable:false ~width:400 ~height:180
826    ~packing:(vbox#pack ~padding:5) () in
827  let hbox4 =
828   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
829  let stateb =
830   GButton.button ~label:"State"
831    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
832  let openb =
833   GButton.button ~label:"Open"
834    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
835  let checkb =
836   GButton.button ~label:"Check"
837    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
838  let inputt = GEdit.text ~editable:true ~width:400 ~height: 100
839    ~packing:(vbox#pack ~padding:5) () in
840  let vbox1 =
841   GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
842  let scrolled_window1 =
843   GBin.scrolled_window ~border_width:10
844    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
845  let _ = scrolled_window1#add proofw#coerce in
846  let hbox3 =
847   GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
848  let exactb =
849   GButton.button ~label:"Exact"
850    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
851  let introsb =
852   GButton.button ~label:"Intros"
853    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
854  let applyb =
855   GButton.button ~label:"Apply"
856    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
857  let elimintrosb =
858   GButton.button ~label:"ElimIntros"
859    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
860  let whdb =
861   GButton.button ~label:"Whd"
862    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
863  let reduceb =
864   GButton.button ~label:"Reduce"
865    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
866  let simplb =
867   GButton.button ~label:"Simpl"
868    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
869  let foldb =
870   GButton.button ~label:"Fold"
871    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
872  let cutb =
873   GButton.button ~label:"Cut"
874    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
875  let changeb =
876   GButton.button ~label:"Change"
877    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
878  let outputhtml =
879   GHtml.xmhtml
880    ~source:"<html><body bgColor=\"white\"></body></html>"
881    ~width:400 ~height: 200
882    ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5)
883    ~show:true () in
884  let scratch_window = new scratch_window () in
885 object(self)
886  method outputhtml = outputhtml
887  method oldinputt = oldinputt
888  method inputt = inputt
889  method output = (output : GMathView.math_view)
890  method proofw = (proofw : GMathView.math_view)
891  method show () = window#show ()
892  initializer
893   button_export_to_postscript#misc#set_sensitive false ;
894
895   (* signal handlers here *)
896   ignore(output#connect#selection_changed
897    (function elem -> proofw#unload ; choose_selection output elem)) ;
898   ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
899   ignore(closeb#connect#clicked (fun _ -> GMain.Main.quit ())) ;
900   let settings_window = new settings_window output scrolled_window0
901    button_export_to_postscript (choose_selection output) in
902   ignore(settingsb#connect#clicked settings_window#show) ;
903   ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
904   ignore(saveb#connect#clicked (save self)) ;
905   ignore(proveitb#connect#clicked (proveit self)) ;
906   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
907   ignore(stateb#connect#clicked (state self)) ;
908   ignore(openb#connect#clicked (open_ self)) ;
909   ignore(checkb#connect#clicked (check self scratch_window)) ;
910   ignore(exactb#connect#clicked (exact self)) ;
911   ignore(applyb#connect#clicked (apply self)) ;
912   ignore(elimintrosb#connect#clicked (elimintros self)) ;
913   ignore(whdb#connect#clicked (whd self)) ;
914   ignore(reduceb#connect#clicked (reduce self)) ;
915   ignore(simplb#connect#clicked (simpl self)) ;
916   ignore(foldb#connect#clicked (fold self)) ;
917   ignore(cutb#connect#clicked (cut self)) ;
918   ignore(changeb#connect#clicked (change self)) ;
919   ignore(introsb#connect#clicked (intros self)) ;
920   Logger.log_callback :=
921    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
922 end;;
923
924 (* MAIN *)
925
926 let initialize_everything () =
927  let module U = Unix in
928   let output = GMathView.math_view ~width:400 ~height:280 ()
929   and proofw = GMathView.math_view ~width:400 ~height:275 ()
930   and label = GMisc.label ~text:"gTopLevel" () in
931     let rendering_window =
932      new rendering_window output proofw label
933     in
934      rendering_window#show () ;
935      GMain.Main.main ()
936 ;;
937
938 let _ =
939  CicCooking.init () ;
940  ignore (GtkMain.Main.init ()) ;
941  initialize_everything ()
942 ;;