]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/gTopLevel.ml
c78c5caff5c42e1f59d13f88d88e7575ca5dd54d
[helm.git] / helm / gTopLevel / gTopLevel.ml
1 (* Copyright (C) 2000-2002, 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
37 (* CSC: quick fix: a function from [uri#xpointer(path)] to [uri#path] *)
38 let wrong_xpointer_format_from_wrong_xpointer_format' uri =
39  try
40   let index_sharp =  String.index uri '#' in
41   let index_rest = index_sharp + 10 in
42    let baseuri = String.sub uri 0 index_sharp in
43    let rest = String.sub uri index_rest (String.length uri - index_rest - 1) in
44     baseuri ^ "#" ^ rest
45  with Not_found -> uri
46 ;;
47
48 (* GLOBAL CONSTANTS *)
49
50 let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
51 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
52
53 let htmlheader =
54  "<html>" ^
55  " <body bgColor=\"white\">"
56 ;;
57
58 let htmlfooter =
59  " </body>" ^
60  "</html>"
61 ;;
62
63 let prooffile =
64  try
65   Sys.getenv "GTOPLEVEL_PROOFFILE"
66  with
67   Not_found -> "/public/currentproof"
68 ;;
69
70 let prooffiletype =
71  try
72   Sys.getenv "GTOPLEVEL_PROOFFILETYPE"
73  with
74   Not_found -> "/public/currentprooftype"
75 ;;
76
77 (*CSC: the getter should handle the innertypes, not the FS *)
78
79 let innertypesfile =
80  try
81   Sys.getenv "GTOPLEVEL_INNERTYPESFILE"
82  with
83   Not_found -> "/public/innertypes"
84 ;;
85
86 let constanttypefile =
87  try
88   Sys.getenv "GTOPLEVEL_CONSTANTTYPEFILE"
89  with
90   Not_found -> "/public/constanttype"
91 ;;
92
93 let postgresqlconnectionstring =
94  try
95   Sys.getenv "POSTGRESQL_CONNECTION_STRING"
96  with
97   Not_found -> "host=mowgli.cs.unibo.it dbname=helm_mowgli_new_schema user=helm"
98 ;;
99
100 let empty_id_to_uris = ([],function _ -> None);;
101
102
103 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
104
105 let htmlheader_and_content = ref htmlheader;;
106
107 let current_cic_infos = ref None;;
108 let current_goal_infos = ref None;;
109 let current_scratch_infos = ref None;;
110
111 let id_to_uris = ref empty_id_to_uris;;
112
113 let check_term = ref (fun _ _ _ -> assert false);;
114 let mml_of_cic_term_ref = ref (fun _ _ -> assert false);;
115
116 exception RenderingWindowsNotInitialized;;
117
118 let set_rendering_window,rendering_window =
119  let rendering_window_ref = ref None in
120   (function rw -> rendering_window_ref := Some rw),
121   (function () ->
122     match !rendering_window_ref with
123        None -> raise RenderingWindowsNotInitialized
124      | Some rw -> rw
125   )
126 ;;
127
128 exception SettingsWindowsNotInitialized;;
129
130 let set_settings_window,settings_window =
131  let settings_window_ref = ref None in
132   (function rw -> settings_window_ref := Some rw),
133   (function () ->
134     match !settings_window_ref with
135        None -> raise SettingsWindowsNotInitialized
136      | Some rw -> rw
137   )
138 ;;
139
140 exception OutputHtmlNotInitialized;;
141
142 let set_outputhtml,outputhtml =
143  let outputhtml_ref = ref None in
144   (function rw -> outputhtml_ref := Some rw),
145   (function () ->
146     match !outputhtml_ref with
147        None -> raise OutputHtmlNotInitialized
148      | Some outputhtml -> outputhtml
149   )
150 ;;
151
152 exception QedSetSensitiveNotInitialized;;
153 let qed_set_sensitive =
154  ref (function _ -> raise QedSetSensitiveNotInitialized)
155 ;;
156
157 exception SaveSetSensitiveNotInitialized;;
158 let save_set_sensitive =
159  ref (function _ -> raise SaveSetSensitiveNotInitialized)
160 ;;
161
162 (* COMMAND LINE OPTIONS *)
163
164 let usedb = ref true
165
166 let argspec =
167   [
168     "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
169   ]
170 in
171 Arg.parse argspec ignore ""
172
173 (* A WIDGET TO ENTER CIC TERMS *)
174
175 class term_editor ?packing ?width ?height ?isnotempty_callback () =
176  let input = GEdit.text ~editable:true ?width ?height ?packing () in
177  let _ =
178   match isnotempty_callback with
179      None -> ()
180    | Some callback ->
181       ignore(input#connect#changed (function () -> callback (input#length > 0)))
182  in
183 object(self)
184  method coerce = input#coerce
185  method reset =
186   input#delete_text 0 input#length
187  (* CSC: txt is now a string, but should be of type Cic.term *)
188  method set_term txt =
189   self#reset ;
190   ignore ((input#insert_text txt) ~pos:0)
191  (* CSC: this method should disappear *)
192  method get_as_string =
193   input#get_chars 0 input#length
194  method get_term ~context ~metasenv =
195   let lexbuf = Lexing.from_string (input#get_chars 0 input#length) in
196    CicTextualParserContext.main ~context ~metasenv CicTextualLexer.token lexbuf
197 end
198 ;;
199
200 (* MISC FUNCTIONS *)
201
202 exception IllFormedUri of string;;
203
204 let cic_textual_parser_uri_of_string uri' =
205  try
206   (* Constant *)
207   if String.sub uri' (String.length uri' - 4) 4 = ".con" then
208    CicTextualParser0.ConUri (UriManager.uri_of_string uri')
209   else
210    if String.sub uri' (String.length uri' - 4) 4 = ".var" then
211     CicTextualParser0.VarUri (UriManager.uri_of_string uri')
212    else
213     (try
214       (* Inductive Type *)
215       let uri'',typeno = CicTextualLexer.indtyuri_of_uri uri' in
216        CicTextualParser0.IndTyUri (uri'',typeno)
217      with
218       _ ->
219        (* Constructor of an Inductive Type *)
220        let uri'',typeno,consno =
221         CicTextualLexer.indconuri_of_uri uri'
222        in
223         CicTextualParser0.IndConUri (uri'',typeno,consno)
224     )
225  with
226   _ -> raise (IllFormedUri uri')
227 ;;
228
229 let term_of_cic_textual_parser_uri uri =
230  let module C = Cic in
231  let module CTP = CicTextualParser0 in
232   match uri with
233      CTP.ConUri uri -> C.Const (uri,[])
234    | CTP.VarUri uri -> C.Var (uri,[])
235    | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
236    | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
237 ;;
238
239 let string_of_cic_textual_parser_uri uri =
240  let module C = Cic in
241  let module CTP = CicTextualParser0 in
242   let uri' =
243    match uri with
244       CTP.ConUri uri -> UriManager.string_of_uri uri
245     | CTP.VarUri uri -> UriManager.string_of_uri uri
246     | CTP.IndTyUri (uri,tyno) ->
247        UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
248     | CTP.IndConUri (uri,tyno,consno) ->
249        UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
250         string_of_int consno
251   in
252    (* 4 = String.length "cic:" *)
253    String.sub uri' 4 (String.length uri' - 4)
254 ;;
255
256 let output_html outputhtml msg =
257  htmlheader_and_content := !htmlheader_and_content ^ msg ;
258  outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
259  outputhtml#set_topline (-1)
260 ;;
261
262 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
263
264 (* Check window *)
265
266 let check_window outputhtml uris =
267  let window =
268   GWindow.window
269    ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
270  let notebook =
271   GPack.notebook ~scrollable:true ~packing:window#add () in
272  window#show () ;
273  let render_terms =
274   List.map
275    (function uri ->
276      let scrolled_window =
277       GBin.scrolled_window ~border_width:10
278        ~packing:
279          (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
280        ()
281      in
282       lazy 
283        (let mmlwidget =
284          GMathView.math_view
285           ~packing:scrolled_window#add ~width:400 ~height:280 () in
286         let expr =
287          let term =
288           term_of_cic_textual_parser_uri (cic_textual_parser_uri_of_string uri)
289          in
290           (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
291         in
292          try
293           let mml = !mml_of_cic_term_ref 111 expr in
294 prerr_endline ("### " ^ CicPp.ppterm expr) ;
295            mmlwidget#load_tree ~dom:mml
296          with
297           e ->
298            output_html outputhtml
299             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
300        )
301    ) uris
302  in
303   ignore
304    (notebook#connect#switch_page
305      (function i -> Lazy.force (List.nth render_terms i)))
306 ;;
307
308 exception NoChoice;;
309
310 let
311  interactive_user_uri_choice ~selection_mode ?(ok="Ok")
312   ?(enable_button_for_non_vars=false) ~title ~msg uris
313 =
314  let choices = ref [] in
315  let chosen = ref false in
316  let use_only_constants = ref false in
317  let window =
318   GWindow.dialog ~modal:true ~title ~width:600 () in
319  let lMessage =
320   GMisc.label ~text:msg
321    ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
322  let scrolled_window =
323   GBin.scrolled_window ~border_width:10
324    ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
325  let clist =
326   let expected_height = 18 * List.length uris in
327    let height = if expected_height > 400 then 400 else expected_height in
328     GList.clist ~columns:1 ~packing:scrolled_window#add
329      ~height ~selection_mode () in
330  let _ = List.map (function x -> clist#append [x]) uris in
331  let hbox2 =
332   GPack.hbox ~border_width:0
333    ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
334  let explain_label =
335   GMisc.label ~text:"None of the above. Try this one:"
336    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
337  let manual_input =
338   GEdit.entry ~editable:true
339    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
340  let hbox =
341   GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
342  let okb =
343   GButton.button ~label:ok
344    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
345  let _ = okb#misc#set_sensitive false in
346  let nonvarsb =
347   GButton.button
348    ~packing:
349     (function w ->
350       if enable_button_for_non_vars then
351        hbox#pack ~expand:false ~fill:false ~padding:5 w)
352    ~label:"Try constants only" () in
353  let checkb =
354   GButton.button ~label:"Check"
355    ~packing:(hbox#pack ~padding:5) () in
356  let _ = checkb#misc#set_sensitive false in
357  let cancelb =
358   GButton.button ~label:"Abort"
359    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
360  (* actions *)
361  let check_callback () =
362   assert (List.length !choices > 0) ;
363   check_window (outputhtml ()) !choices
364  in
365   ignore (window#connect#destroy GMain.Main.quit) ;
366   ignore (cancelb#connect#clicked window#destroy) ;
367   ignore
368    (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
369   ignore
370    (nonvarsb#connect#clicked
371      (function () ->
372        use_only_constants := true ;
373        chosen := true ;
374        window#destroy ()
375    )) ;
376   ignore (checkb#connect#clicked check_callback) ;
377   ignore
378    (clist#connect#select_row
379      (fun ~row ~column ~event ->
380        checkb#misc#set_sensitive true ;
381        okb#misc#set_sensitive true ;
382        choices := (List.nth uris row)::!choices)) ;
383   ignore
384    (clist#connect#unselect_row
385      (fun ~row ~column ~event ->
386        choices :=
387         List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
388   ignore
389    (manual_input#connect#changed
390      (fun _ ->
391        if manual_input#text = "" then
392         begin
393          choices := [] ;
394          checkb#misc#set_sensitive false ;
395          okb#misc#set_sensitive false ;
396          clist#misc#set_sensitive true
397         end
398        else
399         begin
400          choices := [manual_input#text] ;
401          clist#unselect_all () ;
402          checkb#misc#set_sensitive true ;
403          okb#misc#set_sensitive true ;
404          clist#misc#set_sensitive false
405         end));
406   window#set_position `CENTER ;
407   window#show () ;
408   GMain.Main.main () ;
409   if !chosen then
410    if !use_only_constants then
411     List.filter
412      (function uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
413      uris
414    else
415     if List.length !choices > 0 then !choices else raise NoChoice
416   else
417    raise NoChoice
418 ;;
419
420 let interactive_interpretation_choice interpretations =
421  let chosen = ref None in
422  let window =
423   GWindow.window
424    ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
425  let vbox = GPack.vbox ~packing:window#add () in
426  let lMessage =
427   GMisc.label
428    ~text:
429     ("Ambiguous input since there are many well-typed interpretations." ^
430      " Please, choose one of them.")
431    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
432  let notebook =
433   GPack.notebook ~scrollable:true
434    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
435  let _ =
436   List.map
437    (function interpretation ->
438      let clist =
439       let expected_height = 18 * List.length interpretation in
440        let height = if expected_height > 400 then 400 else expected_height in
441         GList.clist ~columns:2 ~packing:notebook#append_page ~height
442          ~titles:["id" ; "URI"] ()
443      in
444       ignore
445        (List.map
446          (function (id,uri) ->
447            let n = clist#append [id;uri] in
448             clist#set_row ~selectable:false n
449          ) interpretation
450        ) ;
451       clist#columns_autosize ()
452    ) interpretations in
453  let hbox =
454   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
455  let okb =
456   GButton.button ~label:"Ok"
457    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
458  let cancelb =
459   GButton.button ~label:"Abort"
460    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
461  (* actions *)
462  ignore (window#connect#destroy GMain.Main.quit) ;
463  ignore (cancelb#connect#clicked window#destroy) ;
464  ignore
465   (okb#connect#clicked
466     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
467  window#set_position `CENTER ;
468  window#show () ;
469  GMain.Main.main () ;
470  match !chosen with
471     None -> raise NoChoice
472   | Some n -> n
473 ;;
474
475
476 (* MISC FUNCTIONS *)
477
478 (* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
479 let get_last_query = 
480  let query = ref "" in
481   MQueryGenerator.set_confirm_query
482    (function q -> query := MQueryUtil.text_of_query q ; true) ;
483   function result -> !query ^ " <h1>Result:</h1> " ^ MQueryUtil.text_of_result result "<br>"
484 ;;
485
486 let domImpl = Gdome.domImplementation ();;
487
488 let parseStyle name =
489  let style =
490   domImpl#createDocumentFromURI
491 (*
492    ~uri:("http://phd.cs.unibo.it:8081/getxslt?uri=" ^ name) ?mode:None
493 *)
494    ~uri:("styles/" ^ name) ()
495  in
496   Gdome_xslt.processStylesheet style
497 ;;
498
499 let d_c = parseStyle "drop_coercions.xsl";;
500 let tc1 = parseStyle "objtheorycontent.xsl";;
501 let hc2 = parseStyle "content_to_html.xsl";;
502 let l   = parseStyle "link.xsl";;
503
504 let c1 = parseStyle "rootcontent.xsl";;
505 let g  = parseStyle "genmmlid.xsl";;
506 let c2 = parseStyle "annotatedpres.xsl";;
507
508
509 let getterURL = Configuration.getter_url;;
510 let processorURL = Configuration.processor_url;;
511
512 let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
513 let mml_args ~explode_all =
514  ("explodeall",(if explode_all then "true()" else "false()"))::
515   ["processorURL", "'" ^ processorURL ^ "'" ;
516    "getterURL", "'" ^ getterURL ^ "'" ;
517    "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
518    "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
519    "UNICODEvsSYMBOL", "'symbol'" ;
520    "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
521    "encoding", "'iso-8859-1'" ;
522    "media-type", "'text/html'" ;
523    "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
524    "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
525    "naturalLanguage", "'yes'" ;
526    "annotations", "'no'" ;
527    "URLs_or_URIs", "'URIs'" ;
528    "topurl", "'http://phd.cs.unibo.it/helm'" ;
529    "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
530 ;;
531
532 let sequent_styles = [d_c ; c1 ; g ; c2 ; l];;
533 let sequent_args =
534  ["processorURL", "'" ^ processorURL ^ "'" ;
535   "getterURL", "'" ^ getterURL ^ "'" ;
536   "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
537   "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
538   "UNICODEvsSYMBOL", "'symbol'" ;
539   "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
540   "encoding", "'iso-8859-1'" ;
541   "media-type", "'text/html'" ;
542   "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
543   "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
544   "naturalLanguage", "'no'" ;
545   "annotations", "'no'" ;
546   "explodeall", "true()" ;
547   "URLs_or_URIs", "'URIs'" ;
548   "topurl", "'http://phd.cs.unibo.it/helm'" ;
549   "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
550 ;;
551
552 let parse_file filename =
553  let inch = open_in filename in
554   let rec read_lines () =
555    try
556     let line = input_line inch in
557      line ^ read_lines ()
558    with
559     End_of_file -> ""
560   in
561    read_lines ()
562 ;;
563
564 let applyStylesheets input styles args =
565  List.fold_left (fun i style -> Gdome_xslt.applyStylesheet i style args)
566   input styles
567 ;;
568
569 let
570  mml_of_cic_object ~explode_all uri annobj ids_to_inner_sorts ids_to_inner_types
571 =
572 (*CSC: ????????????????? *)
573  let xml, bodyxml =
574   Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:true
575    annobj 
576  in
577  let xmlinnertypes =
578   Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
579    ~ask_dtd_to_the_getter:true
580  in
581   let input =
582    match bodyxml with
583       None -> Xml2Gdome.document_of_xml domImpl xml
584     | Some bodyxml' ->
585        Xml.pp xml (Some constanttypefile) ;
586        Xml2Gdome.document_of_xml domImpl bodyxml'
587   in
588 (*CSC: We save the innertypes to disk so that we can retrieve them in the  *)
589 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
590 (*CSC: local.                                                              *)
591    Xml.pp xmlinnertypes (Some innertypesfile) ;
592    let output = applyStylesheets input mml_styles (mml_args ~explode_all) in
593     output
594 ;;
595
596 let
597  save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
598 =
599  let name =
600   let struri = UriManager.string_of_uri uri in
601   let idx = (String.rindex struri '/') + 1 in
602    String.sub struri idx (String.length struri - idx)
603  in
604   let path = pathname ^ "/" ^ name in
605   let xml, bodyxml =
606    Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
607     annobj 
608   in
609   let xmlinnertypes =
610    Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
611     ~ask_dtd_to_the_getter:false
612   in
613    (* innertypes *)
614    let innertypesuri = UriManager.innertypesuri_of_uri uri in
615     Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
616     Getter.register innertypesuri
617      (Configuration.annotations_url ^
618        Str.replace_first (Str.regexp "^cic:") ""
619         (UriManager.string_of_uri innertypesuri) ^ ".xml"
620      ) ;
621     (* constant type / variable / mutual inductive types definition *)
622     Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
623     Getter.register uri
624      (Configuration.annotations_url ^
625        Str.replace_first (Str.regexp "^cic:") ""
626         (UriManager.string_of_uri uri) ^ ".xml"
627      ) ;
628     match bodyxml with
629        None -> ()
630      | Some bodyxml' ->
631         (* constant body *)
632         let bodyuri =
633          match UriManager.bodyuri_of_uri uri with
634             None -> assert false
635           | Some bodyuri -> bodyuri
636         in
637          Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
638          Getter.register bodyuri
639           (Configuration.annotations_url ^
640             Str.replace_first (Str.regexp "^cic:") ""
641              (UriManager.string_of_uri bodyuri) ^ ".xml"
642           )
643 ;;
644
645
646 (* CALLBACKS *)
647
648 exception RefreshSequentException of exn;;
649 exception RefreshProofException of exn;;
650
651 let refresh_proof (output : GMathView.math_view) =
652  try
653   let uri,currentproof =
654    match !ProofEngine.proof with
655       None -> assert false
656     | Some (uri,metasenv,bo,ty) ->
657        !qed_set_sensitive (List.length metasenv = 0) ;
658        (*CSC: Wrong: [] is just plainly wrong *)
659        uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
660   in
661    let
662     (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
663      ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
664    =
665     Cic2acic.acic_object_of_cic_object currentproof
666    in
667     let mml =
668      mml_of_cic_object ~explode_all:true uri acic ids_to_inner_sorts
669       ids_to_inner_types
670     in
671      output#load_tree mml ;
672      current_cic_infos :=
673       Some (ids_to_terms,ids_to_father_ids,ids_to_conjectures,ids_to_hypotheses)
674  with
675   e ->
676  match !ProofEngine.proof with
677     None -> assert false
678   | Some (uri,metasenv,bo,ty) ->
679 prerr_endline ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[]))) ; flush stderr ;
680    raise (RefreshProofException e)
681 ;;
682
683 let refresh_sequent ?(empty_notebook=true) notebook =
684  try
685   match !ProofEngine.goal with
686      None ->
687       if empty_notebook then
688        begin 
689         notebook#remove_all_pages ~skip_switch_page_event:false ;
690         notebook#set_empty_page
691        end
692       else
693        notebook#proofw#unload
694    | Some metano ->
695       let metasenv =
696        match !ProofEngine.proof with
697           None -> assert false
698         | Some (_,metasenv,_,_) -> metasenv
699       in
700       let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
701        let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
702         SequentPp.XmlPp.print_sequent metasenv currentsequent
703        in
704         let regenerate_notebook () = 
705          let skip_switch_page_event =
706           match metasenv with
707              (m,_,_)::_ when m = metano -> false
708            | _ -> true
709          in
710           notebook#remove_all_pages ~skip_switch_page_event ;
711           List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
712         in
713           if empty_notebook then
714            begin
715             regenerate_notebook () ;
716             notebook#set_current_page ~may_skip_switch_page_event:false metano
717            end
718           else
719            begin
720             let sequent_doc = Xml2Gdome.document_of_xml domImpl sequent_gdome in
721             let sequent_mml =
722              applyStylesheets sequent_doc sequent_styles sequent_args
723             in
724              notebook#set_current_page ~may_skip_switch_page_event:true metano;
725              notebook#proofw#load_tree ~dom:sequent_mml
726            end ;
727           current_goal_infos :=
728            Some (ids_to_terms,ids_to_father_ids,ids_to_hypotheses)
729  with
730   e ->
731 let metano =
732   match !ProofEngine.goal with
733      None -> assert false
734    | Some m -> m
735 in
736 let metasenv =
737  match !ProofEngine.proof with
738     None -> assert false
739   | Some (_,metasenv,_,_) -> metasenv
740 in
741 try
742 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
743 prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
744    raise (RefreshSequentException e)
745 with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unkown."); raise (RefreshSequentException e)
746 ;;
747
748 (*
749 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
750  ~name:"/home/galata/miohelm/guruguru1" ~indent:true ()) ;
751 *)
752
753 let mml_of_cic_term metano term =
754  let metasenv =
755   match !ProofEngine.proof with
756      None -> []
757    | Some (_,metasenv,_,_) -> metasenv
758  in
759  let context =
760   match !ProofEngine.goal with
761      None -> []
762    | Some metano ->
763       let (_,canonical_context,_) =
764        List.find (function (m,_,_) -> m=metano) metasenv
765       in
766        canonical_context
767  in
768    let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
769     SequentPp.XmlPp.print_sequent metasenv (metano,context,term)
770    in
771     let sequent_doc =
772      Xml2Gdome.document_of_xml domImpl sequent_gdome
773     in
774      let res =
775       applyStylesheets sequent_doc sequent_styles sequent_args ;
776      in
777       current_scratch_infos :=
778        Some (term,ids_to_terms,ids_to_father_ids,ids_to_hypotheses) ;
779       res
780 ;;
781
782 exception OpenConjecturesStillThere;;
783 exception WrongProof;;
784
785 let pathname_of_annuri uristring =
786  Configuration.annotations_dir ^    
787   Str.replace_first (Str.regexp "^cic:") "" uristring
788 ;;
789
790 let make_dirs dirpath =
791  ignore (Unix.system ("mkdir -p " ^ dirpath))
792 ;;
793
794 let save_obj uri obj =
795  let
796   (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
797    ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
798  =
799   Cic2acic.acic_object_of_cic_object obj
800  in
801   (* let's save the theorem and register it to the getter *) 
802   let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
803    make_dirs pathname ;
804    save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
805     pathname
806 ;;
807
808 let qed () =
809  match !ProofEngine.proof with
810     None -> assert false
811   | Some (uri,[],bo,ty) ->
812      if
813       CicReduction.are_convertible []
814        (CicTypeChecker.type_of_aux' [] [] bo) ty
815      then
816       begin
817        (*CSC: Wrong: [] is just plainly wrong *)
818        let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
819         let
820          (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
821           ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
822         =
823          Cic2acic.acic_object_of_cic_object proof
824         in
825          let mml =
826           mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
827            ids_to_inner_types
828          in
829           ((rendering_window ())#output : GMathView.math_view)#load_tree mml ;
830           !qed_set_sensitive false ;
831           (* let's save the theorem and register it to the getter *) 
832           let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
833           make_dirs pathname ;
834           save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
835            pathname ;
836           current_cic_infos :=
837            Some
838             (ids_to_terms,ids_to_father_ids,ids_to_conjectures,
839              ids_to_hypotheses)
840       end
841      else
842       raise WrongProof
843   | _ -> raise OpenConjecturesStillThere
844 ;;
845
846 let save () =
847  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
848   match !ProofEngine.proof with
849      None -> assert false
850    | Some (uri, metasenv, bo, ty) ->
851       let currentproof =
852        (*CSC: Wrong: [] is just plainly wrong *)
853        Cic.CurrentProof (UriManager.name_of_uri uri,metasenv,bo,ty,[])
854       in
855        let (acurrentproof,_,_,ids_to_inner_sorts,_,_,_) =
856         Cic2acic.acic_object_of_cic_object currentproof
857        in
858         let xml, bodyxml =
859          match
860           Cic2Xml.print_object uri ~ids_to_inner_sorts
861            ~ask_dtd_to_the_getter:true acurrentproof
862          with
863             xml,Some bodyxml -> xml,bodyxml
864           | _,None -> assert false
865         in
866          Xml.pp ~quiet:true xml (Some prooffiletype) ;
867          output_html outputhtml
868           ("<h1 color=\"Green\">Current proof type saved to " ^
869            prooffiletype ^ "</h1>") ;
870          Xml.pp ~quiet:true bodyxml (Some prooffile) ;
871          output_html outputhtml
872           ("<h1 color=\"Green\">Current proof body saved to " ^
873            prooffile ^ "</h1>")
874 ;;
875
876 (* Used to typecheck the loaded proofs *)
877 let typecheck_loaded_proof metasenv bo ty =
878  let module T = CicTypeChecker in
879   ignore (
880    List.fold_left
881     (fun metasenv ((_,context,ty) as conj) ->
882       ignore (T.type_of_aux' metasenv context ty) ;
883       metasenv @ [conj]
884     ) [] metasenv) ;
885   ignore (T.type_of_aux' metasenv [] ty) ;
886   ignore (T.type_of_aux' metasenv [] bo)
887 ;;
888
889 let load () =
890  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
891  let output = ((rendering_window ())#output : GMathView.math_view) in
892  let notebook = (rendering_window ())#notebook in
893   try
894    match 
895     GToolbox.input_string ~title:"Load Unfinished Proof" ~text:"/dummy.con"
896      "Choose an URI:"
897    with
898       None -> raise NoChoice
899     | Some uri0 ->
900        let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
901         match CicParser.obj_of_xml prooffiletype (Some prooffile) with
902            Cic.CurrentProof (_,metasenv,bo,ty,_) ->
903             typecheck_loaded_proof metasenv bo ty ;
904             ProofEngine.proof :=
905              Some (uri, metasenv, bo, ty) ;
906             ProofEngine.goal :=
907              (match metasenv with
908                  [] -> None
909                | (metano,_,_)::_ -> Some metano
910              ) ;
911             refresh_proof output ;
912             refresh_sequent notebook ;
913              output_html outputhtml
914               ("<h1 color=\"Green\">Current proof type loaded from " ^
915                 prooffiletype ^ "</h1>") ;
916              output_html outputhtml
917               ("<h1 color=\"Green\">Current proof body loaded from " ^
918                 prooffile ^ "</h1>") ;
919             !save_set_sensitive true
920          | _ -> assert false
921   with
922      RefreshSequentException e ->
923       output_html outputhtml
924        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
925         "sequent: " ^ Printexc.to_string e ^ "</h1>")
926    | RefreshProofException e ->
927       output_html outputhtml
928        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
929         "proof: " ^ Printexc.to_string e ^ "</h1>")
930    | e ->
931       output_html outputhtml
932        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
933 ;;
934
935 let edit_aliases () =
936  let chosen = ref false in
937  let window =
938   GWindow.window
939    ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
940  let vbox =
941   GPack.vbox ~border_width:0 ~packing:window#add () in
942  let scrolled_window =
943   GBin.scrolled_window ~border_width:10
944    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
945  let input = GEdit.text ~editable:true ~width:400 ~height:100
946    ~packing:scrolled_window#add () in
947  let hbox =
948   GPack.hbox ~border_width:0
949    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
950  let okb =
951   GButton.button ~label:"Ok"
952    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
953  let cancelb =
954   GButton.button ~label:"Cancel"
955    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
956  ignore (window#connect#destroy GMain.Main.quit) ;
957  ignore (cancelb#connect#clicked window#destroy) ;
958  ignore
959   (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
960  let dom,resolve_id = !id_to_uris in
961   ignore
962    (input#insert_text ~pos:0
963     (String.concat "\n"
964       (List.map
965         (function v ->
966           let uri =
967            match resolve_id v with
968               None -> assert false
969             | Some uri -> uri
970           in
971            "alias " ^ v ^ " " ^
972              (string_of_cic_textual_parser_uri uri)
973         ) dom))) ;
974   window#show () ;
975   GMain.Main.main () ;
976   if !chosen then
977    let dom,resolve_id =
978     let inputtext = input#get_chars 0 input#length in
979     let regexpr =
980      let alfa = "[a-zA-Z_-]" in
981      let digit = "[0-9]" in
982      let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
983      let blanks = "\( \|\t\|\n\)+" in
984      let nonblanks = "[^ \t\n]+" in
985      let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
986       Str.regexp
987        ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
988     in
989      let rec aux n =
990       try
991        let n' = Str.search_forward regexpr inputtext n in
992         let id = Str.matched_group 2 inputtext in
993         let uri =
994          cic_textual_parser_uri_of_string
995           ("cic:" ^ (Str.matched_group 5 inputtext))
996         in
997          let dom,resolve_id = aux (n' + 1) in
998           if List.mem id dom then
999            dom,resolve_id
1000           else
1001            id::dom,
1002             (function id' -> if id = id' then Some uri else resolve_id id')
1003       with
1004        Not_found -> empty_id_to_uris
1005      in
1006       aux 0
1007    in
1008     id_to_uris := dom,resolve_id
1009 ;;
1010
1011 let proveit () =
1012  let module L = LogicalOperations in
1013  let module G = Gdome in
1014  let notebook = (rendering_window ())#notebook in
1015  let output = (rendering_window ())#output in
1016  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1017   match (rendering_window ())#output#get_selection with
1018     Some node ->
1019      let xpath =
1020       ((node : Gdome.element)#getAttributeNS
1021       (*CSC: OCAML DIVERGE
1022       ((element : G.element)#getAttributeNS
1023       *)
1024         ~namespaceURI:helmns
1025         ~localName:(G.domString "xref"))#to_string
1026      in
1027       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1028       else
1029        begin
1030         try
1031          match !current_cic_infos with
1032             Some (ids_to_terms, ids_to_father_ids, _, _) ->
1033              let id = xpath in
1034               L.to_sequent id ids_to_terms ids_to_father_ids ;
1035               refresh_proof output ;
1036               refresh_sequent notebook
1037           | None -> assert false (* "ERROR: No current term!!!" *)
1038         with
1039            RefreshSequentException e ->
1040             output_html outputhtml
1041              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1042               "sequent: " ^ Printexc.to_string e ^ "</h1>")
1043          | RefreshProofException e ->
1044             output_html outputhtml
1045              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1046               "proof: " ^ Printexc.to_string e ^ "</h1>")
1047          | e ->
1048             output_html outputhtml
1049              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1050        end
1051   | None -> assert false (* "ERROR: No selection!!!" *)
1052 ;;
1053
1054 let focus () =
1055  let module L = LogicalOperations in
1056  let module G = Gdome in
1057  let notebook = (rendering_window ())#notebook in
1058  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1059   match (rendering_window ())#output#get_selection with
1060     Some node ->
1061      let xpath =
1062       ((node : Gdome.element)#getAttributeNS
1063       (*CSC: OCAML DIVERGE
1064       ((element : G.element)#getAttributeNS
1065       *)
1066         ~namespaceURI:helmns
1067         ~localName:(G.domString "xref"))#to_string
1068      in
1069       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
1070       else
1071        begin
1072         try
1073          match !current_cic_infos with
1074             Some (ids_to_terms, ids_to_father_ids, _, _) ->
1075              let id = xpath in
1076               L.focus id ids_to_terms ids_to_father_ids ;
1077               refresh_sequent notebook
1078           | None -> assert false (* "ERROR: No current term!!!" *)
1079         with
1080            RefreshSequentException e ->
1081             output_html outputhtml
1082              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1083               "sequent: " ^ Printexc.to_string e ^ "</h1>")
1084          | RefreshProofException e ->
1085             output_html outputhtml
1086              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1087               "proof: " ^ Printexc.to_string e ^ "</h1>")
1088          | e ->
1089             output_html outputhtml
1090              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1091        end
1092   | None -> assert false (* "ERROR: No selection!!!" *)
1093 ;;
1094
1095 exception NoPrevGoal;;
1096 exception NoNextGoal;;
1097
1098 let setgoal metano =
1099  let module L = LogicalOperations in
1100  let module G = Gdome in
1101  let notebook = (rendering_window ())#notebook in
1102  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1103   let metasenv =
1104    match !ProofEngine.proof with
1105       None -> assert false
1106     | Some (_,metasenv,_,_) -> metasenv
1107   in
1108    try
1109     refresh_sequent ~empty_notebook:false notebook
1110    with
1111       RefreshSequentException e ->
1112        output_html outputhtml
1113         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1114          "sequent: " ^ Printexc.to_string e ^ "</h1>")
1115     | e ->
1116        output_html outputhtml
1117         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1118 ;;
1119
1120 let
1121  show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
1122 =
1123  let window =
1124   GWindow.window ~width:800 ~border_width:2 () in
1125  let scrolled_window =
1126   GBin.scrolled_window ~border_width:10 ~packing:window#add () in
1127  let mmlwidget =
1128   GMathView.math_view ~packing:scrolled_window#add ~width:600 ~height:400 () in
1129  let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
1130  let href = Gdome.domString "href" in
1131   let show_in_show_window_obj uri obj =
1132    let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1133     try
1134      let
1135       (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
1136        ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
1137      =
1138       Cic2acic.acic_object_of_cic_object obj
1139      in
1140       let mml =
1141        mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
1142         ids_to_inner_types
1143       in
1144        window#set_title (UriManager.string_of_uri uri) ;
1145        window#misc#hide () ; window#show () ;
1146        mmlwidget#load_tree mml ;
1147     with
1148      e ->
1149       output_html outputhtml
1150        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1151   in
1152   let show_in_show_window_uri uri =
1153    let obj = CicEnvironment.get_obj uri in
1154     show_in_show_window_obj uri obj
1155   in
1156    let show_in_show_window_callback mmlwidget (n : Gdome.element) =
1157     if n#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
1158      let uri =
1159       (n#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
1160      in 
1161       show_in_show_window_uri (UriManager.uri_of_string uri)
1162     else
1163      if mmlwidget#get_action <> None then
1164       mmlwidget#action_toggle
1165    in
1166     let _ =
1167      mmlwidget#connect#clicked (show_in_show_window_callback mmlwidget)
1168     in
1169      show_in_show_window_obj, show_in_show_window_uri,
1170       show_in_show_window_callback
1171 ;;
1172
1173 exception NoObjectsLocated;;
1174
1175 let user_uri_choice ~title ~msg uris =
1176  let uri =
1177   match uris with
1178      [] -> raise NoObjectsLocated
1179    | [uri] -> uri
1180    | uris ->
1181       match
1182        interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
1183       with
1184          [uri] -> uri
1185        | _ -> assert false
1186  in
1187   String.sub uri 4 (String.length uri - 4)
1188 ;;
1189
1190 let locate_callback id =
1191  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1192  let result = MQueryGenerator.locate id in
1193  let uris =
1194   List.map
1195    (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
1196    result in
1197  let html =
1198   (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>")
1199  in
1200   output_html outputhtml html ;
1201   user_uri_choice ~title:"Ambiguous input."
1202    ~msg:
1203      ("Ambiguous input \"" ^ id ^
1204       "\". Please, choose one interpetation:")
1205    uris
1206 ;;
1207
1208 let locate () =
1209  let inputt = ((rendering_window ())#inputt : term_editor) in
1210  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1211    try
1212     match
1213      GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
1214     with
1215        None -> raise NoChoice
1216      | Some input ->
1217         let uri = locate_callback input in
1218          inputt#set_term uri
1219    with
1220     e ->
1221      output_html outputhtml
1222       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
1223 ;;
1224
1225 let input_or_locate_uri ~title =
1226  let uri = ref None in
1227  let window =
1228   GWindow.window
1229    ~width:400 ~modal:true ~title ~border_width:2 () in
1230  let vbox = GPack.vbox ~packing:window#add () in
1231  let hbox1 =
1232   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1233  let _ =
1234   GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
1235  let manual_input =
1236   GEdit.entry ~editable:true
1237    ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
1238  let checkb =
1239   GButton.button ~label:"Check"
1240    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1241  let _ = checkb#misc#set_sensitive false in
1242  let hbox2 =
1243   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1244  let _ =
1245   GMisc.label ~text:"You can also enter an indentifier to locate:"
1246    ~packing:(hbox2#pack ~padding:5) () in
1247  let locate_input =
1248   GEdit.entry ~editable:true
1249    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1250  let locateb =
1251   GButton.button ~label:"Locate"
1252    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1253  let _ = locateb#misc#set_sensitive false in
1254  let hbox3 =
1255   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1256  let okb =
1257   GButton.button ~label:"Ok"
1258    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
1259  let _ = okb#misc#set_sensitive false in
1260  let cancelb =
1261   GButton.button ~label:"Cancel"
1262    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
1263  in
1264   ignore (window#connect#destroy GMain.Main.quit) ;
1265   ignore
1266    (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
1267   let check_callback () =
1268    let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1269    let uri = "cic:" ^ manual_input#text in
1270     try
1271       ignore (Getter.resolve (UriManager.uri_of_string uri)) ;
1272       output_html outputhtml "<h1 color=\"Green\">OK</h1>" ;
1273       true
1274     with
1275        Getter.Unresolved ->
1276         output_html outputhtml
1277          ("<h1 color=\"Red\">URI " ^ uri ^
1278           " does not correspond to any object.</h1>") ;
1279         false
1280      | UriManager.IllFormedUri _ ->
1281         output_html outputhtml
1282          ("<h1 color=\"Red\">URI " ^ uri ^ " is not well-formed.</h1>") ;
1283         false
1284      | e ->
1285         output_html outputhtml
1286          ("<h1 color=\"Red\">" ^ Printexc.to_string e ^ "</h1>") ;
1287         false
1288   in
1289   ignore
1290    (okb#connect#clicked
1291      (function () ->
1292        if check_callback () then
1293         begin
1294          uri := Some manual_input#text ;
1295          window#destroy ()
1296         end
1297    )) ;
1298   ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
1299   ignore
1300    (manual_input#connect#changed
1301      (fun _ ->
1302        if manual_input#text = "" then
1303         begin
1304          checkb#misc#set_sensitive false ;
1305          okb#misc#set_sensitive false
1306         end
1307        else
1308         begin
1309          checkb#misc#set_sensitive true ;
1310          okb#misc#set_sensitive true
1311         end));
1312   ignore
1313    (locate_input#connect#changed
1314      (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
1315   ignore
1316    (locateb#connect#clicked
1317      (function () ->
1318        let id = locate_input#text in
1319         manual_input#set_text (locate_callback id) ;
1320         locate_input#delete_text 0 (String.length id)
1321    )) ;
1322   window#show () ;
1323   GMain.Main.main () ;
1324   match !uri with
1325      None -> raise NoChoice
1326    | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
1327 ;;
1328
1329 let locate_one_id id =
1330  let result = MQueryGenerator.locate id in
1331  let uris =
1332   List.map
1333    (function uri,_ ->
1334      wrong_xpointer_format_from_wrong_xpointer_format' uri
1335    ) result in
1336  let html= " <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>" in
1337   output_html (rendering_window ())#outputhtml html ;
1338   let uris' =
1339    match uris with
1340       [] ->
1341        [UriManager.string_of_uri
1342          (input_or_locate_uri ~title:("URI matching \"" ^ id ^ "\" unknown."))]
1343     | [uri] -> [uri]
1344     | _ ->
1345       interactive_user_uri_choice
1346        ~selection_mode:`EXTENDED
1347        ~ok:"Try every selection."
1348        ~enable_button_for_non_vars:true
1349        ~title:"Ambiguous input."
1350        ~msg:
1351          ("Ambiguous input \"" ^ id ^
1352           "\". Please, choose one or more interpretations:")
1353        uris
1354   in
1355    List.map cic_textual_parser_uri_of_string uris'
1356 ;;
1357
1358 exception ThereDoesNotExistAnyWellTypedInterpretationOfTheInput;;
1359 exception AmbiguousInput;;
1360
1361 let disambiguate_input context metasenv dom mk_metasenv_and_expr =
1362  let known_ids,resolve_id = !id_to_uris in
1363  let dom' =
1364   let rec filter =
1365    function
1366       [] -> []
1367     | he::tl ->
1368        if List.mem he known_ids then filter tl else he::(filter tl)
1369   in
1370    filter dom
1371  in
1372   (* for each id in dom' we get the list of uris associated to it *)
1373   let list_of_uris = List.map locate_one_id dom' in
1374   (* and now we compute the list of all possible assignments from id to uris *)
1375   let resolve_ids =
1376    let rec aux ids list_of_uris =
1377     match ids,list_of_uris with
1378        [],[] -> [resolve_id]
1379      | id::idtl,uris::uristl ->
1380         let resolves = aux idtl uristl in
1381          List.concat
1382           (List.map
1383             (function uri ->
1384               List.map
1385                (function f ->
1386                  function id' -> if id = id' then Some uri else f id'
1387                ) resolves
1388             ) uris
1389           )
1390      | _,_ -> assert false
1391    in
1392     aux dom' list_of_uris
1393   in
1394    let tests_no = List.length resolve_ids in
1395     if tests_no > 1 then
1396      output_html (outputhtml ())
1397       ("<h1>Disambiguation phase started: " ^
1398         string_of_int (List.length resolve_ids) ^ " cases will be tried.") ;
1399    (* now we select only the ones that generates well-typed terms *)
1400    let resolve_ids' =
1401     let rec filter =
1402      function
1403         [] -> []
1404       | resolve::tl ->
1405          let metasenv',expr = mk_metasenv_and_expr resolve in
1406           try
1407 (*CSC: Bug here: we do not try to typecheck also the metasenv' *)
1408            ignore
1409             (CicTypeChecker.type_of_aux' metasenv context expr) ;
1410            resolve::(filter tl)
1411           with
1412            _ -> filter tl
1413     in
1414      filter resolve_ids
1415    in
1416     let resolve_id' =
1417      match resolve_ids' with
1418         [] -> raise ThereDoesNotExistAnyWellTypedInterpretationOfTheInput
1419       | [resolve_id] -> resolve_id
1420       | _ ->
1421         let choices =
1422          List.map
1423           (function resolve ->
1424             List.map
1425              (function id ->
1426                id,
1427                 match resolve id with
1428                    None -> assert false
1429                  | Some uri ->
1430                     match uri with
1431                        CicTextualParser0.ConUri uri
1432                      | CicTextualParser0.VarUri uri ->
1433                         UriManager.string_of_uri uri
1434                      | CicTextualParser0.IndTyUri (uri,tyno) ->
1435                         UriManager.string_of_uri uri ^ "#xpointer(1/" ^
1436                          string_of_int (tyno+1) ^ ")"
1437                      | CicTextualParser0.IndConUri (uri,tyno,consno) ->
1438                         UriManager.string_of_uri uri ^ "#xpointer(1/" ^
1439                          string_of_int (tyno+1) ^ "/" ^ string_of_int consno ^                           ")"
1440              ) dom
1441           ) resolve_ids'
1442         in
1443          let index = interactive_interpretation_choice choices in
1444           List.nth resolve_ids' index
1445     in
1446      id_to_uris := known_ids @ dom', resolve_id' ;
1447      mk_metasenv_and_expr resolve_id'
1448 ;;
1449
1450 exception UriAlreadyInUse;;
1451 exception NotAUriToAConstant;;
1452
1453 let new_inductive () =
1454  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1455  let output = ((rendering_window ())#output : GMathView.math_view) in
1456  let notebook = (rendering_window ())#notebook in
1457
1458  let chosen = ref false in
1459  let inductive = ref true in
1460  let paramsno = ref 0 in
1461  let get_uri = ref (function _ -> assert false) in
1462  let get_base_uri = ref (function _ -> assert false) in
1463  let get_names = ref (function _ -> assert false) in
1464  let get_types_and_cons = ref (function _ -> assert false) in
1465  let get_name_context_context_and_subst = ref (function _ -> assert false) in 
1466  let window =
1467   GWindow.window
1468    ~width:600 ~modal:true ~position:`CENTER
1469    ~title:"New Block of Mutual (Co)Inductive Definitions"
1470    ~border_width:2 () in
1471  let vbox = GPack.vbox ~packing:window#add () in
1472  let hbox =
1473   GPack.hbox ~border_width:0
1474    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1475  let _ =
1476   GMisc.label ~text:"Enter the URI for the new block:"
1477    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1478  let uri_entry =
1479   GEdit.entry ~editable:true
1480    ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1481  let hbox0 =
1482   GPack.hbox ~border_width:0
1483    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1484  let _ =
1485   GMisc.label
1486    ~text:
1487      "Enter the number of left parameters in every arity and constructor type:"
1488    ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
1489  let paramsno_entry =
1490   GEdit.entry ~editable:true ~text:"0"
1491    ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
1492  let hbox1 =
1493   GPack.hbox ~border_width:0
1494    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1495  let _ =
1496   GMisc.label ~text:"Are the definitions inductive or coinductive?"
1497    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1498  let inductiveb =
1499   GButton.radio_button ~label:"Inductive"
1500    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1501  let coinductiveb =
1502   GButton.radio_button ~label:"Coinductive"
1503    ~group:inductiveb#group
1504    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1505  let hbox2 =
1506   GPack.hbox ~border_width:0
1507    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1508  let _ =
1509   GMisc.label ~text:"Enter the list of the names of the types:"
1510    ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
1511  let names_entry =
1512   GEdit.entry ~editable:true
1513    ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
1514  let hboxn =
1515   GPack.hbox ~border_width:0
1516    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1517  let okb =
1518   GButton.button ~label:"> Next"
1519    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1520  let _ = okb#misc#set_sensitive true in
1521  let cancelb =
1522   GButton.button ~label:"Abort"
1523    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1524  ignore (window#connect#destroy GMain.Main.quit) ;
1525  ignore (cancelb#connect#clicked window#destroy) ;
1526  (* First phase *)
1527  let rec phase1 () =
1528   ignore
1529    (okb#connect#clicked
1530      (function () ->
1531        try
1532         let uristr = "cic:" ^ uri_entry#text in
1533         let namesstr = names_entry#text in
1534         let paramsno' = int_of_string (paramsno_entry#text) in
1535          match Str.split (Str.regexp " +") namesstr with
1536             [] -> assert false
1537           | (he::tl) as names ->
1538              let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
1539               begin
1540                try
1541                 ignore (Getter.resolve uri) ;
1542                 raise UriAlreadyInUse
1543                with
1544                 Getter.Unresolved ->
1545                  get_uri := (function () -> uri) ; 
1546                  get_names := (function () -> names) ;
1547                  inductive := inductiveb#active ;
1548                  paramsno := paramsno' ;
1549                  phase2 ()
1550               end
1551        with
1552         e ->
1553          output_html outputhtml
1554           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1555      ))
1556  (* Second phase *)
1557  and phase2 () =
1558   let type_widgets =
1559    List.map
1560     (function name ->
1561       let frame =
1562        GBin.frame ~label:name
1563         ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
1564       let vbox = GPack.vbox ~packing:frame#add () in
1565       let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
1566       let _ =
1567        GMisc.label ~text:("Enter its type:")
1568         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1569       let scrolled_window =
1570        GBin.scrolled_window ~border_width:5
1571         ~packing:(vbox#pack ~expand:true ~padding:0) () in
1572       let newinputt =
1573        new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
1574         ~isnotempty_callback:
1575          (function b ->
1576            (*non_empty_type := b ;*)
1577            okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
1578       in
1579       let hbox =
1580        GPack.hbox ~border_width:0
1581         ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1582       let _ =
1583        GMisc.label ~text:("Enter the list of its constructors:")
1584         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1585       let cons_names_entry =
1586        GEdit.entry ~editable:true
1587         ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1588       (newinputt,cons_names_entry)
1589     ) (!get_names ())
1590   in
1591    vbox#remove hboxn#coerce ;
1592    let hboxn =
1593     GPack.hbox ~border_width:0
1594      ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1595    let okb =
1596     GButton.button ~label:"> Next"
1597      ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1598    let cancelb =
1599     GButton.button ~label:"Abort"
1600      ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1601    ignore (cancelb#connect#clicked window#destroy) ;
1602    ignore
1603     (okb#connect#clicked
1604       (function () ->
1605         try
1606          let names = !get_names () in
1607          let types_and_cons =
1608           List.map2
1609            (fun name (newinputt,cons_names_entry) ->
1610              let dom,mk_metasenv_and_expr =
1611               newinputt#get_term ~context:[] ~metasenv:[] in
1612              let consnamesstr = cons_names_entry#text in
1613              let cons_names = Str.split (Str.regexp " +") consnamesstr in
1614              let metasenv,expr =
1615               disambiguate_input [] [] dom mk_metasenv_and_expr
1616              in
1617               match metasenv with
1618                  [] -> expr,cons_names
1619                | _ -> raise AmbiguousInput
1620            ) names type_widgets
1621          in
1622           let uri = !get_uri () in
1623           let _ =
1624            (* Let's see if so far the definition is well-typed *)
1625            let params = [] in
1626            let paramsno = 0 in
1627            (* To test if the arities of the inductive types are well *)
1628            (* typed, we check the inductive block definition where   *)
1629            (* no constructor is given to each type.                  *)
1630            let tys =
1631             List.map2
1632              (fun name (ty,cons) -> (name, !inductive, ty, []))
1633              names types_and_cons
1634            in
1635             CicTypeChecker.typecheck_mutual_inductive_defs uri
1636              (tys,params,paramsno)
1637           in
1638            get_name_context_context_and_subst :=
1639             (function () ->
1640               let i = ref 0 in
1641                List.fold_left2
1642                 (fun (namecontext,context,subst) name (ty,_) ->
1643                   let res =
1644                    (Some (Cic.Name name))::namecontext,
1645                     (Some (Cic.Name name, Cic.Decl ty))::context,
1646                     (Cic.MutInd (uri,!i,[]))::subst
1647                   in
1648                    incr i ; res
1649                 ) ([],[],[]) names types_and_cons) ;
1650            let types_and_cons' =
1651             List.map2
1652              (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
1653              names types_and_cons
1654            in
1655             get_types_and_cons := (function () -> types_and_cons') ;
1656             chosen := true ;
1657             window#destroy ()
1658         with
1659          e ->
1660           output_html outputhtml
1661            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1662       ))
1663  (* Third phase *)
1664  and phase3 name cons =
1665   let get_cons_types = ref (function () -> assert false) in
1666   let window2 =
1667    GWindow.window
1668     ~width:600 ~modal:true ~position:`CENTER
1669     ~title:(name ^ " Constructors")
1670     ~border_width:2 () in
1671   let vbox = GPack.vbox ~packing:window2#add () in
1672   let cons_type_widgets =
1673    List.map
1674     (function consname ->
1675       let hbox =
1676        GPack.hbox ~border_width:0
1677         ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1678       let _ =
1679        GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
1680         ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1681       let scrolled_window =
1682        GBin.scrolled_window ~border_width:5
1683         ~packing:(vbox#pack ~expand:true ~padding:0) () in
1684       let newinputt =
1685        new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
1686         ~isnotempty_callback:
1687          (function b ->
1688            (* (*non_empty_type := b ;*)
1689            okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
1690       in
1691        newinputt
1692     ) cons in
1693   let hboxn =
1694    GPack.hbox ~border_width:0
1695     ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1696   let okb =
1697    GButton.button ~label:"> Next"
1698     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1699   let _ = okb#misc#set_sensitive true in
1700   let cancelb =
1701    GButton.button ~label:"Abort"
1702     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
1703   ignore (window2#connect#destroy GMain.Main.quit) ;
1704   ignore (cancelb#connect#clicked window2#destroy) ;
1705   ignore
1706    (okb#connect#clicked
1707      (function () ->
1708        try
1709         chosen := true ;
1710         let namecontext,context,subst= !get_name_context_context_and_subst () in
1711         let cons_types =
1712          List.map2
1713           (fun name inputt ->
1714             let dom,mk_metasenv_and_expr =
1715              inputt#get_term ~context:namecontext ~metasenv:[]
1716             in
1717              let metasenv,expr =
1718               disambiguate_input context [] dom mk_metasenv_and_expr
1719              in
1720               match metasenv with
1721                  [] ->
1722                   let undebrujined_expr =
1723                    List.fold_left
1724                     (fun expr t -> CicSubstitution.subst t expr) expr subst
1725                   in
1726                    name, undebrujined_expr
1727                | _ -> raise AmbiguousInput
1728           ) cons cons_type_widgets
1729         in
1730          get_cons_types := (function () -> cons_types) ;
1731          window2#destroy ()
1732        with
1733         e ->
1734          output_html outputhtml
1735           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1736      )) ;
1737   window2#show () ;
1738   GMain.Main.main () ;
1739   let okb_pressed = !chosen in
1740    chosen := false ;
1741    if (not okb_pressed) then
1742     begin
1743      window#destroy () ;
1744      assert false (* The control never reaches this point *)
1745     end
1746    else
1747     (!get_cons_types ())
1748  in
1749   phase1 () ;
1750   (* No more phases left or Abort pressed *) 
1751   window#show () ;
1752   GMain.Main.main () ;
1753   window#destroy () ;
1754   if !chosen then
1755    try
1756     let uri = !get_uri () in
1757 (*CSC: Da finire *)
1758     let params = [] in
1759     let tys = !get_types_and_cons () in
1760      let obj = Cic.InductiveDefinition tys params !paramsno in
1761       begin
1762        try
1763         prerr_endline (CicPp.ppobj obj) ;
1764         CicTypeChecker.typecheck_mutual_inductive_defs uri
1765          (tys,params,!paramsno) ;
1766         with
1767          e ->
1768           prerr_endline "Offending mutual (co)inductive type declaration:" ;
1769           prerr_endline (CicPp.ppobj obj) ;
1770       end ;
1771       (* We already know that obj is well-typed. We need to add it to the  *)
1772       (* environment in order to compute the inner-types without having to *)
1773       (* debrujin it or having to modify lots of other functions to avoid  *)
1774       (* asking the environment for the MUTINDs we are defining now.       *)
1775       CicEnvironment.put_inductive_definition uri obj ;
1776       save_obj uri obj ;
1777       show_in_show_window_obj uri obj
1778    with
1779     e ->
1780      output_html outputhtml
1781       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1782 ;;
1783
1784 let new_proof () =
1785  let inputt = ((rendering_window ())#inputt : term_editor) in
1786  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1787  let output = ((rendering_window ())#output : GMathView.math_view) in
1788  let notebook = (rendering_window ())#notebook in
1789
1790  let chosen = ref false in
1791  let get_parsed = ref (function _ -> assert false) in
1792  let get_uri = ref (function _ -> assert false) in
1793  let non_empty_type = ref false in
1794  let window =
1795   GWindow.window
1796    ~width:600 ~modal:true ~title:"New Proof or Definition"
1797    ~border_width:2 () in
1798  let vbox = GPack.vbox ~packing:window#add () in
1799  let hbox =
1800   GPack.hbox ~border_width:0
1801    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1802  let _ =
1803   GMisc.label ~text:"Enter the URI for the new theorem or definition:"
1804    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1805  let uri_entry =
1806   GEdit.entry ~editable:true
1807    ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
1808  let hbox1 =
1809   GPack.hbox ~border_width:0
1810    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1811  let _ =
1812   GMisc.label ~text:"Enter the theorem or definition type:"
1813    ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
1814  let scrolled_window =
1815   GBin.scrolled_window ~border_width:5
1816    ~packing:(vbox#pack ~expand:true ~padding:0) () in
1817  (* the content of the scrolled_window is moved below (see comment) *)
1818  let hbox =
1819   GPack.hbox ~border_width:0
1820    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
1821  let okb =
1822   GButton.button ~label:"Ok"
1823    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1824  let _ = okb#misc#set_sensitive false in
1825  let cancelb =
1826   GButton.button ~label:"Cancel"
1827    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
1828  (* moved here to have visibility of the ok button *)
1829  let newinputt =
1830   new term_editor ~width:400 ~height:100 ~packing:scrolled_window#add ()
1831    ~isnotempty_callback:
1832     (function b ->
1833       non_empty_type := b ;
1834       okb#misc#set_sensitive (b && uri_entry#text <> ""))
1835  in
1836  let _ =
1837   newinputt#set_term inputt#get_as_string ;
1838   inputt#reset in
1839  let _ =
1840   uri_entry#connect#changed
1841    (function () ->
1842      okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
1843  in
1844  ignore (window#connect#destroy GMain.Main.quit) ;
1845  ignore (cancelb#connect#clicked window#destroy) ;
1846  ignore
1847   (okb#connect#clicked
1848     (function () ->
1849       chosen := true ;
1850       try
1851        let parsed = newinputt#get_term [] [] in
1852        let uristr = "cic:" ^ uri_entry#text in
1853        let uri = UriManager.uri_of_string uristr in
1854         if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
1855          raise NotAUriToAConstant
1856         else
1857          begin
1858           try
1859            ignore (Getter.resolve uri) ;
1860            raise UriAlreadyInUse
1861           with
1862            Getter.Unresolved ->
1863             get_parsed := (function () -> parsed) ;
1864             get_uri := (function () -> uri) ; 
1865             window#destroy ()
1866          end
1867       with
1868        e ->
1869         output_html outputhtml
1870          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1871   )) ;
1872  window#show () ;
1873  GMain.Main.main () ;
1874  if !chosen then
1875   try
1876    let dom,mk_metasenv_and_expr = !get_parsed () in
1877     let metasenv,expr =
1878      disambiguate_input [] [] dom mk_metasenv_and_expr
1879     in
1880      let _  = CicTypeChecker.type_of_aux' metasenv [] expr in
1881       ProofEngine.proof :=
1882        Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
1883       ProofEngine.goal := Some 1 ;
1884       refresh_sequent notebook ;
1885       refresh_proof output ;
1886       !save_set_sensitive true ;
1887       inputt#reset
1888   with
1889      RefreshSequentException e ->
1890       output_html outputhtml
1891        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1892         "sequent: " ^ Printexc.to_string e ^ "</h1>")
1893    | RefreshProofException e ->
1894       output_html outputhtml
1895        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1896         "proof: " ^ Printexc.to_string e ^ "</h1>")
1897    | e ->
1898       output_html outputhtml
1899        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1900 ;;
1901
1902 let check_term_in_scratch scratch_window metasenv context expr = 
1903  try
1904   let ty  = CicTypeChecker.type_of_aux' metasenv context expr in
1905    let mml = mml_of_cic_term 111 (Cic.Cast (expr,ty)) in
1906 prerr_endline ("### " ^ CicPp.ppterm expr ^ " ==> " ^ CicPp.ppterm ty) ;
1907     scratch_window#show () ;
1908     scratch_window#mmlwidget#load_tree ~dom:mml
1909  with
1910   e ->
1911    print_endline ("? " ^ CicPp.ppterm expr) ;
1912    raise e
1913 ;;
1914
1915 let check scratch_window () =
1916  let inputt = ((rendering_window ())#inputt : term_editor) in
1917  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1918   let metasenv =
1919    match !ProofEngine.proof with
1920       None -> []
1921     | Some (_,metasenv,_,_) -> metasenv
1922   in
1923   let context,names_context =
1924    let context =
1925     match !ProofEngine.goal with
1926        None -> []
1927      | Some metano ->
1928         let (_,canonical_context,_) =
1929          List.find (function (m,_,_) -> m=metano) metasenv
1930         in
1931          canonical_context
1932    in
1933     context,
1934     List.map
1935      (function
1936          Some (n,_) -> Some n
1937        | None -> None
1938      ) context
1939   in
1940    try
1941     let dom,mk_metasenv_and_expr = inputt#get_term names_context metasenv in
1942      let (metasenv',expr) =
1943       disambiguate_input context metasenv dom mk_metasenv_and_expr
1944      in
1945       check_term_in_scratch scratch_window metasenv' context expr
1946    with
1947     e ->
1948      output_html outputhtml
1949       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1950 ;;
1951
1952
1953 (***********************)
1954 (*       TACTICS       *)
1955 (***********************)
1956
1957 let call_tactic tactic () =
1958  let notebook = (rendering_window ())#notebook in
1959  let output = ((rendering_window ())#output : GMathView.math_view) in
1960  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1961  let savedproof = !ProofEngine.proof in
1962  let savedgoal  = !ProofEngine.goal in
1963   begin
1964    try
1965     tactic () ;
1966     refresh_sequent notebook ;
1967     refresh_proof output
1968    with
1969       RefreshSequentException e ->
1970        output_html outputhtml
1971         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1972          "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
1973        ProofEngine.proof := savedproof ;
1974        ProofEngine.goal := savedgoal ;
1975        refresh_sequent notebook
1976     | RefreshProofException e ->
1977        output_html outputhtml
1978         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
1979          "proof: " ^ Printexc.to_string e ^ "</h1>") ;
1980        ProofEngine.proof := savedproof ;
1981        ProofEngine.goal := savedgoal ;
1982        refresh_sequent notebook ;
1983        refresh_proof output
1984     | e ->
1985        output_html outputhtml
1986         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
1987        ProofEngine.proof := savedproof ;
1988        ProofEngine.goal := savedgoal ;
1989   end
1990 ;;
1991
1992 let call_tactic_with_input tactic () =
1993  let notebook = (rendering_window ())#notebook in
1994  let output = ((rendering_window ())#output : GMathView.math_view) in
1995  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
1996  let inputt = ((rendering_window ())#inputt : term_editor) in
1997  let savedproof = !ProofEngine.proof in
1998  let savedgoal  = !ProofEngine.goal in
1999   let uri,metasenv,bo,ty =
2000    match !ProofEngine.proof with
2001       None -> assert false
2002     | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
2003   in
2004    let canonical_context =
2005     match !ProofEngine.goal with
2006        None -> assert false
2007      | Some metano ->
2008         let (_,canonical_context,_) =
2009          List.find (function (m,_,_) -> m=metano) metasenv
2010         in
2011          canonical_context
2012    in
2013    let context =
2014     List.map
2015      (function
2016          Some (n,_) -> Some n
2017        | None -> None
2018      ) canonical_context
2019    in
2020     try
2021      let dom,mk_metasenv_and_expr = inputt#get_term context metasenv in
2022       let (metasenv',expr) =
2023        disambiguate_input canonical_context metasenv dom mk_metasenv_and_expr
2024       in
2025        ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
2026        tactic expr ;
2027        refresh_sequent notebook ;
2028        refresh_proof output ;
2029        inputt#reset
2030     with
2031        RefreshSequentException e ->
2032         output_html outputhtml
2033          ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2034           "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2035         ProofEngine.proof := savedproof ;
2036         ProofEngine.goal := savedgoal ;
2037         refresh_sequent notebook
2038      | RefreshProofException e ->
2039         output_html outputhtml
2040          ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2041           "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2042         ProofEngine.proof := savedproof ;
2043         ProofEngine.goal := savedgoal ;
2044         refresh_sequent notebook ;
2045         refresh_proof output
2046      | e ->
2047         output_html outputhtml
2048          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2049         ProofEngine.proof := savedproof ;
2050         ProofEngine.goal := savedgoal ;
2051 ;;
2052
2053 let call_tactic_with_goal_input tactic () =
2054  let module L = LogicalOperations in
2055  let module G = Gdome in
2056   let notebook = (rendering_window ())#notebook in
2057   let output = ((rendering_window ())#output : GMathView.math_view) in
2058   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2059   let savedproof = !ProofEngine.proof in
2060   let savedgoal  = !ProofEngine.goal in
2061    match notebook#proofw#get_selection with
2062      Some node ->
2063       let xpath =
2064        ((node : Gdome.element)#getAttributeNS
2065          ~namespaceURI:helmns
2066          ~localName:(G.domString "xref"))#to_string
2067       in
2068        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2069        else
2070         begin
2071          try
2072           match !current_goal_infos with
2073              Some (ids_to_terms, ids_to_father_ids,_) ->
2074               let id = xpath in
2075                tactic (Hashtbl.find ids_to_terms id) ;
2076                refresh_sequent notebook ;
2077                refresh_proof output
2078            | None -> assert false (* "ERROR: No current term!!!" *)
2079          with
2080             RefreshSequentException e ->
2081              output_html outputhtml
2082               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2083                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2084              ProofEngine.proof := savedproof ;
2085              ProofEngine.goal := savedgoal ;
2086              refresh_sequent notebook
2087           | RefreshProofException e ->
2088              output_html outputhtml
2089               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2090                "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2091              ProofEngine.proof := savedproof ;
2092              ProofEngine.goal := savedgoal ;
2093              refresh_sequent notebook ;
2094              refresh_proof output
2095           | e ->
2096              output_html outputhtml
2097               ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2098              ProofEngine.proof := savedproof ;
2099              ProofEngine.goal := savedgoal ;
2100         end
2101    | None ->
2102       output_html outputhtml
2103        ("<h1 color=\"red\">No term selected</h1>")
2104 ;;
2105
2106 let call_tactic_with_input_and_goal_input tactic () =
2107  let module L = LogicalOperations in
2108  let module G = Gdome in
2109   let notebook = (rendering_window ())#notebook in
2110   let output = ((rendering_window ())#output : GMathView.math_view) in
2111   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2112   let inputt = ((rendering_window ())#inputt : term_editor) in
2113   let savedproof = !ProofEngine.proof in
2114   let savedgoal  = !ProofEngine.goal in
2115    match notebook#proofw#get_selection with
2116      Some node ->
2117       let xpath =
2118        ((node : Gdome.element)#getAttributeNS
2119          ~namespaceURI:helmns
2120          ~localName:(G.domString "xref"))#to_string
2121       in
2122        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2123        else
2124         begin
2125          try
2126           match !current_goal_infos with
2127              Some (ids_to_terms, ids_to_father_ids,_) ->
2128               let id = xpath in
2129                let uri,metasenv,bo,ty =
2130                 match !ProofEngine.proof with
2131                    None -> assert false
2132                  | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
2133                in
2134                 let canonical_context =
2135                  match !ProofEngine.goal with
2136                     None -> assert false
2137                   | Some metano ->
2138                      let (_,canonical_context,_) =
2139                       List.find (function (m,_,_) -> m=metano) metasenv
2140                      in
2141                       canonical_context in
2142                 let context =
2143                  List.map
2144                   (function
2145                       Some (n,_) -> Some n
2146                     | None -> None
2147                   ) canonical_context
2148                 in
2149                  let dom,mk_metasenv_and_expr = inputt#get_term context metasenv
2150                  in
2151                   let (metasenv',expr) =
2152                    disambiguate_input canonical_context metasenv dom
2153                     mk_metasenv_and_expr
2154                   in
2155                    ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
2156                    tactic ~goal_input:(Hashtbl.find ids_to_terms id)
2157                     ~input:expr ;
2158                    refresh_sequent notebook ;
2159                    refresh_proof output ;
2160                    inputt#reset
2161            | None -> assert false (* "ERROR: No current term!!!" *)
2162          with
2163             RefreshSequentException e ->
2164              output_html outputhtml
2165               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2166                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2167              ProofEngine.proof := savedproof ;
2168              ProofEngine.goal := savedgoal ;
2169              refresh_sequent notebook
2170           | RefreshProofException e ->
2171              output_html outputhtml
2172               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2173                "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2174              ProofEngine.proof := savedproof ;
2175              ProofEngine.goal := savedgoal ;
2176              refresh_sequent notebook ;
2177              refresh_proof output
2178           | e ->
2179              output_html outputhtml
2180               ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2181              ProofEngine.proof := savedproof ;
2182              ProofEngine.goal := savedgoal ;
2183         end
2184    | None ->
2185       output_html outputhtml
2186        ("<h1 color=\"red\">No term selected</h1>")
2187 ;;
2188
2189 let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
2190  let module L = LogicalOperations in
2191  let module G = Gdome in
2192   let mmlwidget = (scratch_window#mmlwidget : GMathView.math_view) in
2193   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2194   let savedproof = !ProofEngine.proof in
2195   let savedgoal  = !ProofEngine.goal in
2196    match mmlwidget#get_selection with
2197      Some node ->
2198       let xpath =
2199        ((node : Gdome.element)#getAttributeNS
2200          ~namespaceURI:helmns
2201          ~localName:(G.domString "xref"))#to_string
2202       in
2203        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2204        else
2205         begin
2206          try
2207           match !current_scratch_infos with
2208              (* term is the whole goal in the scratch_area *)
2209              Some (term,ids_to_terms, ids_to_father_ids,_) ->
2210               let id = xpath in
2211                let expr = tactic term (Hashtbl.find ids_to_terms id) in
2212                 let mml = mml_of_cic_term 111 expr in
2213                  scratch_window#show () ;
2214                  scratch_window#mmlwidget#load_tree ~dom:mml
2215            | None -> assert false (* "ERROR: No current term!!!" *)
2216          with
2217           e ->
2218            output_html outputhtml
2219             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2220         end
2221    | None ->
2222       output_html outputhtml
2223        ("<h1 color=\"red\">No term selected</h1>")
2224 ;;
2225
2226 let call_tactic_with_hypothesis_input tactic () =
2227  let module L = LogicalOperations in
2228  let module G = Gdome in
2229   let notebook = (rendering_window ())#notebook in
2230   let output = ((rendering_window ())#output : GMathView.math_view) in
2231   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2232   let savedproof = !ProofEngine.proof in
2233   let savedgoal  = !ProofEngine.goal in
2234    match notebook#proofw#get_selection with
2235      Some node ->
2236       let xpath =
2237        ((node : Gdome.element)#getAttributeNS
2238          ~namespaceURI:helmns
2239          ~localName:(G.domString "xref"))#to_string
2240       in
2241        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
2242        else
2243         begin
2244          try
2245           match !current_goal_infos with
2246              Some (_,_,ids_to_hypotheses) ->
2247               let id = xpath in
2248                tactic (Hashtbl.find ids_to_hypotheses id) ;
2249                refresh_sequent notebook ;
2250                refresh_proof output
2251            | None -> assert false (* "ERROR: No current term!!!" *)
2252          with
2253             RefreshSequentException e ->
2254              output_html outputhtml
2255               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2256                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
2257              ProofEngine.proof := savedproof ;
2258              ProofEngine.goal := savedgoal ;
2259              refresh_sequent notebook
2260           | RefreshProofException e ->
2261              output_html outputhtml
2262               ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2263                "proof: " ^ Printexc.to_string e ^ "</h1>") ;
2264              ProofEngine.proof := savedproof ;
2265              ProofEngine.goal := savedgoal ;
2266              refresh_sequent notebook ;
2267              refresh_proof output
2268           | e ->
2269              output_html outputhtml
2270               ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2271              ProofEngine.proof := savedproof ;
2272              ProofEngine.goal := savedgoal ;
2273         end
2274    | None ->
2275       output_html outputhtml
2276        ("<h1 color=\"red\">No term selected</h1>")
2277 ;;
2278
2279
2280 let intros = call_tactic ProofEngine.intros;;
2281 let exact = call_tactic_with_input ProofEngine.exact;;
2282 let apply = call_tactic_with_input ProofEngine.apply;;
2283 let elimintrossimpl = call_tactic_with_input ProofEngine.elim_intros_simpl;;
2284 let elimtype = call_tactic_with_input ProofEngine.elim_type;;
2285 let whd = call_tactic_with_goal_input ProofEngine.whd;;
2286 let reduce = call_tactic_with_goal_input ProofEngine.reduce;;
2287 let simpl = call_tactic_with_goal_input ProofEngine.simpl;;
2288 let fold_whd = call_tactic_with_input ProofEngine.fold_whd;;
2289 let fold_reduce = call_tactic_with_input ProofEngine.fold_reduce;;
2290 let fold_simpl = call_tactic_with_input ProofEngine.fold_simpl;;
2291 let cut = call_tactic_with_input ProofEngine.cut;;
2292 let change = call_tactic_with_input_and_goal_input ProofEngine.change;;
2293 let letin = call_tactic_with_input ProofEngine.letin;;
2294 let ring = call_tactic ProofEngine.ring;;
2295 let clearbody = call_tactic_with_hypothesis_input ProofEngine.clearbody;;
2296 let clear = call_tactic_with_hypothesis_input ProofEngine.clear;;
2297 let fourier = call_tactic ProofEngine.fourier;;
2298 let rewritesimpl = call_tactic_with_input ProofEngine.rewrite_simpl;;
2299 let reflexivity = call_tactic ProofEngine.reflexivity;;
2300 let symmetry = call_tactic ProofEngine.symmetry;;
2301 let transitivity = call_tactic_with_input ProofEngine.transitivity;;
2302 let exists = call_tactic ProofEngine.exists;;
2303 let split = call_tactic ProofEngine.split;;
2304 let left = call_tactic ProofEngine.left;;
2305 let right = call_tactic ProofEngine.right;;
2306 let assumption = call_tactic ProofEngine.assumption;;
2307 let generalize = call_tactic_with_goal_input ProofEngine.generalize;;
2308 let absurd = call_tactic_with_input ProofEngine.absurd;;
2309 let contradiction = call_tactic ProofEngine.contradiction;;
2310 (* Galla: come dare alla tattica la lista di termini da decomporre?
2311 let decompose = call_tactic_with_input_and_goal_input ProofEngine.decompose;;
2312 *)
2313
2314 let whd_in_scratch scratch_window =
2315  call_tactic_with_goal_input_in_scratch ProofEngine.whd_in_scratch
2316   scratch_window
2317 ;;
2318 let reduce_in_scratch scratch_window =
2319  call_tactic_with_goal_input_in_scratch ProofEngine.reduce_in_scratch
2320   scratch_window
2321 ;;
2322 let simpl_in_scratch scratch_window =
2323  call_tactic_with_goal_input_in_scratch ProofEngine.simpl_in_scratch
2324   scratch_window
2325 ;;
2326
2327
2328
2329 (**********************)
2330 (*   END OF TACTICS   *)
2331 (**********************)
2332
2333
2334 let show () =
2335  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2336   try
2337    show_in_show_window_uri (input_or_locate_uri ~title:"Show")
2338   with
2339    e ->
2340     output_html outputhtml
2341      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2342 ;;
2343
2344 exception NotADefinition;;
2345
2346 let open_ () =
2347  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2348  let output = ((rendering_window ())#output : GMathView.math_view) in
2349  let notebook = (rendering_window ())#notebook in
2350    try
2351     let uri = input_or_locate_uri ~title:"Open" in
2352      CicTypeChecker.typecheck uri ;
2353      let metasenv,bo,ty =
2354       match CicEnvironment.get_cooked_obj uri with
2355          Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
2356        | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
2357        | Cic.Constant _
2358        | Cic.Variable _
2359        | Cic.InductiveDefinition _ -> raise NotADefinition
2360      in
2361       ProofEngine.proof :=
2362        Some (uri, metasenv, bo, ty) ;
2363       ProofEngine.goal := None ;
2364       refresh_sequent notebook ;
2365       refresh_proof output
2366    with
2367       RefreshSequentException e ->
2368        output_html outputhtml
2369         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2370          "sequent: " ^ Printexc.to_string e ^ "</h1>")
2371     | RefreshProofException e ->
2372        output_html outputhtml
2373         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
2374          "proof: " ^ Printexc.to_string e ^ "</h1>")
2375     | e ->
2376        output_html outputhtml
2377         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2378 ;;
2379
2380 let show_query_results results =
2381  let window =
2382   GWindow.window
2383    ~modal:false ~title:"Query results." ~border_width:2 () in
2384  let vbox = GPack.vbox ~packing:window#add () in
2385  let hbox =
2386   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2387  let lMessage =
2388   GMisc.label
2389    ~text:"Click on a URI to show that object"
2390    ~packing:hbox#add () in
2391  let scrolled_window =
2392   GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
2393    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2394  let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
2395   ignore
2396    (List.map
2397      (function (uri,_) ->
2398        let n =
2399         clist#append [uri]
2400        in
2401         clist#set_row ~selectable:false n
2402      ) results
2403    ) ;
2404   clist#columns_autosize () ;
2405   ignore
2406    (clist#connect#select_row
2407      (fun ~row ~column ~event ->
2408        let (uristr,_) = List.nth results row in
2409         match
2410          cic_textual_parser_uri_of_string
2411           (wrong_xpointer_format_from_wrong_xpointer_format' uristr)
2412         with
2413            CicTextualParser0.ConUri uri
2414          | CicTextualParser0.VarUri uri
2415          | CicTextualParser0.IndTyUri (uri,_)
2416          | CicTextualParser0.IndConUri (uri,_,_) ->
2417             show_in_show_window_uri uri
2418      )
2419    ) ;
2420   window#show ()
2421 ;;
2422
2423 let refine_constraints (must_obj,must_rel,must_sort) =
2424  let chosen = ref false in
2425  let use_only = ref false in
2426  let window =
2427   GWindow.window
2428    ~modal:true ~title:"Constraints refinement."
2429    ~width:800 ~border_width:2 () in
2430  let vbox = GPack.vbox ~packing:window#add () in
2431  let hbox =
2432   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2433  let lMessage =
2434   GMisc.label
2435    ~text: "\"Only\" constraints can be enforced or not."
2436    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2437  let onlyb =
2438   GButton.toggle_button ~label:"Enforce \"only\" constraints"
2439    ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2440  in
2441   ignore
2442    (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
2443  (* Notebook for the constraints choice *)
2444  let notebook =
2445   GPack.notebook ~scrollable:true
2446    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2447  (* Rel constraints *)
2448  let label =
2449   GMisc.label
2450    ~text: "Constraints on Rels" () in
2451  let vbox' =
2452   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
2453    () in
2454  let hbox =
2455   GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
2456  let lMessage =
2457   GMisc.label
2458    ~text: "You can now specify the constraints on Rels."
2459    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2460  let expected_height = 25 * (List.length must_rel + 2) in
2461  let height = if expected_height > 400 then 400 else expected_height in
2462  let scrolled_window =
2463   GBin.scrolled_window ~border_width:10 ~height ~width:600
2464    ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
2465  let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
2466  let rel_constraints =
2467   List.map
2468    (function (position,depth) ->
2469      let hbox =
2470       GPack.hbox
2471        ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
2472      let lMessage =
2473       GMisc.label
2474        ~text:position
2475        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2476      match depth with
2477         None -> position, ref None
2478       | Some depth' ->
2479          let mutable_ref = ref (Some depth') in
2480          let depthb =
2481           GButton.toggle_button
2482            ~label:("depth = " ^ string_of_int depth') ~active:true
2483            ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2484          in
2485           ignore
2486            (depthb#connect#toggled
2487              (function () ->
2488                let sel_depth = if depthb#active then Some depth' else None in
2489                 mutable_ref := sel_depth
2490             )) ;
2491           position, mutable_ref
2492    ) must_rel in
2493  (* Sort constraints *)
2494  let label =
2495   GMisc.label
2496    ~text: "Constraints on Sorts" () in
2497  let vbox' =
2498   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
2499    () in
2500  let hbox =
2501   GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
2502  let lMessage =
2503   GMisc.label
2504    ~text: "You can now specify the constraints on Sorts."
2505    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2506  let expected_height = 25 * (List.length must_sort + 2) in
2507  let height = if expected_height > 400 then 400 else expected_height in
2508  let scrolled_window =
2509   GBin.scrolled_window ~border_width:10 ~height ~width:600
2510    ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
2511  let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
2512  let sort_constraints =
2513   List.map
2514    (function (position,depth,sort) ->
2515      let hbox =
2516       GPack.hbox
2517        ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
2518      let lMessage =
2519       GMisc.label
2520        ~text:(sort ^ " " ^ position)
2521        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2522      match depth with
2523         None -> position, ref None, sort
2524       | Some depth' ->
2525          let mutable_ref = ref (Some depth') in
2526          let depthb =
2527           GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
2528            ~active:true
2529            ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2530          in
2531           ignore
2532            (depthb#connect#toggled
2533              (function () ->
2534                let sel_depth = if depthb#active then Some depth' else None in
2535                 mutable_ref := sel_depth
2536             )) ;
2537           position, mutable_ref, sort
2538    ) must_sort in
2539  (* Obj constraints *)
2540  let label =
2541   GMisc.label
2542    ~text: "Constraints on constants" () in
2543  let vbox' =
2544   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
2545    () in
2546  let hbox =
2547   GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
2548  let lMessage =
2549   GMisc.label
2550    ~text: "You can now specify the constraints on constants."
2551    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2552  let expected_height = 25 * (List.length must_obj + 2) in
2553  let height = if expected_height > 400 then 400 else expected_height in
2554  let scrolled_window =
2555   GBin.scrolled_window ~border_width:10 ~height ~width:600
2556    ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
2557  let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
2558  let obj_constraints =
2559   List.map
2560    (function (uri,position,depth) ->
2561      let hbox =
2562       GPack.hbox
2563        ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
2564      let lMessage =
2565       GMisc.label
2566        ~text:(uri ^ " " ^ position)
2567        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2568      match depth with
2569         None -> uri, position, ref None
2570       | Some depth' ->
2571          let mutable_ref = ref (Some depth') in
2572          let depthb =
2573           GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
2574            ~active:true
2575            ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2576          in
2577           ignore
2578            (depthb#connect#toggled
2579              (function () ->
2580                let sel_depth = if depthb#active then Some depth' else None in
2581                 mutable_ref := sel_depth
2582             )) ;
2583           uri, position, mutable_ref
2584    ) must_obj in
2585  (* Confirm/abort buttons *)
2586  let hbox =
2587   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2588  let okb =
2589   GButton.button ~label:"Ok"
2590    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2591  let cancelb =
2592   GButton.button ~label:"Abort"
2593    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
2594  in
2595   ignore (window#connect#destroy GMain.Main.quit) ;
2596   ignore (cancelb#connect#clicked window#destroy) ;
2597   ignore
2598    (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
2599   window#set_position `CENTER ;
2600   window#show () ;
2601   GMain.Main.main () ;
2602   if !chosen then
2603    let chosen_must_rel =
2604     List.map
2605      (function (position,ref_depth) -> position,!ref_depth) rel_constraints in
2606    let chosen_must_sort =
2607     List.map
2608      (function (position,ref_depth,sort) -> position,!ref_depth,sort)
2609      sort_constraints
2610    in
2611    let chosen_must_obj =
2612     List.map
2613      (function (uri,position,ref_depth) -> uri,position,!ref_depth)
2614      obj_constraints
2615    in
2616     (chosen_must_obj,chosen_must_rel,chosen_must_sort),
2617      (if !use_only then
2618 (*CSC: ???????????????????????? I assume that must and only are the same... *)
2619        Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
2620       else
2621        None,None,None
2622      )
2623   else
2624    raise NoChoice
2625 ;;
2626
2627 let completeSearchPattern () =
2628  let inputt = ((rendering_window ())#inputt : term_editor) in
2629  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2630   try
2631    let dom,mk_metasenv_and_expr = inputt#get_term ~context:[] ~metasenv:[] in
2632    let metasenv,expr = disambiguate_input [] [] dom mk_metasenv_and_expr in
2633    let must = MQueryLevels2.get_constraints expr in
2634    let must',only = refine_constraints must in
2635    let results = MQueryGenerator.searchPattern must' only in 
2636     show_query_results results
2637   with
2638    e ->
2639     output_html outputhtml
2640      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
2641 ;;
2642
2643 let choose_must list_of_must only =
2644  let chosen = ref None in
2645  let user_constraints = ref [] in
2646  let window =
2647   GWindow.window
2648    ~modal:true ~title:"Query refinement." ~border_width:2 () in
2649  let vbox = GPack.vbox ~packing:window#add () in
2650  let hbox =
2651   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2652  let lMessage =
2653   GMisc.label
2654    ~text:
2655     ("You can now specify the genericity of the query. " ^
2656      "The more generic the slower.")
2657    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2658  let hbox =
2659   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2660  let lMessage =
2661   GMisc.label
2662    ~text:
2663     "Suggestion: start with faster queries before moving to more generic ones."
2664    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2665  let notebook =
2666   GPack.notebook ~scrollable:true
2667    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2668  let _ =
2669   let page = ref 0 in
2670   let last = List.length list_of_must in
2671   List.map
2672    (function must ->
2673      incr page ;
2674      let label =
2675       GMisc.label ~text:
2676        (if !page = 1 then "More generic" else
2677          if !page = last then "More precise" else "          ") () in
2678      let expected_height = 25 * (List.length must + 2) in
2679      let height = if expected_height > 400 then 400 else expected_height in
2680      let scrolled_window =
2681       GBin.scrolled_window ~border_width:10 ~height ~width:600
2682        ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2683      let clist =
2684         GList.clist ~columns:2 ~packing:scrolled_window#add
2685          ~titles:["URI" ; "Position"] ()
2686      in
2687       ignore
2688        (List.map
2689          (function (uri,position) ->
2690            let n =
2691             clist#append 
2692              [uri; if position then "MainConclusion" else "Conclusion"]
2693            in
2694             clist#set_row ~selectable:false n
2695          ) must
2696        ) ;
2697       clist#columns_autosize ()
2698    ) list_of_must in
2699  let _ =
2700   let label = GMisc.label ~text:"User provided" () in
2701   let vbox =
2702    GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
2703   let hbox =
2704    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2705   let lMessage =
2706    GMisc.label
2707    ~text:"Select the constraints that must be satisfied and press OK."
2708    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2709   let expected_height = 25 * (List.length only + 2) in
2710   let height = if expected_height > 400 then 400 else expected_height in
2711   let scrolled_window =
2712    GBin.scrolled_window ~border_width:10 ~height ~width:600
2713     ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
2714   let clist =
2715    GList.clist ~columns:2 ~packing:scrolled_window#add
2716     ~selection_mode:`EXTENDED
2717     ~titles:["URI" ; "Position"] ()
2718   in
2719    ignore
2720     (List.map
2721       (function (uri,position) ->
2722         let n =
2723          clist#append 
2724           [uri; if position then "MainConclusion" else "Conclusion"]
2725         in
2726          clist#set_row ~selectable:true n
2727       ) only
2728     ) ;
2729    clist#columns_autosize () ;
2730    ignore
2731     (clist#connect#select_row
2732       (fun ~row ~column ~event ->
2733         user_constraints := (List.nth only row)::!user_constraints)) ;
2734    ignore
2735     (clist#connect#unselect_row
2736       (fun ~row ~column ~event ->
2737         user_constraints :=
2738          List.filter
2739           (function uri -> uri != (List.nth only row)) !user_constraints)) ;
2740  in
2741  let hbox =
2742   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2743  let okb =
2744   GButton.button ~label:"Ok"
2745    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2746  let cancelb =
2747   GButton.button ~label:"Abort"
2748    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2749  (* actions *)
2750  ignore (window#connect#destroy GMain.Main.quit) ;
2751  ignore (cancelb#connect#clicked window#destroy) ;
2752  ignore
2753   (okb#connect#clicked
2754     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
2755  window#set_position `CENTER ;
2756  window#show () ;
2757  GMain.Main.main () ;
2758  match !chosen with
2759     None -> raise NoChoice
2760   | Some n ->
2761      if n = List.length list_of_must then
2762       (* user provided constraints *)
2763       !user_constraints
2764      else
2765       List.nth list_of_must n
2766 ;;
2767
2768 let searchPattern () =
2769  let inputt = ((rendering_window ())#inputt : term_editor) in
2770  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
2771   try
2772     let metasenv =
2773      match !ProofEngine.proof with
2774         None -> assert false
2775       | Some (_,metasenv,_,_) -> metasenv
2776     in
2777      match !ProofEngine.goal with
2778         None -> ()
2779       | Some metano ->
2780          let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
2781           let list_of_must,only = MQueryLevels.out_restr metasenv ey ty in
2782           let must = choose_must list_of_must only in
2783           let torigth_restriction (u,b) =
2784            let p =
2785             if b then
2786              "http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion" 
2787             else
2788              "http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion"
2789            in
2790             (u,p,None)
2791           in
2792           let rigth_must = List.map torigth_restriction must in
2793           let rigth_only = Some (List.map torigth_restriction only) in
2794           let result =
2795            MQueryGenerator.searchPattern
2796             (rigth_must,[],[]) (rigth_only,None,None) in 
2797           let uris =
2798            List.map
2799             (function uri,_ ->
2800               wrong_xpointer_format_from_wrong_xpointer_format' uri
2801             ) result in
2802           let html =
2803            " <h1>Backward Query: </h1>" ^
2804            " <pre>" ^ get_last_query result ^ "</pre>"
2805           in
2806            output_html outputhtml html ;
2807            let uris',exc =
2808             let rec filter_out =
2809              function
2810                 [] -> [],""
2811               | uri::tl ->
2812                  let tl',exc = filter_out tl in
2813                   try
2814                    if
2815                     ProofEngine.can_apply
2816                      (term_of_cic_textual_parser_uri
2817                       (cic_textual_parser_uri_of_string uri))
2818                    then
2819                     uri::tl',exc
2820                    else
2821                     tl',exc
2822                   with
2823                    e ->
2824                     let exc' =
2825                      "<h1 color=\"red\"> ^ Exception raised trying to apply " ^
2826                       uri ^ ": " ^ Printexc.to_string e ^ " </h1>" ^ exc
2827                     in
2828                      tl',exc'
2829             in
2830              filter_out uris
2831            in
2832             let html' =
2833              " <h1>Objects that can actually be applied: </h1> " ^
2834              String.concat "<br>" uris' ^ exc ^
2835              " <h1>Number of false matches: " ^
2836               string_of_int (List.length uris - List.length uris') ^ "</h1>" ^
2837              " <h1>Number of good matches: " ^
2838               string_of_int (List.length uris') ^ "</h1>"
2839             in
2840              output_html outputhtml html' ;
2841              let uri' =
2842               user_uri_choice ~title:"Ambiguous input."
2843               ~msg:
2844                 "Many lemmas can be successfully applied. Please, choose one:"
2845                uris'
2846              in
2847               inputt#set_term uri' ;
2848               apply ()
2849   with
2850    e -> 
2851     output_html outputhtml 
2852      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
2853 ;;
2854       
2855 let choose_selection
2856      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
2857 =
2858  let module G = Gdome in
2859   let rec aux element =
2860    if element#hasAttributeNS
2861        ~namespaceURI:helmns
2862        ~localName:(G.domString "xref")
2863    then
2864      mmlwidget#set_selection (Some element)
2865    else
2866       match element#get_parentNode with
2867          None -> assert false
2868        (*CSC: OCAML DIVERGES!
2869        | Some p -> aux (new G.element_of_node p)
2870        *)
2871        | Some p -> aux (new Gdome.element_of_node p)
2872   in
2873    match element with
2874      Some x -> aux x
2875    | None   -> mmlwidget#set_selection None
2876 ;;
2877
2878 (* STUFF TO BUILD THE GTK INTERFACE *)
2879
2880 (* Stuff for the widget settings *)
2881
2882 let export_to_postscript (output : GMathView.math_view) =
2883  let lastdir = ref (Unix.getcwd ()) in
2884   function () ->
2885    match
2886     GToolbox.select_file ~title:"Export to PostScript"
2887      ~dir:lastdir ~filename:"screenshot.ps" ()
2888    with
2889       None -> ()
2890     | Some filename ->
2891        output#export_to_postscript ~filename:filename ();
2892 ;;
2893
2894 let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
2895  button_set_kerning button_set_transparency export_to_postscript_menu_item
2896  button_t1 ()
2897 =
2898  let is_set = button_t1#active in
2899   output#set_font_manager_type
2900    (if is_set then `font_manager_t1 else `font_manager_gtk) ;
2901   if is_set then
2902    begin
2903     button_set_anti_aliasing#misc#set_sensitive true ;
2904     button_set_kerning#misc#set_sensitive true ;
2905     button_set_transparency#misc#set_sensitive true ;
2906     export_to_postscript_menu_item#misc#set_sensitive true ;
2907    end
2908   else
2909    begin
2910     button_set_anti_aliasing#misc#set_sensitive false ;
2911     button_set_kerning#misc#set_sensitive false ;
2912     button_set_transparency#misc#set_sensitive false ;
2913     export_to_postscript_menu_item#misc#set_sensitive false ;
2914    end
2915 ;;
2916
2917 let set_anti_aliasing output button_set_anti_aliasing () =
2918  output#set_anti_aliasing button_set_anti_aliasing#active
2919 ;;
2920
2921 let set_kerning output button_set_kerning () =
2922  output#set_kerning button_set_kerning#active
2923 ;;
2924
2925 let set_transparency output button_set_transparency () =
2926  output#set_transparency button_set_transparency#active
2927 ;;
2928
2929 let changefont output font_size_spinb () =
2930  output#set_font_size font_size_spinb#value_as_int
2931 ;;
2932
2933 let set_log_verbosity output log_verbosity_spinb () =
2934  output#set_log_verbosity log_verbosity_spinb#value_as_int
2935 ;;
2936
2937 class settings_window (output : GMathView.math_view) sw
2938  export_to_postscript_menu_item selection_changed_callback
2939 =
2940  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
2941  let vbox =
2942   GPack.vbox ~packing:settings_window#add () in
2943  let table =
2944   GPack.table
2945    ~rows:1 ~columns:3 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2946    ~border_width:5 ~packing:vbox#add () in
2947  let button_t1 =
2948   GButton.toggle_button ~label:"activate t1 fonts"
2949    ~packing:(table#attach ~left:0 ~top:0) () in
2950  let button_set_anti_aliasing =
2951   GButton.toggle_button ~label:"set_anti_aliasing"
2952    ~packing:(table#attach ~left:0 ~top:1) () in
2953  let button_set_kerning =
2954   GButton.toggle_button ~label:"set_kerning"
2955    ~packing:(table#attach ~left:1 ~top:1) () in
2956  let button_set_transparency =
2957   GButton.toggle_button ~label:"set_transparency"
2958    ~packing:(table#attach ~left:2 ~top:1) () in
2959  let table =
2960   GPack.table
2961    ~rows:2 ~columns:2 ~homogeneous:false ~row_spacings:5 ~col_spacings:5
2962    ~border_width:5 ~packing:vbox#add () in
2963  let font_size_label =
2964   GMisc.label ~text:"font size:"
2965    ~packing:(table#attach ~left:0 ~top:0 ~expand:`NONE) () in
2966  let font_size_spinb =
2967   let sadj =
2968    GData.adjustment ~value:14.0 ~lower:5.0 ~upper:50.0 ~step_incr:1.0 ()
2969   in
2970    GEdit.spin_button 
2971     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:0 ~fill:`NONE) () in
2972  let log_verbosity_label =
2973   GMisc.label ~text:"log verbosity:"
2974    ~packing:(table#attach ~left:0 ~top:1) () in
2975  let log_verbosity_spinb =
2976   let sadj =
2977    GData.adjustment ~value:0.0 ~lower:0.0 ~upper:3.0 ~step_incr:1.0 ()
2978   in
2979    GEdit.spin_button 
2980     ~adjustment:sadj ~packing:(table#attach ~left:1 ~top:1) () in
2981  let hbox =
2982   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
2983  let closeb =
2984   GButton.button ~label:"Close"
2985    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
2986 object(self)
2987  method show = settings_window#show
2988  initializer
2989   button_set_anti_aliasing#misc#set_sensitive false ;
2990   button_set_kerning#misc#set_sensitive false ;
2991   button_set_transparency#misc#set_sensitive false ;
2992   (* Signals connection *)
2993   ignore(button_t1#connect#clicked
2994    (activate_t1 output button_set_anti_aliasing button_set_kerning
2995     button_set_transparency export_to_postscript_menu_item button_t1)) ;
2996   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
2997   ignore(button_set_anti_aliasing#connect#toggled
2998    (set_anti_aliasing output button_set_anti_aliasing));
2999   ignore(button_set_kerning#connect#toggled
3000    (set_kerning output button_set_kerning)) ;
3001   ignore(button_set_transparency#connect#toggled
3002    (set_transparency output button_set_transparency)) ;
3003   ignore(log_verbosity_spinb#connect#changed
3004    (set_log_verbosity output log_verbosity_spinb)) ;
3005   ignore(closeb#connect#clicked settings_window#misc#hide)
3006 end;;
3007
3008 (* Scratch window *)
3009
3010 class scratch_window =
3011  let window =
3012   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
3013  let vbox =
3014   GPack.vbox ~packing:window#add () in
3015  let hbox =
3016   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
3017  let whdb =
3018   GButton.button ~label:"Whd"
3019    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
3020  let reduceb =
3021   GButton.button ~label:"Reduce"
3022    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
3023  let simplb =
3024   GButton.button ~label:"Simpl"
3025    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
3026  let scrolled_window =
3027   GBin.scrolled_window ~border_width:10
3028    ~packing:(vbox#pack ~expand:true ~padding:5) () in
3029  let mmlwidget =
3030   GMathView.math_view
3031    ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
3032 object(self)
3033  method mmlwidget = mmlwidget
3034  method show () = window#misc#hide () ; window#show ()
3035  initializer
3036   ignore(mmlwidget#connect#selection_changed (choose_selection mmlwidget)) ;
3037   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
3038   ignore(whdb#connect#clicked (whd_in_scratch self)) ;
3039   ignore(reduceb#connect#clicked (reduce_in_scratch self)) ;
3040   ignore(simplb#connect#clicked (simpl_in_scratch self))
3041 end;;
3042
3043 class page () =
3044  let vbox1 = GPack.vbox () in
3045 object(self)
3046  val mutable proofw_ref = None
3047  val mutable compute_ref = None
3048  method proofw =
3049   Lazy.force self#compute ;
3050   match proofw_ref with
3051      None -> assert false
3052    | Some proofw -> proofw
3053  method content = vbox1
3054  method compute =
3055   match compute_ref with
3056      None -> assert false
3057    | Some compute -> compute
3058  initializer
3059   compute_ref <-
3060    Some (lazy (
3061    let scrolled_window1 =
3062     GBin.scrolled_window ~border_width:10
3063      ~packing:(vbox1#pack ~expand:true ~padding:5) () in
3064    let proofw =
3065     GMathView.math_view ~width:400 ~height:275
3066      ~packing:(scrolled_window1#add) () in
3067    let _ = proofw_ref <- Some proofw in
3068    let hbox3 =
3069     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3070    let exactb =
3071     GButton.button ~label:"Exact"
3072      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3073    let introsb =
3074     GButton.button ~label:"Intros"
3075      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3076    let applyb =
3077     GButton.button ~label:"Apply"
3078      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3079    let elimintrossimplb =
3080     GButton.button ~label:"ElimIntrosSimpl"
3081      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3082    let elimtypeb =
3083     GButton.button ~label:"ElimType"
3084      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3085    let whdb =
3086     GButton.button ~label:"Whd"
3087      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3088    let reduceb =
3089     GButton.button ~label:"Reduce"
3090      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3091    let simplb =
3092     GButton.button ~label:"Simpl"
3093      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3094    let foldwhdb =
3095     GButton.button ~label:"Fold_whd"
3096      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
3097    let hbox4 =
3098     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3099    let foldreduceb =
3100     GButton.button ~label:"Fold_reduce"
3101      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3102    let foldsimplb =
3103     GButton.button ~label:"Fold_simpl"
3104      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3105    let cutb =
3106     GButton.button ~label:"Cut"
3107      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3108    let changeb =
3109     GButton.button ~label:"Change"
3110      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3111    let letinb =
3112     GButton.button ~label:"Let ... In"
3113      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3114    let ringb =
3115     GButton.button ~label:"Ring"
3116      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3117    let clearbodyb =
3118     GButton.button ~label:"ClearBody"
3119      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3120    let clearb =
3121     GButton.button ~label:"Clear"
3122      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
3123    let hbox5 =
3124     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3125    let fourierb =
3126     GButton.button ~label:"Fourier"
3127      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3128    let rewritesimplb =
3129     GButton.button ~label:"RewriteSimpl ->"
3130      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3131    let reflexivityb =
3132     GButton.button ~label:"Reflexivity"
3133      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3134    let symmetryb =
3135     GButton.button ~label:"Symmetry"
3136      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3137    let transitivityb =
3138     GButton.button ~label:"Transitivity"
3139      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3140    let existsb =
3141     GButton.button ~label:"Exists"
3142      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3143    let splitb =
3144     GButton.button ~label:"Split"
3145      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
3146    let hbox6 =
3147     GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
3148    let leftb =
3149     GButton.button ~label:"Left"
3150      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3151    let rightb =
3152     GButton.button ~label:"Right"
3153      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3154    let assumptionb =
3155     GButton.button ~label:"Assumption"
3156      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3157    let generalizeb =
3158     GButton.button ~label:"Generalize"
3159      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3160    let absurdb =
3161     GButton.button ~label:"Absurd"
3162      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3163    let contradictionb =
3164     GButton.button ~label:"Contradiction"
3165      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3166    let searchpatternb =
3167     GButton.button ~label:"SearchPattern_Apply"
3168      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
3169
3170    ignore(exactb#connect#clicked exact) ;
3171    ignore(applyb#connect#clicked apply) ;
3172    ignore(elimintrossimplb#connect#clicked elimintrossimpl) ;
3173    ignore(elimtypeb#connect#clicked elimtype) ;
3174    ignore(whdb#connect#clicked whd) ;
3175    ignore(reduceb#connect#clicked reduce) ;
3176    ignore(simplb#connect#clicked simpl) ;
3177    ignore(foldwhdb#connect#clicked fold_whd) ;
3178    ignore(foldreduceb#connect#clicked fold_reduce) ;
3179    ignore(foldsimplb#connect#clicked fold_simpl) ;
3180    ignore(cutb#connect#clicked cut) ;
3181    ignore(changeb#connect#clicked change) ;
3182    ignore(letinb#connect#clicked letin) ;
3183    ignore(ringb#connect#clicked ring) ;
3184    ignore(clearbodyb#connect#clicked clearbody) ;
3185    ignore(clearb#connect#clicked clear) ;
3186    ignore(fourierb#connect#clicked fourier) ;
3187    ignore(rewritesimplb#connect#clicked rewritesimpl) ;
3188    ignore(reflexivityb#connect#clicked reflexivity) ;
3189    ignore(symmetryb#connect#clicked symmetry) ;
3190    ignore(transitivityb#connect#clicked transitivity) ;
3191    ignore(existsb#connect#clicked exists) ;
3192    ignore(splitb#connect#clicked split) ;
3193    ignore(leftb#connect#clicked left) ;
3194    ignore(rightb#connect#clicked right) ;
3195    ignore(assumptionb#connect#clicked assumption) ;
3196    ignore(generalizeb#connect#clicked generalize) ;
3197    ignore(absurdb#connect#clicked absurd) ;
3198    ignore(contradictionb#connect#clicked contradiction) ;
3199    ignore(introsb#connect#clicked intros) ;
3200    ignore(searchpatternb#connect#clicked searchPattern) ;
3201    ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
3202   ))
3203 end
3204 ;;
3205
3206 class empty_page =
3207  let vbox1 = GPack.vbox () in
3208  let scrolled_window1 =
3209   GBin.scrolled_window ~border_width:10
3210    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
3211  let proofw =
3212   GMathView.math_view ~width:400 ~height:275
3213    ~packing:(scrolled_window1#add) () in
3214 object(self)
3215  method proofw = (assert false : GMathView.math_view)
3216  method content = vbox1
3217  method compute = (assert false : unit)
3218 end
3219 ;;
3220
3221 let empty_page = new empty_page;;
3222
3223 class notebook =
3224 object(self)
3225  val notebook = GPack.notebook ()
3226  val pages = ref []
3227  val mutable skip_switch_page_event = false 
3228  val mutable empty = true
3229  method notebook = notebook
3230  method add_page n =
3231   let new_page = new page () in
3232    empty <- false ;
3233    pages := !pages @ [n,lazy (setgoal n),new_page] ;
3234    notebook#append_page
3235     ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
3236     new_page#content#coerce
3237  method remove_all_pages ~skip_switch_page_event:skip =
3238   if empty then
3239    notebook#remove_page 0 (* let's remove the empty page *)
3240   else
3241    List.iter (function _ -> notebook#remove_page 0) !pages ;
3242   pages := [] ;
3243   skip_switch_page_event <- skip
3244  method set_current_page ~may_skip_switch_page_event n =
3245   let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
3246    let new_page = notebook#page_num page#content#coerce in
3247     if may_skip_switch_page_event && new_page <> notebook#current_page then
3248      skip_switch_page_event <- true ;
3249     notebook#goto_page new_page
3250  method set_empty_page =
3251   empty <- true ;
3252   pages := [] ;
3253   notebook#append_page
3254    ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
3255    empty_page#content#coerce
3256  method proofw =
3257   let (_,_,page) = List.nth !pages notebook#current_page in
3258    page#proofw
3259  initializer
3260   ignore
3261    (notebook#connect#switch_page
3262     (function i ->
3263       let skip = skip_switch_page_event in
3264        skip_switch_page_event <- false ;
3265        if not skip then
3266         try
3267          let (metano,setgoal,page) = List.nth !pages i in
3268           ProofEngine.goal := Some metano ;
3269           Lazy.force (page#compute) ;
3270           Lazy.force setgoal
3271         with _ -> ()
3272     ))
3273 end
3274 ;;
3275
3276 (* Main window *)
3277
3278 class rendering_window output (notebook : notebook) =
3279  let scratch_window = new scratch_window in
3280  let window =
3281   GWindow.window ~title:"MathML viewer" ~border_width:0
3282    ~allow_shrink:false () in
3283  let vbox_for_menu = GPack.vbox ~packing:window#add () in
3284  (* menus *)
3285  let handle_box = GBin.handle_box ~border_width:2
3286   ~packing:(vbox_for_menu#pack ~padding:0) () in
3287  let menubar = GMenu.menu_bar ~packing:handle_box#add () in
3288  let factory0 = new GMenu.factory menubar in
3289  let accel_group = factory0#accel_group in
3290  (* file menu *)
3291  let file_menu = factory0#add_submenu "File" in
3292  let factory1 = new GMenu.factory file_menu ~accel_group in
3293  let export_to_postscript_menu_item =
3294   begin
3295    let _ =
3296     factory1#add_item "New Block of (Co)Inductive Definitions..."
3297      ~key:GdkKeysyms._B ~callback:new_inductive
3298    in
3299    let _ =
3300     factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
3301      ~callback:new_proof
3302    in
3303    let reopen_menu_item =
3304     factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
3305      ~callback:open_
3306    in
3307    let qed_menu_item =
3308     factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
3309    ignore (factory1#add_separator ()) ;
3310    ignore
3311     (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
3312       ~callback:load) ;
3313    let save_menu_item =
3314     factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S ~callback:save
3315    in
3316    ignore
3317     (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
3318    ignore (!save_set_sensitive false);
3319    ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
3320    ignore (!qed_set_sensitive false);
3321    ignore (factory1#add_separator ()) ;
3322    let export_to_postscript_menu_item =
3323     factory1#add_item "Export to PostScript..."
3324      ~callback:(export_to_postscript output) in
3325    ignore (factory1#add_separator ()) ;
3326    ignore
3327     (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) ;
3328    export_to_postscript_menu_item
3329   end in
3330  (* edit menu *)
3331  let edit_menu = factory0#add_submenu "Edit Current Proof" in
3332  let factory2 = new GMenu.factory edit_menu ~accel_group in
3333  let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
3334  let proveit_menu_item =
3335   factory2#add_item "Prove It" ~key:GdkKeysyms._I
3336    ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
3337  in
3338  let focus_menu_item =
3339   factory2#add_item "Focus" ~key:GdkKeysyms._F
3340    ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
3341  in
3342  let _ =
3343   focus_and_proveit_set_sensitive :=
3344    function b ->
3345     proveit_menu_item#misc#set_sensitive b ;
3346     focus_menu_item#misc#set_sensitive b
3347  in
3348  let _ = !focus_and_proveit_set_sensitive false in
3349  (* edit term menu *)
3350  let edit_term_menu = factory0#add_submenu "Edit Term" in
3351  let factory5 = new GMenu.factory edit_term_menu ~accel_group in
3352  let check_menu_item =
3353   factory5#add_item "Check Term" ~key:GdkKeysyms._C
3354    ~callback:(check scratch_window) in
3355  let _ = check_menu_item#misc#set_sensitive false in
3356  (* search menu *)
3357  let settings_menu = factory0#add_submenu "Search" in
3358  let factory4 = new GMenu.factory settings_menu ~accel_group in
3359  let _ =
3360   factory4#add_item "Locate..." ~key:GdkKeysyms._T
3361    ~callback:locate in
3362  let searchPattern_menu_item =
3363   factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
3364    ~callback:completeSearchPattern in
3365  let _ = searchPattern_menu_item#misc#set_sensitive false in
3366  let show_menu_item =
3367   factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
3368  in
3369  (* settings menu *)
3370  let settings_menu = factory0#add_submenu "Settings" in
3371  let factory3 = new GMenu.factory settings_menu ~accel_group in
3372  let _ =
3373   factory3#add_item "Edit Aliases" ~key:GdkKeysyms._A
3374    ~callback:edit_aliases in
3375  let _ = factory3#add_separator () in
3376  let _ =
3377   factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
3378    ~callback:(function _ -> (settings_window ())#show ()) in
3379  (* accel group *)
3380  let _ = window#add_accel_group accel_group in
3381  (* end of menus *)
3382  let hbox0 =
3383   GPack.hbox
3384    ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
3385  let vbox =
3386   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
3387  let scrolled_window0 =
3388   GBin.scrolled_window ~border_width:10
3389    ~packing:(vbox#pack ~expand:true ~padding:5) () in
3390  let _ = scrolled_window0#add output#coerce in
3391  let frame =
3392   GBin.frame ~label:"Insert Term"
3393    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
3394  let scrolled_window1 =
3395   GBin.scrolled_window ~border_width:5
3396    ~packing:frame#add () in
3397  let inputt =
3398   new term_editor ~width:400 ~height:100 ~packing:scrolled_window1#add ()
3399    ~isnotempty_callback:
3400     (function b ->
3401       check_menu_item#misc#set_sensitive b ;
3402       searchPattern_menu_item#misc#set_sensitive b) in
3403  let vboxl =
3404   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
3405  let _ =
3406   vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
3407  let frame =
3408   GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
3409  in
3410  let outputhtml =
3411   GHtml.xmhtml
3412    ~source:"<html><body bgColor=\"white\"></body></html>"
3413    ~width:400 ~height: 100
3414    ~border_width:20
3415    ~packing:frame#add
3416    ~show:true () in
3417 object
3418  method outputhtml = outputhtml
3419  method inputt = inputt
3420  method output = (output : GMathView.math_view)
3421  method notebook = notebook
3422  method show = window#show
3423  initializer
3424   notebook#set_empty_page ;
3425   export_to_postscript_menu_item#misc#set_sensitive false ;
3426   check_term := (check_term_in_scratch scratch_window) ;
3427
3428   (* signal handlers here *)
3429   ignore(output#connect#selection_changed
3430    (function elem ->
3431      choose_selection output elem ;
3432      !focus_and_proveit_set_sensitive true
3433    )) ;
3434   ignore (output#connect#clicked (show_in_show_window_callback output)) ;
3435   let settings_window = new settings_window output scrolled_window0
3436    export_to_postscript_menu_item (choose_selection output) in
3437   set_settings_window settings_window ;
3438   set_outputhtml outputhtml ;
3439   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
3440   Logger.log_callback :=
3441    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
3442 end;;
3443
3444 (* MAIN *)
3445
3446 let initialize_everything () =
3447  let module U = Unix in
3448   let output = GMathView.math_view ~width:350 ~height:280 () in
3449   let notebook = new notebook in
3450    let rendering_window' = new rendering_window output notebook in
3451     set_rendering_window rendering_window' ;
3452     mml_of_cic_term_ref := mml_of_cic_term ;
3453     rendering_window'#show () ;
3454     GMain.Main.main ()
3455 ;;
3456
3457 let _ =
3458  if !usedb then
3459   begin
3460    Mqint.set_database Mqint.postgres_db ;
3461    Mqint.init postgresqlconnectionstring ;
3462   end ;
3463  ignore (GtkMain.Main.init ()) ;
3464  initialize_everything () ;
3465  if !usedb then Mqint.close ();
3466 ;;