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