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