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