]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/gTopLevel/gTopLevel.ml
1. helmns and domImpl moved to the misc module ;-(
[helm.git] / helm / gTopLevel / gTopLevel.ml
index c4e070193efad73897ef21debc0548621bddc4b6..4bef88816c302adba3a353cdaf3f1274f0f30e15 100644 (file)
 (******************************************************************************)
 
 
-(* CSC: quick fix: a function from [uri#xpointer(path)] to [uri#path] *)
-let wrong_xpointer_format_from_wrong_xpointer_format' uri =
- try
-  let index_sharp =  String.index uri '#' in
-  let index_rest = index_sharp + 10 in
-   let baseuri = String.sub uri 0 index_sharp in
-   let rest = String.sub uri index_rest (String.length uri - index_rest - 1) in
-    baseuri ^ "#" ^ rest
- with Not_found -> uri
-;;
-
 (* GLOBAL CONSTANTS *)
 
-let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
+let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
 
 let htmlheader =
  "<html>" ^
@@ -59,25 +48,42 @@ let htmlfooter =
  "</html>"
 ;;
 
-(*
-let prooffile = "/home/tassi/miohelm/tmp/currentproof";;
-let prooffile = "/public/sacerdot/currentproof";;
-*)
+let prooffile =
+ try
+  Sys.getenv "GTOPLEVEL_PROOFFILE"
+ with
+  Not_found -> "/public/currentproof"
+;;
 
-let prooffile = "/public/sacerdot/currentproof";;
-let prooffiletype = "/public/sacerdot/currentprooftype";;
+let prooffiletype =
+ try
+  Sys.getenv "GTOPLEVEL_PROOFFILETYPE"
+ with
+  Not_found -> "/public/currentprooftype"
+;;
 
 (*CSC: the getter should handle the innertypes, not the FS *)
-(*
-let innertypesfile = "/home/tassi/miohelm/tmp/innertypes";;
-let innertypesfile = "/public/sacerdot/innertypes";;
-*)
 
-let innertypesfile = "/public/sacerdot/innertypes";;
-let constanttypefile = "/public/sacerdot/constanttype";;
+let innertypesfile =
+ try
+  Sys.getenv "GTOPLEVEL_INNERTYPESFILE"
+ with
+  Not_found -> "/public/innertypes"
+;;
 
-let empty_id_to_uris = ([],function _ -> None);;
+let constanttypefile =
+ try
+  Sys.getenv "GTOPLEVEL_CONSTANTTYPEFILE"
+ with
+  Not_found -> "/public/constanttype"
+;;
 
+let postgresqlconnectionstring =
+ try
+  Sys.getenv "POSTGRESQL_CONNECTION_STRING"
+ with
+  Not_found -> "host=mowgli.cs.unibo.it dbname=helm_mowgli_new_schema user=helm"
+;;
 
 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
 
@@ -87,9 +93,8 @@ let current_cic_infos = ref None;;
 let current_goal_infos = ref None;;
 let current_scratch_infos = ref None;;
 
-let id_to_uris = ref empty_id_to_uris;;
-
 let check_term = ref (fun _ _ _ -> assert false);;
+let mml_of_cic_term_ref = ref (fun _ _ -> assert false);;
 
 exception RenderingWindowsNotInitialized;;
 
@@ -115,6 +120,28 @@ let set_settings_window,settings_window =
   )
 ;;
 
+exception OutputHtmlNotInitialized;;
+
+let set_outputhtml,outputhtml =
+ let outputhtml_ref = ref None in
+  (function rw -> outputhtml_ref := Some rw),
+  (function () ->
+    match !outputhtml_ref with
+       None -> raise OutputHtmlNotInitialized
+     | Some outputhtml -> outputhtml
+  )
+;;
+
+exception QedSetSensitiveNotInitialized;;
+let qed_set_sensitive =
+ ref (function _ -> raise QedSetSensitiveNotInitialized)
+;;
+
+exception SaveSetSensitiveNotInitialized;;
+let save_set_sensitive =
+ ref (function _ -> raise SaveSetSensitiveNotInitialized)
+;;
+
 (* COMMAND LINE OPTIONS *)
 
 let usedb = ref true
@@ -126,31 +153,8 @@ let argspec =
 in
 Arg.parse argspec ignore ""
 
-
 (* MISC FUNCTIONS *)
 
-let cic_textual_parser_uri_of_string uri' =
- (* Constant *)
- if String.sub uri' (String.length uri' - 4) 4 = ".con" then
-  CicTextualParser0.ConUri (UriManager.uri_of_string uri')
- else
-  if String.sub uri' (String.length uri' - 4) 4 = ".var" then
-   CicTextualParser0.VarUri (UriManager.uri_of_string uri')
-  else
-   (try
-     (* Inductive Type *)
-     let uri'',typeno = CicTextualLexer.indtyuri_of_uri uri' in
-      CicTextualParser0.IndTyUri (uri'',typeno)
-    with
-     _ ->
-      (* Constructor of an Inductive Type *)
-      let uri'',typeno,consno =
-       CicTextualLexer.indconuri_of_uri uri'
-      in
-       CicTextualParser0.IndConUri (uri'',typeno,consno)
-   )
-;;
-
 let term_of_cic_textual_parser_uri uri =
  let module C = Cic in
  let module CTP = CicTextualParser0 in
@@ -178,52 +182,226 @@ let string_of_cic_textual_parser_uri uri =
    String.sub uri' 4 (String.length uri' - 4)
 ;;
 
+let output_html outputhtml msg =
+ htmlheader_and_content := !htmlheader_and_content ^ msg ;
+ outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
+ outputhtml#set_topline (-1)
+;;
+
 (* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
 
+(* Check window *)
+
+let check_window outputhtml uris =
+ let window =
+  GWindow.window
+   ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
+ let notebook =
+  GPack.notebook ~scrollable:true ~packing:window#add () in
+ window#show () ;
+ let render_terms =
+  List.map
+   (function uri ->
+     let scrolled_window =
+      GBin.scrolled_window ~border_width:10
+       ~packing:
+         (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
+       ()
+     in
+      lazy 
+       (let mmlwidget =
+         GMathViewAux.single_selection_math_view
+          ~packing:scrolled_window#add ~width:400 ~height:280 () in
+        let expr =
+         let term =
+          term_of_cic_textual_parser_uri
+           (Misc.cic_textual_parser_uri_of_string uri)
+         in
+          (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
+        in
+         try
+          let mml = !mml_of_cic_term_ref 111 expr in
+           mmlwidget#load_doc ~dom:mml
+         with
+          e ->
+           output_html outputhtml
+            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+       )
+   ) uris
+ in
+  ignore
+   (notebook#connect#switch_page
+     (function i -> Lazy.force (List.nth render_terms i)))
+;;
+
 exception NoChoice;;
 
-let interactive_user_uri_choice ?(cancel="Cancel") ~title ~msg uris =
- let choice = ref None in
- let window = GWindow.dialog ~modal:true ~title () in
+let
+ interactive_user_uri_choice ~(selection_mode:[`SINGLE|`EXTENDED]) ?(ok="Ok")
+  ?(enable_button_for_non_vars=false) ~title ~msg uris
+=
+ let choices = ref [] in
+ let chosen = ref false in
+ let use_only_constants = ref false in
+ let window =
+  GWindow.dialog ~modal:true ~title ~width:600 () in
  let lMessage =
-  GMisc.label ~text:msg ~packing:window#vbox#add () in
- let vbox = GPack.vbox ~border_width:10
-  ~packing:(window#action_area#pack ~expand:true ~padding:4) () in
- let hbox1 = GPack.hbox ~border_width:10 ~packing:vbox#add () in
- let combo =
-  GEdit.combo ~popdown_strings:uris ~packing:hbox1#add () in
- let checkb =
-  GButton.button ~label:"Check"
-   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let hbox = GPack.hbox ~border_width:10 ~packing:vbox#add () in
+  GMisc.label ~text:msg
+   ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10
+   ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let clist =
+  let expected_height = 18 * List.length uris in
+   let height = if expected_height > 400 then 400 else expected_height in
+    GList.clist ~columns:1 ~packing:scrolled_window#add
+     ~height ~selection_mode:(selection_mode :> Gtk.Tags.selection_mode) () in
+ let _ = List.map (function x -> clist#append [x]) uris in
+ let hbox2 =
+  GPack.hbox ~border_width:0
+   ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let explain_label =
+  GMisc.label ~text:"None of the above. Try this one:"
+   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
+ let manual_input =
+  GEdit.entry ~editable:true
+   ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
+ let hbox =
+  GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
  let okb =
-  GButton.button ~label:"Ok"
+  GButton.button ~label:ok
    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = okb#misc#set_sensitive false in
+ let nonvarsb =
+  GButton.button
+   ~packing:
+    (function w ->
+      if enable_button_for_non_vars then
+       hbox#pack ~expand:false ~fill:false ~padding:5 w)
+   ~label:"Try constants only" () in
+ let checkb =
+  GButton.button ~label:"Check"
+   ~packing:(hbox#pack ~padding:5) () in
+ let _ = checkb#misc#set_sensitive false in
  let cancelb =
-  GButton.button ~label:cancel
+  GButton.button ~label:"Abort"
    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
  (* actions *)
- let ok_callback () =
-  choice := Some combo#entry#text ;
-  window#destroy ()
- in
  let check_callback () =
-   !check_term [] []
-    (term_of_cic_textual_parser_uri
-     (cic_textual_parser_uri_of_string combo#entry#text))
+  assert (List.length !choices > 0) ;
+  check_window (outputhtml ()) !choices
  in
   ignore (window#connect#destroy GMain.Main.quit) ;
   ignore (cancelb#connect#clicked window#destroy) ;
-  ignore (okb#connect#clicked ok_callback) ;
+  ignore
+   (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
+  ignore
+   (nonvarsb#connect#clicked
+     (function () ->
+       use_only_constants := true ;
+       chosen := true ;
+       window#destroy ()
+   )) ;
   ignore (checkb#connect#clicked check_callback) ;
+  ignore
+   (clist#connect#select_row
+     (fun ~row ~column ~event ->
+       checkb#misc#set_sensitive true ;
+       okb#misc#set_sensitive true ;
+       choices := (List.nth uris row)::!choices)) ;
+  ignore
+   (clist#connect#unselect_row
+     (fun ~row ~column ~event ->
+       choices :=
+        List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
+  ignore
+   (manual_input#connect#changed
+     (fun _ ->
+       if manual_input#text = "" then
+        begin
+         choices := [] ;
+         checkb#misc#set_sensitive false ;
+         okb#misc#set_sensitive false ;
+         clist#misc#set_sensitive true
+        end
+       else
+        begin
+         choices := [manual_input#text] ;
+         clist#unselect_all () ;
+         checkb#misc#set_sensitive true ;
+         okb#misc#set_sensitive true ;
+         clist#misc#set_sensitive false
+        end));
   window#set_position `CENTER ;
   window#show () ;
   GMain.Main.main () ;
-  match !choice with
-     None -> raise NoChoice
-   | Some uri -> uri
+  if !chosen then
+   if !use_only_constants then
+    List.filter
+     (function uri -> not (String.sub uri (String.length uri - 4) 4 = ".var"))
+     uris
+   else
+    if List.length !choices > 0 then !choices else raise NoChoice
+  else
+   raise NoChoice
+;;
+
+let interactive_interpretation_choice interpretations =
+ let chosen = ref None in
+ let window =
+  GWindow.window
+   ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let lMessage =
+  GMisc.label
+   ~text:
+    ("Ambiguous input since there are many well-typed interpretations." ^
+     " Please, choose one of them.")
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let notebook =
+  GPack.notebook ~scrollable:true
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let _ =
+  List.map
+   (function interpretation ->
+     let clist =
+      let expected_height = 18 * List.length interpretation in
+       let height = if expected_height > 400 then 400 else expected_height in
+        GList.clist ~columns:2 ~packing:notebook#append_page ~height
+         ~titles:["id" ; "URI"] ()
+     in
+      ignore
+       (List.map
+         (function (id,uri) ->
+           let n = clist#append [id;uri] in
+            clist#set_row ~selectable:false n
+         ) interpretation
+       ) ;
+      clist#columns_autosize ()
+   ) interpretations in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let cancelb =
+  GButton.button ~label:"Abort"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ (* actions *)
+ ignore (window#connect#destroy GMain.Main.quit) ;
+ ignore (cancelb#connect#clicked window#destroy) ;
+ ignore
+  (okb#connect#clicked
+    (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
+ window#set_position `CENTER ;
+ window#show () ;
+ GMain.Main.main () ;
+ match !chosen with
+    None -> raise NoChoice
+  | Some n -> n
 ;;
 
+
 (* MISC FUNCTIONS *)
 
 (* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
@@ -234,270 +412,95 @@ let get_last_query =
   function result -> !query ^ " <h1>Result:</h1> " ^ MQueryUtil.text_of_result result "<br>"
 ;;
 
-let register_alias (id,uri) =
- let dom,resolve_id = !id_to_uris in
-  id_to_uris :=
-   (if List.mem id dom then dom else id::dom),
-    function id' -> if id' = id then Some uri else resolve_id id'
-;;  
-
-let output_html outputhtml msg =
- htmlheader_and_content := !htmlheader_and_content ^ msg ;
- outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
- outputhtml#set_topline (-1)
-;;
-
-let locate_one_id id =
- let result = MQueryGenerator.locate id in
- let uris =
-  List.map
-   (function uri,_ ->
-     wrong_xpointer_format_from_wrong_xpointer_format' uri
-   ) result in
- let html= " <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>" in
-  output_html (rendering_window ())#outputhtml html ;
-  let uris' =
-   match uris with
-      [] ->
-       (match
-         (GToolbox.input_string ~title:"Unknown input"
-          ("No URI matching \"" ^ id ^ "\" found. Please enter its URI"))
-        with
-           None -> raise NoChoice
-         | Some uri -> ["cic:" ^ uri]
-       )
-    | [uri] -> [uri]
-    | _ ->
-      try
-       [interactive_user_uri_choice
-         ~cancel:"Try every possibility."
-         ~title:"Ambiguous input."
-         ~msg:
-           ("Ambiguous input \"" ^ id ^
-            "\". Please, choose one interpretation:")
-         uris
-       ]
-      with
-       NoChoice -> uris
-  in
-   List.map cic_textual_parser_uri_of_string uris'
-;;
-
-exception ThereDoesNotExistAnyWellTypedInterpretationOfTheInput;;
-exception AmbiguousInput;;
-
-let disambiguate_input context metasenv dom mk_metasenv_and_expr =
- let known_ids,resolve_id = !id_to_uris in
- let dom' =
-  let rec filter =
-   function
-      [] -> []
-    | he::tl ->
-       if List.mem he known_ids then filter tl else he::(filter tl)
-  in
-   filter dom
- in
-  (* for each id in dom' we get the list of uris associated to it *)
-  let list_of_uris = List.map locate_one_id dom' in
-  (* and now we compute the list of all possible assignments from id to uris *)
-  let resolve_ids =
-   let rec aux ids list_of_uris =
-    match ids,list_of_uris with
-       [],[] -> [resolve_id]
-     | id::idtl,uris::uristl ->
-        let resolves = aux idtl uristl in
-         List.concat
-          (List.map
-            (function uri ->
-              List.map
-               (function f ->
-                 function id' -> if id = id' then Some uri else f id'
-               ) resolves
-            ) uris
-          )
-     | _,_ -> assert false
-   in
-    aux dom' list_of_uris
-  in
-prerr_endline ("##### NE DISAMBIGUO: " ^ string_of_int (List.length resolve_ids)) ;
-   (* now we select only the ones that generates well-typed terms *)
-   let resolve_ids' =
-    let rec filter =
-     function
-        [] -> []
-      | resolve::tl ->
-         let metasenv',expr = mk_metasenv_and_expr resolve in
-          try
-(*CSC: Bug here: we do not try to typecheck also the metasenv' *)
-           ignore
-            (CicTypeChecker.type_of_aux' metasenv context expr) ;
-           resolve::(filter tl)
-          with
-           _ -> filter tl
-    in
-     filter resolve_ids
-   in
-    let resolve_id' =
-     match resolve_ids' with
-        [] -> raise ThereDoesNotExistAnyWellTypedInterpretationOfTheInput
-      | [resolve_id] -> resolve_id
-      | _ ->
-        let choices =
-         List.map
-          (function resolve ->
-            String.concat " ; "
-             (List.map
-              (function id ->
-                id ^ " := " ^
-                 match resolve id with
-                    None -> assert false
-                  | Some uri ->
-                     match uri with
-                        CicTextualParser0.ConUri uri
-                      | CicTextualParser0.VarUri uri ->
-                         UriManager.string_of_uri uri
-                      | CicTextualParser0.IndTyUri (uri,tyno) ->
-                         UriManager.string_of_uri uri ^ "#xpointer(1/" ^
-                          string_of_int (tyno+1) ^ ")"
-                      | CicTextualParser0.IndConUri (uri,tyno,consno) ->
-                         UriManager.string_of_uri uri ^ "#xpointer(1/" ^
-                          string_of_int (tyno+1) ^ "/" ^ string_of_int consno ^                           ")"
-              ) dom
-             )
-          ) resolve_ids'
-        in
-        let choice =
-         GToolbox.question_box ~title:"Ambiguous input."
-          ~buttons:choices
-          ~default:1 "Ambiguous input. Please, choose one interpretation."
-        in
-         if choice > 0 then
-          List.nth resolve_ids' (choice - 1)
-         else
-          (* No choice from the user *)
-          raise NoChoice
-    in
-     id_to_uris := known_ids @ dom', resolve_id' ;
-     mk_metasenv_and_expr resolve_id'
-;;
-
-let domImpl = Gdome.domImplementation ();;
-
-let parseStyle name =
- let style =
-  domImpl#createDocumentFromURI
-(*
-   ~uri:("http://phd.cs.unibo.it:8081/getxslt?uri=" ^ name) ?mode:None
-*)
-   ~uri:("styles/" ^ name) ()
- in
-  Gdome_xslt.processStylesheet style
-;;
-
-let d_c = parseStyle "drop_coercions.xsl";;
-let tc1 = parseStyle "objtheorycontent.xsl";;
-let hc2 = parseStyle "content_to_html.xsl";;
-let l   = parseStyle "link.xsl";;
-
-let c1 = parseStyle "rootcontent.xsl";;
-let g  = parseStyle "genmmlid.xsl";;
-let c2 = parseStyle "annotatedpres.xsl";;
-
-
-let getterURL = Configuration.getter_url;;
-let processorURL = Configuration.processor_url;;
-
-let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
-let mml_args =
- ["processorURL", "'" ^ processorURL ^ "'" ;
-  "getterURL", "'" ^ getterURL ^ "'" ;
-  "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
-  "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
-  "UNICODEvsSYMBOL", "'symbol'" ;
-  "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
-  "encoding", "'iso-8859-1'" ;
-  "media-type", "'text/html'" ;
-  "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
-  "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
-  "naturalLanguage", "'yes'" ;
-  "annotations", "'no'" ;
-  "explodeall", "'true()'" ;
-  "topurl", "'http://phd.cs.unibo.it/helm'" ;
-  "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
-;;
-
-let sequent_styles = [d_c ; c1 ; g ; c2 ; l];;
-let sequent_args =
- ["processorURL", "'" ^ processorURL ^ "'" ;
-  "getterURL", "'" ^ getterURL ^ "'" ;
-  "draw_graphURL", "'http%3A//phd.cs.unibo.it%3A8083/'" ;
-  "uri_set_queueURL", "'http%3A//phd.cs.unibo.it%3A8084/'" ;
-  "UNICODEvsSYMBOL", "'symbol'" ;
-  "doctype-public", "'-//W3C//DTD%20XHTML%201.0%20Transitional//EN'" ;
-  "encoding", "'iso-8859-1'" ;
-  "media-type", "'text/html'" ;
-  "keys", "'d_c%2CC1%2CG%2CC2%2CL'" ;
-  "interfaceURL", "'http%3A//phd.cs.unibo.it/helm/html/cic/index.html'" ;
-  "naturalLanguage", "'no'" ;
-  "annotations", "'no'" ;
-  "explodeall", "'true()'" ;
-  "topurl", "'http://phd.cs.unibo.it/helm'" ;
-  "CICURI", "'cic:/Coq/Init/Datatypes/bool_ind.con'" ]
-;;
-
-let parse_file filename =
- let inch = open_in filename in
-  let rec read_lines () =
-   try
-    let line = input_line inch in
-     line ^ read_lines ()
-   with
-    End_of_file -> ""
-  in
-   read_lines ()
-;;
-
-let applyStylesheets input styles args =
- List.fold_left (fun i style -> Gdome_xslt.applyStylesheet i style args)
-  input styles
-;;
-
-let mml_of_cic_object uri annobj ids_to_inner_sorts ids_to_inner_types =
+let
+ mml_of_cic_object ~explode_all uri annobj ids_to_inner_sorts ids_to_inner_types
+=
 (*CSC: ????????????????? *)
  let xml, bodyxml =
-  Cic2Xml.print_object uri ~ids_to_inner_sorts annobj 
+  Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:true
+   annobj 
  in
  let xmlinnertypes =
-  Cic2Xml.print_inner_types uri ~ids_to_inner_sorts
-   ~ids_to_inner_types
+  Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
+   ~ask_dtd_to_the_getter:true
  in
   let input =
    match bodyxml with
-      None -> Xml2Gdome.document_of_xml domImpl xml
+      None -> Xml2Gdome.document_of_xml Misc.domImpl xml
     | Some bodyxml' ->
        Xml.pp xml (Some constanttypefile) ;
-       Xml2Gdome.document_of_xml domImpl bodyxml'
+       Xml2Gdome.document_of_xml Misc.domImpl bodyxml'
   in
 (*CSC: We save the innertypes to disk so that we can retrieve them in the  *)
 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
 (*CSC: local.                                                              *)
    Xml.pp xmlinnertypes (Some innertypesfile) ;
-   let output = applyStylesheets input mml_styles mml_args in
+   let output = ApplyStylesheets.apply_proof_stylesheets input ~explode_all in
     output
 ;;
 
+let
+ save_object_to_disk uri annobj ids_to_inner_sorts ids_to_inner_types pathname
+=
+ let name =
+  let struri = UriManager.string_of_uri uri in
+  let idx = (String.rindex struri '/') + 1 in
+   String.sub struri idx (String.length struri - idx)
+ in
+  let path = pathname ^ "/" ^ name in
+  let xml, bodyxml =
+   Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
+    annobj 
+  in
+  let xmlinnertypes =
+   Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
+    ~ask_dtd_to_the_getter:false
+  in
+   (* innertypes *)
+   let innertypesuri = UriManager.innertypesuri_of_uri uri in
+    Xml.pp ~quiet:true xmlinnertypes (Some (path ^ ".types.xml")) ;
+    Getter.register innertypesuri
+     (Configuration.annotations_url ^
+       Str.replace_first (Str.regexp "^cic:") ""
+        (UriManager.string_of_uri innertypesuri) ^ ".xml"
+     ) ;
+    (* constant type / variable / mutual inductive types definition *)
+    Xml.pp ~quiet:true xml (Some (path ^ ".xml")) ;
+    Getter.register uri
+     (Configuration.annotations_url ^
+       Str.replace_first (Str.regexp "^cic:") ""
+        (UriManager.string_of_uri uri) ^ ".xml"
+     ) ;
+    match bodyxml with
+       None -> ()
+     | Some bodyxml' ->
+        (* constant body *)
+        let bodyuri =
+         match UriManager.bodyuri_of_uri uri with
+            None -> assert false
+          | Some bodyuri -> bodyuri
+        in
+         Xml.pp ~quiet:true bodyxml' (Some (path ^ ".body.xml")) ;
+         Getter.register bodyuri
+          (Configuration.annotations_url ^
+            Str.replace_first (Str.regexp "^cic:") ""
+             (UriManager.string_of_uri bodyuri) ^ ".xml"
+          )
+;;
+
 
 (* CALLBACKS *)
 
 exception RefreshSequentException of exn;;
 exception RefreshProofException of exn;;
 
-let refresh_proof (output : GMathView.math_view) =
+let refresh_proof (output : GMathViewAux.single_selection_math_view) =
  try
   let uri,currentproof =
    match !ProofEngine.proof with
       None -> assert false
     | Some (uri,metasenv,bo,ty) ->
+       !qed_set_sensitive (List.length metasenv = 0) ;
        (*CSC: Wrong: [] is just plainly wrong *)
        uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
   in
@@ -508,9 +511,10 @@ let refresh_proof (output : GMathView.math_view) =
     Cic2acic.acic_object_of_cic_object currentproof
    in
     let mml =
-     mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types
+     mml_of_cic_object ~explode_all:true uri acic ids_to_inner_sorts
+      ids_to_inner_types
     in
-     output#load_tree mml ;
+     output#load_doc ~dom:mml ;
      current_cic_infos :=
       Some (ids_to_terms,ids_to_father_ids,ids_to_conjectures,ids_to_hypotheses)
  with
@@ -528,7 +532,7 @@ let refresh_sequent ?(empty_notebook=true) notebook =
      None ->
       if empty_notebook then
        begin 
-        notebook#remove_all_pages ;
+        notebook#remove_all_pages ~skip_switch_page_event:false ;
         notebook#set_empty_page
        end
       else
@@ -543,19 +547,30 @@ let refresh_sequent ?(empty_notebook=true) notebook =
        let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
         SequentPp.XmlPp.print_sequent metasenv currentsequent
        in
-        let sequent_doc =
-         Xml2Gdome.document_of_xml domImpl sequent_gdome
-        in
-         let sequent_mml =
-          applyStylesheets sequent_doc sequent_styles sequent_args
+        let regenerate_notebook () = 
+         let skip_switch_page_event =
+          match metasenv with
+             (m,_,_)::_ when m = metano -> false
+           | _ -> true
          in
+          notebook#remove_all_pages ~skip_switch_page_event ;
+          List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
+        in
           if empty_notebook then
            begin
-            notebook#remove_all_pages ;
-            List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
+            regenerate_notebook () ;
+            notebook#set_current_page ~may_skip_switch_page_event:false metano
+           end
+          else
+           begin
+            let sequent_doc =
+             Xml2Gdome.document_of_xml Misc.domImpl sequent_gdome in
+            let sequent_mml =
+             ApplyStylesheets.apply_sequent_stylesheets sequent_doc
+            in
+             notebook#set_current_page ~may_skip_switch_page_event:true metano;
+             notebook#proofw#load_doc ~dom:sequent_mml
            end ;
-          notebook#set_current_page metano ;
-          notebook#proofw#load_tree ~dom:sequent_mml ;
           current_goal_infos :=
            Some (ids_to_terms,ids_to_father_ids,ids_to_hypotheses)
  with
@@ -570,9 +585,11 @@ let metasenv =
     None -> assert false
   | Some (_,metasenv,_,_) -> metasenv
 in
+try
 let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
 prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
    raise (RefreshSequentException e)
+with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unkown."); raise (RefreshSequentException e)
 ;;
 
 (*
@@ -599,427 +616,40 @@ let mml_of_cic_term metano term =
     SequentPp.XmlPp.print_sequent metasenv (metano,context,term)
    in
     let sequent_doc =
-     Xml2Gdome.document_of_xml domImpl sequent_gdome
+     Xml2Gdome.document_of_xml Misc.domImpl sequent_gdome
     in
-     let res =
-      applyStylesheets sequent_doc sequent_styles sequent_args ;
-     in
+     let res = ApplyStylesheets.apply_sequent_stylesheets sequent_doc in
       current_scratch_infos :=
        Some (term,ids_to_terms,ids_to_father_ids,ids_to_hypotheses) ;
       res
 ;;
 
-(***********************)
-(*       TACTICS       *)
-(***********************)
+exception OpenConjecturesStillThere;;
+exception WrongProof;;
 
-let call_tactic tactic () =
- let notebook = (rendering_window ())#notebook in
- let output = ((rendering_window ())#output : GMathView.math_view) in
- let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let savedproof = !ProofEngine.proof in
- let savedgoal  = !ProofEngine.goal in
-  begin
-   try
-    tactic () ;
-    refresh_sequent notebook ;
-    refresh_proof output
-   with
-      RefreshSequentException e ->
-       output_html outputhtml
-        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-         "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
-       ProofEngine.proof := savedproof ;
-       ProofEngine.goal := savedgoal ;
-       refresh_sequent notebook
-    | RefreshProofException e ->
-       output_html outputhtml
-        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-         "proof: " ^ Printexc.to_string e ^ "</h1>") ;
-       ProofEngine.proof := savedproof ;
-       ProofEngine.goal := savedgoal ;
-       refresh_sequent notebook ;
-       refresh_proof output
-    | e ->
-       output_html outputhtml
-        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-       ProofEngine.proof := savedproof ;
-       ProofEngine.goal := savedgoal ;
-  end
+let pathname_of_annuri uristring =
+ Configuration.annotations_dir ^    
+  Str.replace_first (Str.regexp "^cic:") "" uristring
 ;;
 
-let call_tactic_with_input tactic () =
- let notebook = (rendering_window ())#notebook in
- let output = ((rendering_window ())#output : GMathView.math_view) in
- let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
- let savedproof = !ProofEngine.proof in
- let savedgoal  = !ProofEngine.goal in
-(*CSC: Gran cut&paste da sotto... *)
-  let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen ^ "\n" in
-   let lexbuf = Lexing.from_string input in
-   let curi =
-    match !ProofEngine.proof with
-       None -> assert false
-     | Some (curi,_,_,_) -> curi
-   in
-   let uri,metasenv,bo,ty =
-    match !ProofEngine.proof with
-       None -> assert false
-     | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
-   in
-   let canonical_context =
-    match !ProofEngine.goal with
-       None -> assert false
-     | Some metano ->
-        let (_,canonical_context,_) =
-         List.find (function (m,_,_) -> m=metano) metasenv
-        in
-         canonical_context
-   in
-   let context =
-    List.map
-     (function
-         Some (n,_) -> Some n
-       | None -> None
-     ) canonical_context
-   in
-    try
-     while true do
-      match
-       CicTextualParserContext.main context metasenv CicTextualLexer.token
-        lexbuf register_alias
-      with
-         None -> ()
-       | Some (dom,mk_metasenv_and_expr) ->
-          let (metasenv',expr) =
-           disambiguate_input canonical_context metasenv dom
-            mk_metasenv_and_expr
-          in
-           ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
-           tactic expr ;
-           refresh_sequent notebook ;
-           refresh_proof output
-     done
-    with
-       CicTextualParser0.Eof ->
-        inputt#delete_text 0 inputlen
-     | RefreshSequentException e ->
-        output_html outputhtml
-         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-          "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
-        ProofEngine.proof := savedproof ;
-        ProofEngine.goal := savedgoal ;
-        refresh_sequent notebook
-     | RefreshProofException e ->
-        output_html outputhtml
-         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-          "proof: " ^ Printexc.to_string e ^ "</h1>") ;
-        ProofEngine.proof := savedproof ;
-        ProofEngine.goal := savedgoal ;
-        refresh_sequent notebook ;
-        refresh_proof output
-     | e ->
-        output_html outputhtml
-         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-        ProofEngine.proof := savedproof ;
-        ProofEngine.goal := savedgoal ;
+let make_dirs dirpath =
+ ignore (Unix.system ("mkdir -p " ^ dirpath))
 ;;
 
-let call_tactic_with_goal_input tactic () =
- let module L = LogicalOperations in
- let module G = Gdome in
-  let notebook = (rendering_window ())#notebook in
-  let output = ((rendering_window ())#output : GMathView.math_view) in
-  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  let savedproof = !ProofEngine.proof in
-  let savedgoal  = !ProofEngine.goal in
-   match notebook#proofw#get_selection with
-     Some node ->
-      let xpath =
-       ((node : Gdome.element)#getAttributeNS
-         ~namespaceURI:helmns
-         ~localName:(G.domString "xref"))#to_string
-      in
-       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
-       else
-        begin
-         try
-          match !current_goal_infos with
-             Some (ids_to_terms, ids_to_father_ids,_) ->
-              let id = xpath in
-               tactic (Hashtbl.find ids_to_terms id) ;
-               refresh_sequent notebook ;
-               refresh_proof output
-           | None -> assert false (* "ERROR: No current term!!!" *)
-         with
-            RefreshSequentException e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-             refresh_sequent notebook
-          | RefreshProofException e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-             refresh_sequent notebook ;
-             refresh_proof output
-          | e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-        end
-   | None ->
-      output_html outputhtml
-       ("<h1 color=\"red\">No term selected</h1>")
-;;
-
-let call_tactic_with_input_and_goal_input tactic () =
- let module L = LogicalOperations in
- let module G = Gdome in
-  let notebook = (rendering_window ())#notebook in
-  let output = ((rendering_window ())#output : GMathView.math_view) in
-  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  let inputt = ((rendering_window ())#inputt : GEdit.text) in
-  let savedproof = !ProofEngine.proof in
-  let savedgoal  = !ProofEngine.goal in
-   match notebook#proofw#get_selection with
-     Some node ->
-      let xpath =
-       ((node : Gdome.element)#getAttributeNS
-         ~namespaceURI:helmns
-         ~localName:(G.domString "xref"))#to_string
-      in
-       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
-       else
-        begin
-         try
-          match !current_goal_infos with
-             Some (ids_to_terms, ids_to_father_ids,_) ->
-              let id = xpath in
-               (* Let's parse the input *)
-               let inputlen = inputt#length in
-               let input = inputt#get_chars 0 inputlen ^ "\n" in
-                let lexbuf = Lexing.from_string input in
-                let curi =
-                 match !ProofEngine.proof with
-                    None -> assert false
-                  | Some (curi,_,_,_) -> curi
-                in
-                let uri,metasenv,bo,ty =
-                 match !ProofEngine.proof with
-                    None -> assert false
-                  | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
-                in
-                let canonical_context =
-                 match !ProofEngine.goal with
-                    None -> assert false
-                  | Some metano ->
-                     let (_,canonical_context,_) =
-                      List.find (function (m,_,_) -> m=metano) metasenv
-                     in
-                      canonical_context in
-                let context =
-                 List.map
-                  (function
-                      Some (n,_) -> Some n
-                    | None -> None
-                  ) canonical_context
-                in
-                 begin
-                  try
-                   while true do
-                    match
-                     CicTextualParserContext.main context metasenv
-                      CicTextualLexer.token lexbuf register_alias
-                    with
-                       None -> ()
-                     | Some (dom,mk_metasenv_and_expr) ->
-                        let (metasenv',expr) =
-                         disambiguate_input canonical_context metasenv dom
-                          mk_metasenv_and_expr
-                        in
-                         ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
-                         tactic ~goal_input:(Hashtbl.find ids_to_terms id)
-                          ~input:expr ;
-                         refresh_sequent notebook ;
-                         refresh_proof output
-                   done
-                  with
-                     CicTextualParser0.Eof ->
-                      inputt#delete_text 0 inputlen
-                 end
-           | None -> assert false (* "ERROR: No current term!!!" *)
-         with
-            RefreshSequentException e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-             refresh_sequent notebook
-          | RefreshProofException e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-             refresh_sequent notebook ;
-             refresh_proof output
-          | e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-        end
-   | None ->
-      output_html outputhtml
-       ("<h1 color=\"red\">No term selected</h1>")
-;;
-
-let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
- let module L = LogicalOperations in
- let module G = Gdome in
-  let mmlwidget = (scratch_window#mmlwidget : GMathView.math_view) in
-  let outputhtml = (scratch_window#outputhtml : GHtml.xmhtml) in
-  let savedproof = !ProofEngine.proof in
-  let savedgoal  = !ProofEngine.goal in
-   match mmlwidget#get_selection with
-     Some node ->
-      let xpath =
-       ((node : Gdome.element)#getAttributeNS
-         ~namespaceURI:helmns
-         ~localName:(G.domString "xref"))#to_string
-      in
-       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
-       else
-        begin
-         try
-          match !current_scratch_infos with
-             (* term is the whole goal in the scratch_area *)
-             Some (term,ids_to_terms, ids_to_father_ids,_) ->
-              let id = xpath in
-               let expr = tactic term (Hashtbl.find ids_to_terms id) in
-                let mml = mml_of_cic_term 111 expr in
-                 scratch_window#show () ;
-                 scratch_window#mmlwidget#load_tree ~dom:mml
-           | None -> assert false (* "ERROR: No current term!!!" *)
-         with
-          e ->
-           output_html outputhtml
-            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
-        end
-   | None ->
-      output_html outputhtml
-       ("<h1 color=\"red\">No term selected</h1>")
-;;
-
-let call_tactic_with_hypothesis_input tactic () =
- let module L = LogicalOperations in
- let module G = Gdome in
-  let notebook = (rendering_window ())#notebook in
-  let output = ((rendering_window ())#output : GMathView.math_view) in
-  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  let savedproof = !ProofEngine.proof in
-  let savedgoal  = !ProofEngine.goal in
-   match notebook#proofw#get_selection with
-     Some node ->
-      let xpath =
-       ((node : Gdome.element)#getAttributeNS
-         ~namespaceURI:helmns
-         ~localName:(G.domString "xref"))#to_string
-      in
-       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
-       else
-        begin
-         try
-          match !current_goal_infos with
-             Some (_,_,ids_to_hypotheses) ->
-              let id = xpath in
-               tactic (Hashtbl.find ids_to_hypotheses id) ;
-               refresh_sequent notebook ;
-               refresh_proof output
-           | None -> assert false (* "ERROR: No current term!!!" *)
-         with
-            RefreshSequentException e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-             refresh_sequent notebook
-          | RefreshProofException e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-             refresh_sequent notebook ;
-             refresh_proof output
-          | e ->
-             output_html outputhtml
-              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-             ProofEngine.proof := savedproof ;
-             ProofEngine.goal := savedgoal ;
-        end
-   | None ->
-      output_html outputhtml
-       ("<h1 color=\"red\">No term selected</h1>")
-;;
-
-
-let intros = call_tactic ProofEngine.intros;;
-let exact = call_tactic_with_input ProofEngine.exact;;
-let apply = call_tactic_with_input ProofEngine.apply;;
-let elimsimplintros = call_tactic_with_input ProofEngine.elim_simpl_intros;;
-let elimtype = call_tactic_with_input ProofEngine.elim_type;;
-let whd = call_tactic_with_goal_input ProofEngine.whd;;
-let reduce = call_tactic_with_goal_input ProofEngine.reduce;;
-let simpl = call_tactic_with_goal_input ProofEngine.simpl;;
-let fold = call_tactic_with_input ProofEngine.fold;;
-let cut = call_tactic_with_input ProofEngine.cut;;
-let change = call_tactic_with_input_and_goal_input ProofEngine.change;;
-let letin = call_tactic_with_input ProofEngine.letin;;
-let ring = call_tactic ProofEngine.ring;;
-let clearbody = call_tactic_with_hypothesis_input ProofEngine.clearbody;;
-let clear = call_tactic_with_hypothesis_input ProofEngine.clear;;
-let fourier = call_tactic ProofEngine.fourier;;
-let rewritesimpl = call_tactic_with_input ProofEngine.rewrite_simpl;;
-let reflexivity = call_tactic ProofEngine.reflexivity;;
-let symmetry = call_tactic ProofEngine.symmetry;;
-let transitivity = call_tactic_with_input ProofEngine.transitivity;;
-let left = call_tactic ProofEngine.left;;
-let right = call_tactic ProofEngine.right;;
-let assumption = call_tactic ProofEngine.assumption;;
-
-let whd_in_scratch scratch_window =
- call_tactic_with_goal_input_in_scratch ProofEngine.whd_in_scratch
-  scratch_window
-;;
-let reduce_in_scratch scratch_window =
- call_tactic_with_goal_input_in_scratch ProofEngine.reduce_in_scratch
-  scratch_window
-;;
-let simpl_in_scratch scratch_window =
- call_tactic_with_goal_input_in_scratch ProofEngine.simpl_in_scratch
-  scratch_window
+let save_obj uri obj =
+ let
+  (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
+   ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
+ =
+  Cic2acic.acic_object_of_cic_object obj
+ in
+  (* let's save the theorem and register it to the getter *) 
+  let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
+   make_dirs pathname ;
+   save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
+    pathname
 ;;
 
-
-
-(**********************)
-(*   END OF TACTICS   *)
-(**********************)
-
-exception OpenConjecturesStillThere;;
-exception WrongProof;;
-
 let qed () =
  match !ProofEngine.proof with
     None -> assert false
@@ -1038,9 +668,16 @@ let qed () =
          Cic2acic.acic_object_of_cic_object proof
         in
          let mml =
-          mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types
+          mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
+           ids_to_inner_types
          in
-          ((rendering_window ())#output : GMathView.math_view)#load_tree mml ;
+          ((rendering_window ())#output : GMathViewAux.single_selection_math_view)#load_doc mml ;
+          !qed_set_sensitive false ;
+          (* let's save the theorem and register it to the getter *) 
+          let pathname = pathname_of_annuri (UriManager.buri_of_uri uri) in
+          make_dirs pathname ;
+          save_object_to_disk uri acic ids_to_inner_sorts ids_to_inner_types
+           pathname ;
           current_cic_infos :=
            Some
             (ids_to_terms,ids_to_father_ids,ids_to_conjectures,
@@ -1051,12 +688,6 @@ let qed () =
   | _ -> raise OpenConjecturesStillThere
 ;;
 
-(*????
-let dtdname = "http://www.cs.unibo.it/helm/dtd/cic.dtd";;
-let dtdname = "/home/tassi/miohelm/helm/dtd/cic.dtd";;
-*)
-let dtdname = "/projects/helm/V7_mowgli/dtd/cic.dtd";;
-
 let save () =
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
   match !ProofEngine.proof with
@@ -1070,7 +701,10 @@ let save () =
         Cic2acic.acic_object_of_cic_object currentproof
        in
         let xml, bodyxml =
-         match Cic2Xml.print_object uri ~ids_to_inner_sorts acurrentproof with
+         match
+          Cic2Xml.print_object uri ~ids_to_inner_sorts
+           ~ask_dtd_to_the_getter:true acurrentproof
+         with
             xml,Some bodyxml -> xml,bodyxml
           | _,None -> assert false
         in
@@ -1099,29 +733,36 @@ let typecheck_loaded_proof metasenv bo ty =
 
 let load () =
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let output = ((rendering_window ())#output : GMathView.math_view) in
+ let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
  let notebook = (rendering_window ())#notebook in
   try
-   let uri = UriManager.uri_of_string "cic:/dummy.con" in
-    match CicParser.obj_of_xml prooffiletype (Some prooffile) with
-       Cic.CurrentProof (_,metasenv,bo,ty,_) ->
-        typecheck_loaded_proof metasenv bo ty ;
-        ProofEngine.proof :=
-         Some (uri, metasenv, bo, ty) ;
-        ProofEngine.goal :=
-         (match metasenv with
-             [] -> None
-           | (metano,_,_)::_ -> Some metano
-         ) ;
-        refresh_proof output ;
-        refresh_sequent notebook ;
-         output_html outputhtml
-          ("<h1 color=\"Green\">Current proof type loaded from " ^
-            prooffiletype ^ "</h1>") ;
-         output_html outputhtml
-          ("<h1 color=\"Green\">Current proof body loaded from " ^
-            prooffile ^ "</h1>")
-     | _ -> assert false
+   match 
+    GToolbox.input_string ~title:"Load Unfinished Proof" ~text:"/dummy.con"
+     "Choose an URI:"
+   with
+      None -> raise NoChoice
+    | Some uri0 ->
+       let uri = UriManager.uri_of_string ("cic:" ^ uri0) in
+        match CicParser.obj_of_xml prooffiletype (Some prooffile) with
+           Cic.CurrentProof (_,metasenv,bo,ty,_) ->
+            typecheck_loaded_proof metasenv bo ty ;
+            ProofEngine.proof :=
+             Some (uri, metasenv, bo, ty) ;
+            ProofEngine.goal :=
+             (match metasenv with
+                 [] -> None
+               | (metano,_,_)::_ -> Some metano
+             ) ;
+            refresh_proof output ;
+            refresh_sequent notebook ;
+             output_html outputhtml
+              ("<h1 color=\"Green\">Current proof type loaded from " ^
+                prooffiletype ^ "</h1>") ;
+             output_html outputhtml
+              ("<h1 color=\"Green\">Current proof body loaded from " ^
+                prooffile ^ "</h1>") ;
+            !save_set_sensitive true
+         | _ -> assert false
   with
      RefreshSequentException e ->
       output_html outputhtml
@@ -1137,25 +778,81 @@ let load () =
 ;;
 
 let edit_aliases () =
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let id_to_uris = inputt#id_to_uris in
+ let chosen = ref false in
+ let window =
+  GWindow.window
+   ~width:400 ~modal:true ~title:"Edit Aliases..." ~border_width:2 () in
+ let vbox =
+  GPack.vbox ~border_width:0 ~packing:window#add () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let input = GEdit.text ~editable:true ~width:400 ~height:100
+   ~packing:scrolled_window#add () in
+ let hbox =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let cancelb =
+  GButton.button ~label:"Cancel"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ ignore (window#connect#destroy GMain.Main.quit) ;
+ ignore (cancelb#connect#clicked window#destroy) ;
+ ignore
+  (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
  let dom,resolve_id = !id_to_uris in
-  let inputlen = inputt#length in
-   inputt#delete_text 0 inputlen ;
-   let _ =
-    inputt#insert_text ~pos:0
-     (String.concat "\n"
-       (List.map
-         (function v ->
-           let uri =
-            match resolve_id v with
-               None -> assert false
-             | Some uri -> uri
-           in
-            "alias " ^ v ^ " " ^
-              (string_of_cic_textual_parser_uri uri)
-         ) dom))
+  ignore
+   (input#insert_text ~pos:0
+    (String.concat "\n"
+      (List.map
+        (function v ->
+          let uri =
+           match resolve_id v with
+              None -> assert false
+            | Some uri -> uri
+          in
+           "alias " ^ v ^ " " ^
+             (string_of_cic_textual_parser_uri uri)
+        ) dom))) ;
+  window#show () ;
+  GMain.Main.main () ;
+  if !chosen then
+   let dom,resolve_id =
+    let inputtext = input#get_chars 0 input#length in
+    let regexpr =
+     let alfa = "[a-zA-Z_-]" in
+     let digit = "[0-9]" in
+     let ident = alfa ^ "\(" ^ alfa ^ "\|" ^ digit ^ "\)*" in
+     let blanks = "\( \|\t\|\n\)+" in
+     let nonblanks = "[^ \t\n]+" in
+     let uri = "/\(" ^ ident ^ "/\)*" ^ nonblanks in (* not very strict check *)
+      Str.regexp
+       ("alias" ^ blanks ^ "\(" ^ ident ^ "\)" ^ blanks ^ "\(" ^ uri ^ "\)")
+    in
+     let rec aux n =
+      try
+       let n' = Str.search_forward regexpr inputtext n in
+        let id = Str.matched_group 2 inputtext in
+        let uri =
+         Misc.cic_textual_parser_uri_of_string
+          ("cic:" ^ (Str.matched_group 5 inputtext))
+        in
+         let dom,resolve_id = aux (n' + 1) in
+          if List.mem id dom then
+           dom,resolve_id
+          else
+           id::dom,
+            (function id' -> if id = id' then Some uri else resolve_id id')
+      with
+       Not_found -> TermEditor.empty_id_to_uris
+     in
+      aux 0
    in
-    id_to_uris := empty_id_to_uris
+    id_to_uris := (dom,resolve_id)
 ;;
 
 let proveit () =
@@ -1171,7 +868,7 @@ let proveit () =
       (*CSC: OCAML DIVERGE
       ((element : G.element)#getAttributeNS
       *)
-        ~namespaceURI:helmns
+        ~namespaceURI:Misc.helmns
         ~localName:(G.domString "xref"))#to_string
      in
       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
@@ -1213,7 +910,7 @@ let focus () =
       (*CSC: OCAML DIVERGE
       ((element : G.element)#getAttributeNS
       *)
-        ~namespaceURI:helmns
+        ~namespaceURI:Misc.helmns
         ~localName:(G.domString "xref"))#to_string
      in
       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
@@ -1256,8 +953,7 @@ let setgoal metano =
     | Some (_,metasenv,_,_) -> metasenv
   in
    try
-    ProofEngine.goal := Some metano ;
-    refresh_sequent ~empty_notebook:false notebook ;
+    refresh_sequent ~empty_notebook:false notebook
    with
       RefreshSequentException e ->
        output_html outputhtml
@@ -1268,17 +964,1257 @@ let setgoal metano =
         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
 ;;
 
+let
+ show_in_show_window_obj, show_in_show_window_uri, show_in_show_window_callback
+=
+ let window =
+  GWindow.window ~width:800 ~border_width:2 () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10 ~packing:window#add () in
+ let mmlwidget =
+  GMathViewAux.single_selection_math_view ~packing:scrolled_window#add ~width:600 ~height:400 () in
+ let _ = window#event#connect#delete (fun _ -> window#misc#hide () ; true ) in
+ let href = Gdome.domString "href" in
+  let show_in_show_window_obj uri obj =
+   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+    try
+     let
+      (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,
+       ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses)
+     =
+      Cic2acic.acic_object_of_cic_object obj
+     in
+      let mml =
+       mml_of_cic_object ~explode_all:false uri acic ids_to_inner_sorts
+        ids_to_inner_types
+      in
+       window#set_title (UriManager.string_of_uri uri) ;
+       window#misc#hide () ; window#show () ;
+       mmlwidget#load_doc mml ;
+    with
+     e ->
+      output_html outputhtml
+       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+  in
+  let show_in_show_window_uri uri =
+   let obj = CicEnvironment.get_obj uri in
+    show_in_show_window_obj uri obj
+  in
+   let show_in_show_window_callback mmlwidget (n : Gdome.element) _ =
+    if n#hasAttributeNS ~namespaceURI:xlinkns ~localName:href then
+     let uri =
+      (n#getAttributeNS ~namespaceURI:xlinkns ~localName:href)#to_string
+     in 
+      show_in_show_window_uri (UriManager.uri_of_string uri)
+    else
+     ignore (mmlwidget#action_toggle n)
+   in
+    let _ =
+     mmlwidget#connect#click (show_in_show_window_callback mmlwidget)
+    in
+     show_in_show_window_obj, show_in_show_window_uri,
+      show_in_show_window_callback
+;;
+
+exception NoObjectsLocated;;
+
+let user_uri_choice ~title ~msg uris =
+ let uri =
+  match uris with
+     [] -> raise NoObjectsLocated
+   | [uri] -> uri
+   | uris ->
+      match
+       interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
+      with
+         [uri] -> uri
+       | _ -> assert false
+ in
+  String.sub uri 4 (String.length uri - 4)
+;;
+
+let locate_callback id =
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let result = MQueryGenerator.locate id in
+ let uris =
+  List.map
+   (function uri,_ ->
+     Misc.wrong_xpointer_format_from_wrong_xpointer_format' uri)
+   result in
+ let html =
+  (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>")
+ in
+  output_html outputhtml html ;
+  user_uri_choice ~title:"Ambiguous input."
+   ~msg:
+     ("Ambiguous input \"" ^ id ^
+      "\". Please, choose one interpetation:")
+   uris
+;;
+
+
+let input_or_locate_uri ~title =
+ let uri = ref None in
+ let window =
+  GWindow.window
+   ~width:400 ~modal:true ~title ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let hbox1 =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"Enter a valid URI:" ~packing:(hbox1#pack ~padding:5) () in
+ let manual_input =
+  GEdit.entry ~editable:true
+   ~packing:(hbox1#pack ~expand:true ~fill:true ~padding:5) () in
+ let checkb =
+  GButton.button ~label:"Check"
+   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = checkb#misc#set_sensitive false in
+ let hbox2 =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"You can also enter an indentifier to locate:"
+   ~packing:(hbox2#pack ~padding:5) () in
+ let locate_input =
+  GEdit.entry ~editable:true
+   ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
+ let locateb =
+  GButton.button ~label:"Locate"
+   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = locateb#misc#set_sensitive false in
+ let hbox3 =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = okb#misc#set_sensitive false in
+ let cancelb =
+  GButton.button ~label:"Cancel"
+   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) ()
+ in
+  ignore (window#connect#destroy GMain.Main.quit) ;
+  ignore
+   (cancelb#connect#clicked (function () -> uri := None ; window#destroy ())) ;
+  let check_callback () =
+   let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+   let uri = "cic:" ^ manual_input#text in
+    try
+      ignore (Getter.resolve (UriManager.uri_of_string uri)) ;
+      output_html outputhtml "<h1 color=\"Green\">OK</h1>" ;
+      true
+    with
+       Getter.Unresolved ->
+        output_html outputhtml
+         ("<h1 color=\"Red\">URI " ^ uri ^
+          " does not correspond to any object.</h1>") ;
+        false
+     | UriManager.IllFormedUri _ ->
+        output_html outputhtml
+         ("<h1 color=\"Red\">URI " ^ uri ^ " is not well-formed.</h1>") ;
+        false
+     | e ->
+        output_html outputhtml
+         ("<h1 color=\"Red\">" ^ Printexc.to_string e ^ "</h1>") ;
+        false
+  in
+  ignore
+   (okb#connect#clicked
+     (function () ->
+       if check_callback () then
+        begin
+         uri := Some manual_input#text ;
+         window#destroy ()
+        end
+   )) ;
+  ignore (checkb#connect#clicked (function () -> ignore (check_callback ()))) ;
+  ignore
+   (manual_input#connect#changed
+     (fun _ ->
+       if manual_input#text = "" then
+        begin
+         checkb#misc#set_sensitive false ;
+         okb#misc#set_sensitive false
+        end
+       else
+        begin
+         checkb#misc#set_sensitive true ;
+         okb#misc#set_sensitive true
+        end));
+  ignore
+   (locate_input#connect#changed
+     (fun _ -> locateb#misc#set_sensitive (locate_input#text <> ""))) ;
+  ignore
+   (locateb#connect#clicked
+     (function () ->
+       let id = locate_input#text in
+        manual_input#set_text (locate_callback id) ;
+        locate_input#delete_text 0 (String.length id)
+   )) ;
+  window#show () ;
+  GMain.Main.main () ;
+  match !uri with
+     None -> raise NoChoice
+   | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
+;;
+
+exception AmbiguousInput;;
+
+(* A WIDGET TO ENTER CIC TERMS *)
+
+module Callbacks =
+ struct
+  let output_html msg = output_html (outputhtml ()) msg;;
+  let interactive_user_uri_choice =
+   fun ~selection_mode ?ok ?enable_button_for_non_vars ~title ~msg ~id ->
+    interactive_user_uri_choice ~selection_mode ?ok
+     ?enable_button_for_non_vars ~title ~msg;;
+  let interactive_interpretation_choice = interactive_interpretation_choice;;
+  let input_or_locate_uri = input_or_locate_uri;;
+ end
+;;
+
+module TermEditor' = TermEditor.Make(Callbacks);;
+
+(* OTHER FUNCTIONS *)
+
+let locate () =
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+   try
+    match
+     GToolbox.input_string ~title:"Locate" "Enter an identifier to locate:"
+    with
+       None -> raise NoChoice
+     | Some input ->
+        let uri = locate_callback input in
+         inputt#set_term uri
+   with
+    e ->
+     output_html outputhtml
+      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+;;
+
+
+exception UriAlreadyInUse;;
+exception NotAUriToAConstant;;
+
+let new_inductive () =
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+ let notebook = (rendering_window ())#notebook in
+
+ let chosen = ref false in
+ let inductive = ref true in
+ let paramsno = ref 0 in
+ let get_uri = ref (function _ -> assert false) in
+ let get_base_uri = ref (function _ -> assert false) in
+ let get_names = ref (function _ -> assert false) in
+ let get_types_and_cons = ref (function _ -> assert false) in
+ let get_context_and_subst = ref (function _ -> assert false) in 
+ let window =
+  GWindow.window
+   ~width:600 ~modal:true ~position:`CENTER
+   ~title:"New Block of Mutual (Co)Inductive Definitions"
+   ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let hbox =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"Enter the URI for the new block:"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let uri_entry =
+  GEdit.entry ~editable:true
+   ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let hbox0 =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label
+   ~text:
+     "Enter the number of left parameters in every arity and constructor type:"
+   ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
+ let paramsno_entry =
+  GEdit.entry ~editable:true ~text:"0"
+   ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
+ let hbox1 =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"Are the definitions inductive or coinductive?"
+   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
+ let inductiveb =
+  GButton.radio_button ~label:"Inductive"
+   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
+ let coinductiveb =
+  GButton.radio_button ~label:"Coinductive"
+   ~group:inductiveb#group
+   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
+ let hbox2 =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"Enter the list of the names of the types:"
+   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
+ let names_entry =
+  GEdit.entry ~editable:true
+   ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
+ let hboxn =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"> Next"
+   ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = okb#misc#set_sensitive true in
+ let cancelb =
+  GButton.button ~label:"Abort"
+   ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
+ ignore (window#connect#destroy GMain.Main.quit) ;
+ ignore (cancelb#connect#clicked window#destroy) ;
+ (* First phase *)
+ let rec phase1 () =
+  ignore
+   (okb#connect#clicked
+     (function () ->
+       try
+        let uristr = "cic:" ^ uri_entry#text in
+        let namesstr = names_entry#text in
+        let paramsno' = int_of_string (paramsno_entry#text) in
+         match Str.split (Str.regexp " +") namesstr with
+            [] -> assert false
+          | (he::tl) as names ->
+             let uri = UriManager.uri_of_string (uristr ^ "/" ^ he ^ ".ind") in
+              begin
+               try
+                ignore (Getter.resolve uri) ;
+                raise UriAlreadyInUse
+               with
+                Getter.Unresolved ->
+                 get_uri := (function () -> uri) ; 
+                 get_names := (function () -> names) ;
+                 inductive := inductiveb#active ;
+                 paramsno := paramsno' ;
+                 phase2 ()
+              end
+       with
+        e ->
+         output_html outputhtml
+          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+     ))
+ (* Second phase *)
+ and phase2 () =
+  let type_widgets =
+   List.map
+    (function name ->
+      let frame =
+       GBin.frame ~label:name
+        ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+      let vbox = GPack.vbox ~packing:frame#add () in
+      let hbox = GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false) () in
+      let _ =
+       GMisc.label ~text:("Enter its type:")
+        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+      let scrolled_window =
+       GBin.scrolled_window ~border_width:5
+        ~packing:(vbox#pack ~expand:true ~padding:0) () in
+      let newinputt =
+       TermEditor'.term_editor
+        ~width:400 ~height:20 ~packing:scrolled_window#add 
+        ~share_id_to_uris_with:inputt ()
+        ~isnotempty_callback:
+         (function b ->
+           (*non_empty_type := b ;*)
+           okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*)
+      in
+      let hbox =
+       GPack.hbox ~border_width:0
+        ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+      let _ =
+       GMisc.label ~text:("Enter the list of its constructors:")
+        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+      let cons_names_entry =
+       GEdit.entry ~editable:true
+        ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
+      (newinputt,cons_names_entry)
+    ) (!get_names ())
+  in
+   vbox#remove hboxn#coerce ;
+   let hboxn =
+    GPack.hbox ~border_width:0
+     ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+   let okb =
+    GButton.button ~label:"> Next"
+     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
+   let cancelb =
+    GButton.button ~label:"Abort"
+     ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
+   ignore (cancelb#connect#clicked window#destroy) ;
+   ignore
+    (okb#connect#clicked
+      (function () ->
+        try
+         let names = !get_names () in
+         let types_and_cons =
+          List.map2
+           (fun name (newinputt,cons_names_entry) ->
+             let consnamesstr = cons_names_entry#text in
+             let cons_names = Str.split (Str.regexp " +") consnamesstr in
+             let metasenv,expr =
+              newinputt#get_metasenv_and_term ~context:[] ~metasenv:[]
+             in
+              match metasenv with
+                 [] -> expr,cons_names
+               | _ -> raise AmbiguousInput
+           ) names type_widgets
+         in
+          let uri = !get_uri () in
+          let _ =
+           (* Let's see if so far the definition is well-typed *)
+           let params = [] in
+           let paramsno = 0 in
+           (* To test if the arities of the inductive types are well *)
+           (* typed, we check the inductive block definition where   *)
+           (* no constructor is given to each type.                  *)
+           let tys =
+            List.map2
+             (fun name (ty,cons) -> (name, !inductive, ty, []))
+             names types_and_cons
+           in
+            CicTypeChecker.typecheck_mutual_inductive_defs uri
+             (tys,params,paramsno)
+          in
+           get_context_and_subst :=
+            (function () ->
+              let i = ref 0 in
+               List.fold_left2
+                (fun (context,subst) name (ty,_) ->
+                  let res =
+                   (Some (Cic.Name name, Cic.Decl ty))::context,
+                    (Cic.MutInd (uri,!i,[]))::subst
+                  in
+                   incr i ; res
+                ) ([],[]) names types_and_cons) ;
+           let types_and_cons' =
+            List.map2
+             (fun name (ty,cons) -> (name, !inductive, ty, phase3 name cons))
+             names types_and_cons
+           in
+            get_types_and_cons := (function () -> types_and_cons') ;
+            chosen := true ;
+            window#destroy ()
+        with
+         e ->
+          output_html outputhtml
+           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+      ))
+ (* Third phase *)
+ and phase3 name cons =
+  let get_cons_types = ref (function () -> assert false) in
+  let window2 =
+   GWindow.window
+    ~width:600 ~modal:true ~position:`CENTER
+    ~title:(name ^ " Constructors")
+    ~border_width:2 () in
+  let vbox = GPack.vbox ~packing:window2#add () in
+  let cons_type_widgets =
+   List.map
+    (function consname ->
+      let hbox =
+       GPack.hbox ~border_width:0
+        ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+      let _ =
+       GMisc.label ~text:("Enter the type of " ^ consname ^ ":")
+        ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+      let scrolled_window =
+       GBin.scrolled_window ~border_width:5
+        ~packing:(vbox#pack ~expand:true ~padding:0) () in
+      let newinputt =
+       TermEditor'.term_editor
+        ~width:400 ~height:20 ~packing:scrolled_window#add
+        ~share_id_to_uris_with:inputt ()
+        ~isnotempty_callback:
+         (function b ->
+           (* (*non_empty_type := b ;*)
+           okb#misc#set_sensitive true) (*(b && uri_entry#text <> ""))*) *)())
+      in
+       newinputt
+    ) cons in
+  let hboxn =
+   GPack.hbox ~border_width:0
+    ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+  let okb =
+   GButton.button ~label:"> Next"
+    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
+  let _ = okb#misc#set_sensitive true in
+  let cancelb =
+   GButton.button ~label:"Abort"
+    ~packing:(hboxn#pack ~expand:false ~fill:false ~padding:5) () in
+  ignore (window2#connect#destroy GMain.Main.quit) ;
+  ignore (cancelb#connect#clicked window2#destroy) ;
+  ignore
+   (okb#connect#clicked
+     (function () ->
+       try
+        chosen := true ;
+        let context,subst= !get_context_and_subst () in
+        let cons_types =
+         List.map2
+          (fun name inputt ->
+            let metasenv,expr =
+             inputt#get_metasenv_and_term ~context ~metasenv:[]
+            in
+             match metasenv with
+                [] ->
+                 let undebrujined_expr =
+                  List.fold_left
+                   (fun expr t -> CicSubstitution.subst t expr) expr subst
+                 in
+                  name, undebrujined_expr
+              | _ -> raise AmbiguousInput
+          ) cons cons_type_widgets
+        in
+         get_cons_types := (function () -> cons_types) ;
+         window2#destroy ()
+       with
+        e ->
+         output_html outputhtml
+          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+     )) ;
+  window2#show () ;
+  GMain.Main.main () ;
+  let okb_pressed = !chosen in
+   chosen := false ;
+   if (not okb_pressed) then
+    begin
+     window#destroy () ;
+     assert false (* The control never reaches this point *)
+    end
+   else
+    (!get_cons_types ())
+ in
+  phase1 () ;
+  (* No more phases left or Abort pressed *) 
+  window#show () ;
+  GMain.Main.main () ;
+  window#destroy () ;
+  if !chosen then
+   try
+    let uri = !get_uri () in
+(*CSC: Da finire *)
+    let params = [] in
+    let tys = !get_types_and_cons () in
+     let obj = Cic.InductiveDefinition tys params !paramsno in
+      begin
+       try
+        prerr_endline (CicPp.ppobj obj) ;
+        CicTypeChecker.typecheck_mutual_inductive_defs uri
+         (tys,params,!paramsno) ;
+        with
+         e ->
+          prerr_endline "Offending mutual (co)inductive type declaration:" ;
+          prerr_endline (CicPp.ppobj obj) ;
+      end ;
+      (* We already know that obj is well-typed. We need to add it to the  *)
+      (* environment in order to compute the inner-types without having to *)
+      (* debrujin it or having to modify lots of other functions to avoid  *)
+      (* asking the environment for the MUTINDs we are defining now.       *)
+      CicEnvironment.put_inductive_definition uri obj ;
+      save_obj uri obj ;
+      show_in_show_window_obj uri obj
+   with
+    e ->
+     output_html outputhtml
+      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+;;
+
+let mk_fresh_name_callback context name ~typ =
+ let fresh_name =
+  match ProofEngineHelpers.mk_fresh_name context name ~typ with
+     Cic.Name fresh_name -> fresh_name
+   | Cic.Anonymous -> assert false
+ in
+  match
+   GToolbox.input_string ~title:"Enter a fresh hypothesis name" ~text:fresh_name
+    ("Enter a fresh name for the hypothesis " ^
+      CicPp.pp typ
+       (List.map (function None -> None | Some (n,_) -> Some n) context))
+  with
+     Some fresh_name' -> Cic.Name fresh_name'
+   | None -> raise NoChoice
+;;
+
+let new_proof () =
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+ let notebook = (rendering_window ())#notebook in
+
+ let chosen = ref false in
+ let get_metasenv_and_term = ref (function _ -> assert false) in
+ let get_uri = ref (function _ -> assert false) in
+ let non_empty_type = ref false in
+ let window =
+  GWindow.window
+   ~width:600 ~modal:true ~title:"New Proof or Definition"
+   ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let hbox =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"Enter the URI for the new theorem or definition:"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let uri_entry =
+  GEdit.entry ~editable:true
+   ~packing:(hbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let hbox1 =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ =
+  GMisc.label ~text:"Enter the theorem or definition type:"
+   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:5
+   ~packing:(vbox#pack ~expand:true ~padding:0) () in
+ (* the content of the scrolled_window is moved below (see comment) *)
+ let hbox =
+  GPack.hbox ~border_width:0
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = okb#misc#set_sensitive false in
+ let cancelb =
+  GButton.button ~label:"Cancel"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ (* moved here to have visibility of the ok button *)
+ let newinputt =
+  TermEditor'.term_editor ~width:400 ~height:100 ~packing:scrolled_window#add
+   ~share_id_to_uris_with:inputt ()
+   ~isnotempty_callback:
+    (function b ->
+      non_empty_type := b ;
+      okb#misc#set_sensitive (b && uri_entry#text <> ""))
+ in
+ let _ =
+  newinputt#set_term inputt#get_as_string ;
+  inputt#reset in
+ let _ =
+  uri_entry#connect#changed
+   (function () ->
+     okb#misc#set_sensitive (!non_empty_type && uri_entry#text <> ""))
+ in
+ ignore (window#connect#destroy GMain.Main.quit) ;
+ ignore (cancelb#connect#clicked window#destroy) ;
+ ignore
+  (okb#connect#clicked
+    (function () ->
+      chosen := true ;
+      try
+       let metasenv,parsed = newinputt#get_metasenv_and_term [] [] in
+       let uristr = "cic:" ^ uri_entry#text in
+       let uri = UriManager.uri_of_string uristr in
+        if String.sub uristr (String.length uristr - 4) 4 <> ".con" then
+         raise NotAUriToAConstant
+        else
+         begin
+          try
+           ignore (Getter.resolve uri) ;
+           raise UriAlreadyInUse
+          with
+           Getter.Unresolved ->
+            get_metasenv_and_term := (function () -> metasenv,parsed) ;
+            get_uri := (function () -> uri) ; 
+            window#destroy ()
+         end
+      with
+       e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+  )) ;
+ window#show () ;
+ GMain.Main.main () ;
+ if !chosen then
+  try
+   let metasenv,expr = !get_metasenv_and_term () in
+    let _  = CicTypeChecker.type_of_aux' metasenv [] expr in
+     ProofEngine.proof :=
+      Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
+     ProofEngine.goal := Some 1 ;
+     refresh_sequent notebook ;
+     refresh_proof output ;
+     !save_set_sensitive true ;
+     inputt#reset ;
+     ProofEngine.intros ~mk_fresh_name_callback () ;
+     refresh_sequent notebook ;
+     refresh_proof output
+  with
+     RefreshSequentException e ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+        "sequent: " ^ Printexc.to_string e ^ "</h1>")
+   | RefreshProofException e ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+        "proof: " ^ Printexc.to_string e ^ "</h1>")
+   | e ->
+      output_html outputhtml
+       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+;;
+
+let check_term_in_scratch scratch_window metasenv context expr = 
+ try
+  let ty = CicTypeChecker.type_of_aux' metasenv context expr in
+   let mml = mml_of_cic_term 111 (Cic.Cast (expr,ty)) in
+    scratch_window#show () ;
+    scratch_window#mmlwidget#load_doc ~dom:mml
+ with
+  e ->
+   print_endline ("? " ^ CicPp.ppterm expr) ;
+   raise e
+;;
+
+let check scratch_window () =
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let metasenv =
+   match !ProofEngine.proof with
+      None -> []
+    | Some (_,metasenv,_,_) -> metasenv
+  in
+  let context =
+   match !ProofEngine.goal with
+      None -> []
+    | Some metano ->
+       let (_,canonical_context,_) =
+        List.find (function (m,_,_) -> m=metano) metasenv
+       in
+        canonical_context
+  in
+   try
+    let metasenv',expr = inputt#get_metasenv_and_term context metasenv in
+     check_term_in_scratch scratch_window metasenv' context expr
+   with
+    e ->
+     output_html outputhtml
+      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+;;
+
+let decompose_uris_choice_callback uris = 
+(* N.B.: in questo passaggio perdo l'informazione su exp_named_subst !!!! *)
+  let module U = UriManager in 
+   List.map 
+    (function uri ->
+      match Misc.cic_textual_parser_uri_of_string uri with
+         CicTextualParser0.IndTyUri (uri,typeno) -> (uri,typeno,[])
+       | _ -> assert false)
+    (interactive_user_uri_choice 
+      ~selection_mode:`EXTENDED ~ok:"Ok" ~enable_button_for_non_vars:false 
+      ~title:"Decompose" ~msg:"Please, select the Inductive Types to decompose" 
+      (List.map 
+        (function (uri,typeno,_) ->
+          U.string_of_uri uri ^ "#1/" ^ string_of_int (typeno+1)
+        ) uris)
+    ) 
+;;
+
+(***********************)
+(*       TACTICS       *)
+(***********************)
+
+let call_tactic tactic () =
+ let notebook = (rendering_window ())#notebook in
+ let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let savedproof = !ProofEngine.proof in
+ let savedgoal  = !ProofEngine.goal in
+  begin
+   try
+    tactic () ;
+    refresh_sequent notebook ;
+    refresh_proof output
+   with
+      RefreshSequentException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+       refresh_sequent notebook
+    | RefreshProofException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+       refresh_sequent notebook ;
+       refresh_proof output
+    | e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+  end
+;;
+
+let call_tactic_with_input tactic () =
+ let notebook = (rendering_window ())#notebook in
+ let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let savedproof = !ProofEngine.proof in
+ let savedgoal  = !ProofEngine.goal in
+  let uri,metasenv,bo,ty =
+   match !ProofEngine.proof with
+      None -> assert false
+    | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
+  in
+   let canonical_context =
+    match !ProofEngine.goal with
+       None -> assert false
+     | Some metano ->
+        let (_,canonical_context,_) =
+         List.find (function (m,_,_) -> m=metano) metasenv
+        in
+         canonical_context
+   in
+    try
+     let metasenv',expr =
+      inputt#get_metasenv_and_term canonical_context metasenv
+     in
+      ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
+      tactic expr ;
+      refresh_sequent notebook ;
+      refresh_proof output ;
+      inputt#reset
+    with
+       RefreshSequentException e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+          "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+        ProofEngine.proof := savedproof ;
+        ProofEngine.goal := savedgoal ;
+        refresh_sequent notebook
+     | RefreshProofException e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+          "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+        ProofEngine.proof := savedproof ;
+        ProofEngine.goal := savedgoal ;
+        refresh_sequent notebook ;
+        refresh_proof output
+     | e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+        ProofEngine.proof := savedproof ;
+        ProofEngine.goal := savedgoal ;
+;;
+
+let call_tactic_with_goal_input tactic () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let notebook = (rendering_window ())#notebook in
+  let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match notebook#proofw#get_selections with
+     [node] ->
+      let xpath =
+       ((node : Gdome.element)#getAttributeNS
+         ~namespaceURI:Misc.helmns
+         ~localName:(G.domString "xref"))#to_string
+      in
+       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+       else
+        begin
+         try
+          match !current_goal_infos with
+             Some (ids_to_terms, ids_to_father_ids,_) ->
+              let id = xpath in
+               tactic (Hashtbl.find ids_to_terms id) ;
+               refresh_sequent notebook ;
+               refresh_proof output
+           | None -> assert false (* "ERROR: No current term!!!" *)
+         with
+            RefreshSequentException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook
+          | RefreshProofException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook ;
+             refresh_proof output
+          | e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+        end
+   | [] ->
+      output_html outputhtml
+       ("<h1 color=\"red\">No term selected</h1>")
+   | _ ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Many terms selected</h1>")
+;;
+
+let call_tactic_with_goal_inputs tactic () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let notebook = (rendering_window ())#notebook in
+  let output =
+   ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   try
+    let term_of_node node =
+     let xpath =
+      ((node : Gdome.element)#getAttributeNS
+        ~namespaceURI:Misc.helmns
+        ~localName:(G.domString "xref"))#to_string
+     in
+      if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+      else
+       match !current_goal_infos with
+          Some (ids_to_terms, ids_to_father_ids,_) ->
+           let id = xpath in
+            (Hashtbl.find ids_to_terms id)
+        | None -> assert false (* "ERROR: No current term!!!" *)
+    in
+     match notebook#proofw#get_selections with
+        [] ->
+         output_html outputhtml
+          ("<h1 color=\"red\">No term selected</h1>")
+      | l ->
+         let terms = List.map term_of_node l in
+           match !current_goal_infos with
+              Some (ids_to_terms, ids_to_father_ids,_) ->
+               tactic terms ;
+               refresh_sequent notebook ;
+               refresh_proof output
+            | None -> assert false (* "ERROR: No current term!!!" *)
+   with
+      RefreshSequentException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+       refresh_sequent notebook
+    | RefreshProofException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+       refresh_sequent notebook ;
+       refresh_proof output
+    | e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal
+;;
+
+let call_tactic_with_input_and_goal_input tactic () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let notebook = (rendering_window ())#notebook in
+  let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match notebook#proofw#get_selections with
+     [node] ->
+      let xpath =
+       ((node : Gdome.element)#getAttributeNS
+         ~namespaceURI:Misc.helmns
+         ~localName:(G.domString "xref"))#to_string
+      in
+       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+       else
+        begin
+         try
+          match !current_goal_infos with
+             Some (ids_to_terms, ids_to_father_ids,_) ->
+              let id = xpath in
+               let uri,metasenv,bo,ty =
+                match !ProofEngine.proof with
+                   None -> assert false
+                 | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
+               in
+                let canonical_context =
+                 match !ProofEngine.goal with
+                    None -> assert false
+                  | Some metano ->
+                     let (_,canonical_context,_) =
+                      List.find (function (m,_,_) -> m=metano) metasenv
+                     in
+                      canonical_context in
+                let (metasenv',expr) =
+                 inputt#get_metasenv_and_term canonical_context metasenv
+                in
+                 ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
+                 tactic ~goal_input:(Hashtbl.find ids_to_terms id)
+                  ~input:expr ;
+                 refresh_sequent notebook ;
+                 refresh_proof output ;
+                 inputt#reset
+           | None -> assert false (* "ERROR: No current term!!!" *)
+         with
+            RefreshSequentException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook
+          | RefreshProofException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook ;
+             refresh_proof output
+          | e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+        end
+   | [] ->
+      output_html outputhtml
+       ("<h1 color=\"red\">No term selected</h1>")
+   | _ ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Many terms selected</h1>")
+;;
+
+let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let mmlwidget =
+   (scratch_window#mmlwidget : GMathViewAux.multi_selection_math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match mmlwidget#get_selections with
+     [node] ->
+      let xpath =
+       ((node : Gdome.element)#getAttributeNS
+         ~namespaceURI:Misc.helmns
+         ~localName:(G.domString "xref"))#to_string
+      in
+       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+       else
+        begin
+         try
+          match !current_scratch_infos with
+             (* term is the whole goal in the scratch_area *)
+             Some (term,ids_to_terms, ids_to_father_ids,_) ->
+              let id = xpath in
+               let expr = tactic term (Hashtbl.find ids_to_terms id) in
+                let mml = mml_of_cic_term 111 expr in
+                 scratch_window#show () ;
+                 scratch_window#mmlwidget#load_doc ~dom:mml
+           | None -> assert false (* "ERROR: No current term!!!" *)
+         with
+          e ->
+           output_html outputhtml
+            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+        end
+   | [] ->
+      output_html outputhtml
+       ("<h1 color=\"red\">No term selected</h1>")
+   | _ ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Many terms selected</h1>")
+;;
+
+let call_tactic_with_goal_inputs_in_scratch tactic scratch_window () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let mmlwidget =
+   (scratch_window#mmlwidget : GMathViewAux.multi_selection_math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match mmlwidget#get_selections with
+      [] ->
+       output_html outputhtml
+        ("<h1 color=\"red\">No term selected</h1>")
+    | l ->
+       try
+        match !current_scratch_infos with
+           (* term is the whole goal in the scratch_area *)
+           Some (term,ids_to_terms, ids_to_father_ids,_) ->
+            let term_of_node node =
+             let xpath =
+              ((node : Gdome.element)#getAttributeNS
+                ~namespaceURI:Misc.helmns
+                ~localName:(G.domString "xref"))#to_string
+             in
+              if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+              else
+               let id = xpath in
+                Hashtbl.find ids_to_terms id
+            in
+             let terms = List.map term_of_node l in
+              let expr = tactic terms term in
+               let mml = mml_of_cic_term 111 expr in
+                scratch_window#show () ;
+                scratch_window#mmlwidget#load_doc ~dom:mml
+         | None -> assert false (* "ERROR: No current term!!!" *)
+       with
+        e ->
+         output_html outputhtml
+          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+;;
+
+let call_tactic_with_hypothesis_input tactic () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let notebook = (rendering_window ())#notebook in
+  let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match notebook#proofw#get_selections with
+     [node] ->
+      let xpath =
+       ((node : Gdome.element)#getAttributeNS
+         ~namespaceURI:Misc.helmns
+         ~localName:(G.domString "xref"))#to_string
+      in
+       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+       else
+        begin
+         try
+          match !current_goal_infos with
+             Some (_,_,ids_to_hypotheses) ->
+              let id = xpath in
+               tactic (Hashtbl.find ids_to_hypotheses id) ;
+               refresh_sequent notebook ;
+               refresh_proof output
+           | None -> assert false (* "ERROR: No current term!!!" *)
+         with
+            RefreshSequentException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook
+          | RefreshProofException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook ;
+             refresh_proof output
+          | e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+        end
+   | [] ->
+      output_html outputhtml
+       ("<h1 color=\"red\">No term selected</h1>")
+   | _ ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Many terms selected</h1>")
+;;
+
+
+let intros = call_tactic (ProofEngine.intros ~mk_fresh_name_callback);;
+let exact = call_tactic_with_input ProofEngine.exact;;
+let apply = call_tactic_with_input ProofEngine.apply;;
+let elimintrossimpl = call_tactic_with_input ProofEngine.elim_intros_simpl;;
+let elimtype = call_tactic_with_input ProofEngine.elim_type;;
+let whd = call_tactic_with_goal_inputs ProofEngine.whd;;
+let reduce = call_tactic_with_goal_inputs ProofEngine.reduce;;
+let simpl = call_tactic_with_goal_inputs ProofEngine.simpl;;
+let fold_whd = call_tactic_with_input ProofEngine.fold_whd;;
+let fold_reduce = call_tactic_with_input ProofEngine.fold_reduce;;
+let fold_simpl = call_tactic_with_input ProofEngine.fold_simpl;;
+let cut = call_tactic_with_input (ProofEngine.cut ~mk_fresh_name_callback);;
+let change = call_tactic_with_input_and_goal_input ProofEngine.change;;
+let letin = call_tactic_with_input (ProofEngine.letin ~mk_fresh_name_callback);;
+let ring = call_tactic ProofEngine.ring;;
+let clearbody = call_tactic_with_hypothesis_input ProofEngine.clearbody;;
+let clear = call_tactic_with_hypothesis_input ProofEngine.clear;;
+let fourier = call_tactic ProofEngine.fourier;;
+let rewritesimpl = call_tactic_with_input ProofEngine.rewrite_simpl;;
+let rewritebacksimpl = call_tactic_with_input ProofEngine.rewrite_back_simpl;;
+let replace = call_tactic_with_input_and_goal_input ProofEngine.replace;;
+let reflexivity = call_tactic ProofEngine.reflexivity;;
+let symmetry = call_tactic ProofEngine.symmetry;;
+let transitivity = call_tactic_with_input ProofEngine.transitivity;;
+let exists = call_tactic ProofEngine.exists;;
+let split = call_tactic ProofEngine.split;;
+let left = call_tactic ProofEngine.left;;
+let right = call_tactic ProofEngine.right;;
+let assumption = call_tactic ProofEngine.assumption;;
+let generalize =
+ call_tactic_with_goal_inputs (ProofEngine.generalize ~mk_fresh_name_callback);;
+let absurd = call_tactic_with_input ProofEngine.absurd;;
+let contradiction = call_tactic ProofEngine.contradiction;;
+let decompose =
+ call_tactic_with_input
+  (ProofEngine.decompose ~uris_choice_callback:decompose_uris_choice_callback);;
+
+let whd_in_scratch scratch_window =
+ call_tactic_with_goal_inputs_in_scratch ProofEngine.whd_in_scratch
+  scratch_window
+;;
+let reduce_in_scratch scratch_window =
+ call_tactic_with_goal_inputs_in_scratch ProofEngine.reduce_in_scratch
+  scratch_window
+;;
+let simpl_in_scratch scratch_window =
+ call_tactic_with_goal_inputs_in_scratch ProofEngine.simpl_in_scratch
+  scratch_window
+;;
+
+
+
+(**********************)
+(*   END OF TACTICS   *)
+(**********************)
+
+
+let show () =
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  try
+   show_in_show_window_uri (input_or_locate_uri ~title:"Show")
+  with
+   e ->
+    output_html outputhtml
+     ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+;;
+
 exception NotADefinition;;
 
 let open_ () =
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let output = ((rendering_window ())#output : GMathView.math_view) in
+ let output = ((rendering_window ())#output : GMathViewAux.single_selection_math_view) in
  let notebook = (rendering_window ())#notebook in
-  let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen in
    try
-    let uri = UriManager.uri_of_string ("cic:" ^ input) in
+    let uri = input_or_locate_uri ~title:"Open" in
      CicTypeChecker.typecheck uri ;
      let metasenv,bo,ty =
       match CicEnvironment.get_cooked_obj uri with
@@ -1292,8 +2228,7 @@ let open_ () =
        Some (uri, metasenv, bo, ty) ;
       ProofEngine.goal := None ;
       refresh_sequent notebook ;
-      refresh_proof output ;
-      inputt#delete_text 0 inputlen
+      refresh_proof output
    with
       RefreshSequentException e ->
        output_html outputhtml
@@ -1308,250 +2243,569 @@ let open_ () =
         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
-let state () =
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
- let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let output = ((rendering_window ())#output : GMathView.math_view) in
- let notebook = (rendering_window ())#notebook in
-  let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen ^ "\n" in
-   (* Do something interesting *)
-   let lexbuf = Lexing.from_string input in
-    try
-     while true do
-      (* Execute the actions *)
-      match
-       CicTextualParserContext.main [] [] CicTextualLexer.token
-        lexbuf register_alias
-      with
-         None -> ()
-       | Some (dom,mk_metasenv_and_expr) ->
-          let metasenv,expr =
-           disambiguate_input [] [] dom mk_metasenv_and_expr
-          in
-           let _  = CicTypeChecker.type_of_aux' metasenv [] expr in
-            ProofEngine.proof :=
-             Some (UriManager.uri_of_string "cic:/dummy.con",
-                    (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
-            ProofEngine.goal := Some 1 ;
-            refresh_sequent notebook ;
-            refresh_proof output ;
-     done
-    with
-       CicTextualParser0.Eof ->
-        inputt#delete_text 0 inputlen
-     | RefreshSequentException e ->
-        output_html outputhtml
-         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-          "sequent: " ^ Printexc.to_string e ^ "</h1>")
-     | RefreshProofException e ->
-        output_html outputhtml
-         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
-          "proof: " ^ Printexc.to_string e ^ "</h1>")
-     | e ->
-        output_html outputhtml
-         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-;;
-
-let check_term_in_scratch scratch_window metasenv context expr = 
- try
-  let ty  = CicTypeChecker.type_of_aux' metasenv context expr in
-   let mml = mml_of_cic_term 111 (Cic.Cast (expr,ty)) in
-prerr_endline ("### " ^ CicPp.ppterm expr ^ " ==> " ^ CicPp.ppterm ty) ;
-    scratch_window#show () ;
-    scratch_window#mmlwidget#load_tree ~dom:mml
- with
-  e ->
-   print_endline ("? " ^ CicPp.ppterm expr) ;
-   raise e
+let show_query_results results =
+ let window =
+  GWindow.window
+   ~modal:false ~title:"Query results." ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text:"Click on a URI to show that object"
+   ~packing:hbox#add () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let clist = GList.clist ~columns:1 ~packing:scrolled_window#add () in
+  ignore
+   (List.map
+     (function (uri,_) ->
+       let n =
+        clist#append [uri]
+       in
+        clist#set_row ~selectable:false n
+     ) results
+   ) ;
+  clist#columns_autosize () ;
+  ignore
+   (clist#connect#select_row
+     (fun ~row ~column ~event ->
+       let (uristr,_) = List.nth results row in
+        match
+         Misc.cic_textual_parser_uri_of_string
+          (Misc.wrong_xpointer_format_from_wrong_xpointer_format'
+            uristr)
+        with
+           CicTextualParser0.ConUri uri
+         | CicTextualParser0.VarUri uri
+         | CicTextualParser0.IndTyUri (uri,_)
+         | CicTextualParser0.IndConUri (uri,_,_) ->
+            show_in_show_window_uri uri
+     )
+   ) ;
+  window#show ()
 ;;
 
-let check scratch_window () =
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
- let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen ^ "\n" in
-  let curi,metasenv =
-   match !ProofEngine.proof with
-      None -> UriManager.uri_of_string "cic:/dummy.con", []
-    | Some (curi,metasenv,_,_) -> curi,metasenv
-  in
-  let context,names_context =
-   let context =
-    match !ProofEngine.goal with
-       None -> []
-     | Some metano ->
-        let (_,canonical_context,_) =
-         List.find (function (m,_,_) -> m=metano) metasenv
-        in
-         canonical_context
+let refine_constraints (must_obj,must_rel,must_sort) =
+ let chosen = ref false in
+ let use_only = ref false in
+ let window =
+  GWindow.window
+   ~modal:true ~title:"Constraints refinement."
+   ~width:800 ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text: "\"Only\" constraints can be enforced or not."
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let onlyb =
+  GButton.toggle_button ~label:"Enforce \"only\" constraints"
+   ~active:false ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
+ in
+  ignore
+   (onlyb#connect#toggled (function () -> use_only := onlyb#active)) ;
+ (* Notebook for the constraints choice *)
+ let notebook =
+  GPack.notebook ~scrollable:true
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ (* Rel constraints *)
+ let label =
+  GMisc.label
+   ~text: "Constraints on Rels" () in
+ let vbox' =
+  GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
+   () in
+ let hbox =
+  GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text: "You can now specify the constraints on Rels."
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let expected_height = 25 * (List.length must_rel + 2) in
+ let height = if expected_height > 400 then 400 else expected_height in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10 ~height ~width:600
+   ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
+ let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
+ let rel_constraints =
+  List.map
+   (function (position,depth) ->
+     let hbox =
+      GPack.hbox
+       ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
+     let lMessage =
+      GMisc.label
+       ~text:position
+       ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+     match depth with
+        None -> position, ref None
+      | Some depth' ->
+         let mutable_ref = ref (Some depth') in
+         let depthb =
+          GButton.toggle_button
+           ~label:("depth = " ^ string_of_int depth') ~active:true
+           ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
+         in
+          ignore
+           (depthb#connect#toggled
+             (function () ->
+               let sel_depth = if depthb#active then Some depth' else None in
+                mutable_ref := sel_depth
+            )) ;
+          position, mutable_ref
+   ) must_rel in
+ (* Sort constraints *)
+ let label =
+  GMisc.label
+   ~text: "Constraints on Sorts" () in
+ let vbox' =
+  GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
+   () in
+ let hbox =
+  GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text: "You can now specify the constraints on Sorts."
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let expected_height = 25 * (List.length must_sort + 2) in
+ let height = if expected_height > 400 then 400 else expected_height in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10 ~height ~width:600
+   ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
+ let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
+ let sort_constraints =
+  List.map
+   (function (position,depth,sort) ->
+     let hbox =
+      GPack.hbox
+       ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
+     let lMessage =
+      GMisc.label
+       ~text:(sort ^ " " ^ position)
+       ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+     match depth with
+        None -> position, ref None, sort
+      | Some depth' ->
+         let mutable_ref = ref (Some depth') in
+         let depthb =
+          GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
+           ~active:true
+           ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
+         in
+          ignore
+           (depthb#connect#toggled
+             (function () ->
+               let sel_depth = if depthb#active then Some depth' else None in
+                mutable_ref := sel_depth
+            )) ;
+          position, mutable_ref, sort
+   ) must_sort in
+ (* Obj constraints *)
+ let label =
+  GMisc.label
+   ~text: "Constraints on constants" () in
+ let vbox' =
+  GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce)
+   () in
+ let hbox =
+  GPack.hbox ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text: "You can now specify the constraints on constants."
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let expected_height = 25 * (List.length must_obj + 2) in
+ let height = if expected_height > 400 then 400 else expected_height in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10 ~height ~width:600
+   ~packing:(vbox'#pack ~expand:true ~fill:true ~padding:5) () in
+ let scrolled_vbox = GPack.vbox ~packing:scrolled_window#add_with_viewport () in
+ let obj_constraints =
+  List.map
+   (function (uri,position,depth) ->
+     let hbox =
+      GPack.hbox
+       ~packing:(scrolled_vbox#pack ~expand:false ~fill:false ~padding:5) () in
+     let lMessage =
+      GMisc.label
+       ~text:(uri ^ " " ^ position)
+       ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+     match depth with
+        None -> uri, position, ref None
+      | Some depth' ->
+         let mutable_ref = ref (Some depth') in
+         let depthb =
+          GButton.toggle_button ~label:("depth = " ^ string_of_int depth')
+           ~active:true
+           ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
+         in
+          ignore
+           (depthb#connect#toggled
+             (function () ->
+               let sel_depth = if depthb#active then Some depth' else None in
+                mutable_ref := sel_depth
+            )) ;
+          uri, position, mutable_ref
+   ) must_obj in
+ (* Confirm/abort buttons *)
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let cancelb =
+  GButton.button ~label:"Abort"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) ()
+ in
+  ignore (window#connect#destroy GMain.Main.quit) ;
+  ignore (cancelb#connect#clicked window#destroy) ;
+  ignore
+   (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
+  window#set_position `CENTER ;
+  window#show () ;
+  GMain.Main.main () ;
+  if !chosen then
+   let chosen_must_rel =
+    List.map
+     (function (position,ref_depth) -> position,!ref_depth) rel_constraints in
+   let chosen_must_sort =
+    List.map
+     (function (position,ref_depth,sort) -> position,!ref_depth,sort)
+     sort_constraints
    in
-    context,
+   let chosen_must_obj =
     List.map
-     (function
-         Some (n,_) -> Some n
-       | None -> None
-     ) context
-  in
-   let lexbuf = Lexing.from_string input in
-    try
-     while true do
-      (* Execute the actions *)
-      match
-       CicTextualParserContext.main names_context metasenv CicTextualLexer.token
-        lexbuf register_alias
-      with
-         None -> ()
-       | Some (dom,mk_metasenv_and_expr) ->
-          let (metasenv',expr) =
-           disambiguate_input context metasenv dom mk_metasenv_and_expr
-          in
-           check_term_in_scratch scratch_window metasenv' context expr
-     done
-    with
-       CicTextualParser0.Eof -> ()
-     | e ->
-       output_html outputhtml
-        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+     (function (uri,position,ref_depth) -> uri,position,!ref_depth)
+     obj_constraints
+   in
+    (chosen_must_obj,chosen_must_rel,chosen_must_sort),
+     (if !use_only then
+(*CSC: ???????????????????????? I assume that must and only are the same... *)
+       Some chosen_must_obj,Some chosen_must_rel,Some chosen_must_sort
+      else
+       None,None,None
+     )
+  else
+   raise NoChoice
 ;;
 
-exception NoObjectsLocated;;
-
-let user_uri_choice ~title ~msg uris =
- let uri =
-  match uris with
-     [] -> raise NoObjectsLocated
-   | [uri] -> uri
-   | uris ->
-      interactive_user_uri_choice ~title ~msg uris
- in
-  String.sub uri 4 (String.length uri - 4)
+let completeSearchPattern () =
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  try
+   let metasenv,expr = inputt#get_metasenv_and_term ~context:[] ~metasenv:[] in
+   let must = MQueryLevels2.get_constraints expr in
+   let must',only = refine_constraints must in
+   let results = MQueryGenerator.searchPattern must' only in 
+    show_query_results results
+  with
+   e ->
+    output_html outputhtml
+     ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
-let locate () =
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
+let insertQuery () =
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen in
-   try
-    match Str.split (Str.regexp "[ \t]+") input with
-       [] -> ()
-     | head :: tail ->
-        inputt#delete_text 0 inputlen ;
-        let result = MQueryGenerator.locate head in
-       let uris =
-         List.map
-          (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
-          result in
-       let html = (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>") in
-         output_html outputhtml html ;
-         let uri' =
-          user_uri_choice ~title:"Ambiguous input."
-           ~msg:
-             ("Ambiguous input \"" ^ head ^
-              "\". Please, choose one interpetation:")
-           uris
-         in
-          ignore ((inputt#insert_text uri') ~pos:0)
-   with
-    e ->
-     output_html outputhtml
-      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+  try
+   let chosen = ref None in
+   let window =
+    GWindow.window
+     ~modal:true ~title:"Insert Query (Experts Only)" ~border_width:2 () in
+   let vbox = GPack.vbox ~packing:window#add () in
+   let label =
+    GMisc.label ~text:"Insert Query. For Experts Only."
+     ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+   let scrolled_window =
+    GBin.scrolled_window ~border_width:10 ~height:400 ~width:600
+     ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+   let input = GEdit.text ~editable:true
+    ~packing:scrolled_window#add () in
+   let hbox =
+    GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+   let okb =
+    GButton.button ~label:"Ok"
+     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+   let loadb =
+    GButton.button ~label:"Load from file..."
+     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+   let cancelb =
+    GButton.button ~label:"Abort"
+     ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+   ignore (window#connect#destroy GMain.Main.quit) ;
+   ignore (cancelb#connect#clicked window#destroy) ;
+   ignore
+    (okb#connect#clicked
+      (function () ->
+        chosen := Some (input#get_chars 0 input#length) ; window#destroy ())) ;
+   ignore
+    (loadb#connect#clicked
+      (function () ->
+        match
+         GToolbox.select_file ~title:"Select Query File" ()
+        with
+           None -> ()
+         | Some filename ->
+            let inch = open_in filename in
+             let rec read_file () =
+              try
+               let line = input_line inch in
+                line ^ "\n" ^ read_file ()
+              with
+               End_of_file -> ""
+             in
+              let text = read_file () in
+               input#delete_text 0 input#length ;
+               ignore (input#insert_text text ~pos:0))) ;
+   window#set_position `CENTER ;
+   window#show () ;
+   GMain.Main.main () ;
+   match !chosen with
+      None -> ()
+    | Some q ->
+       let results =
+        Mqint.execute (MQueryUtil.query_of_text (Lexing.from_string q))
+       in
+        show_query_results results
+  with
+   e ->
+    output_html outputhtml
+     ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+;;
+
+let choose_must list_of_must only =
+ let chosen = ref None in
+ let user_constraints = ref [] in
+ let window =
+  GWindow.window
+   ~modal:true ~title:"Query refinement." ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text:
+    ("You can now specify the genericity of the query. " ^
+     "The more generic the slower.")
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let lMessage =
+  GMisc.label
+   ~text:
+    "Suggestion: start with faster queries before moving to more generic ones."
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let notebook =
+  GPack.notebook ~scrollable:true
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let _ =
+  let page = ref 0 in
+  let last = List.length list_of_must in
+  List.map
+   (function must ->
+     incr page ;
+     let label =
+      GMisc.label ~text:
+       (if !page = 1 then "More generic" else
+         if !page = last then "More precise" else "          ") () in
+     let expected_height = 25 * (List.length must + 2) in
+     let height = if expected_height > 400 then 400 else expected_height in
+     let scrolled_window =
+      GBin.scrolled_window ~border_width:10 ~height ~width:600
+       ~packing:(notebook#append_page ~tab_label:label#coerce) () in
+     let clist =
+        GList.clist ~columns:2 ~packing:scrolled_window#add
+         ~titles:["URI" ; "Position"] ()
+     in
+      ignore
+       (List.map
+         (function (uri,position) ->
+           let n =
+            clist#append 
+             [uri; if position then "MainConclusion" else "Conclusion"]
+           in
+            clist#set_row ~selectable:false n
+         ) must
+       ) ;
+      clist#columns_autosize ()
+   ) list_of_must in
+ let _ =
+  let label = GMisc.label ~text:"User provided" () in
+  let vbox =
+   GPack.vbox ~packing:(notebook#append_page ~tab_label:label#coerce) () in
+  let hbox =
+   GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+  let lMessage =
+   GMisc.label
+   ~text:"Select the constraints that must be satisfied and press OK."
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+  let expected_height = 25 * (List.length only + 2) in
+  let height = if expected_height > 400 then 400 else expected_height in
+  let scrolled_window =
+   GBin.scrolled_window ~border_width:10 ~height ~width:600
+    ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+  let clist =
+   GList.clist ~columns:2 ~packing:scrolled_window#add
+    ~selection_mode:`EXTENDED
+    ~titles:["URI" ; "Position"] ()
+  in
+   ignore
+    (List.map
+      (function (uri,position) ->
+        let n =
+         clist#append 
+          [uri; if position then "MainConclusion" else "Conclusion"]
+        in
+         clist#set_row ~selectable:true n
+      ) only
+    ) ;
+   clist#columns_autosize () ;
+   ignore
+    (clist#connect#select_row
+      (fun ~row ~column ~event ->
+        user_constraints := (List.nth only row)::!user_constraints)) ;
+   ignore
+    (clist#connect#unselect_row
+      (fun ~row ~column ~event ->
+        user_constraints :=
+         List.filter
+          (function uri -> uri != (List.nth only row)) !user_constraints)) ;
+ in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let cancelb =
+  GButton.button ~label:"Abort"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ (* actions *)
+ ignore (window#connect#destroy GMain.Main.quit) ;
+ ignore (cancelb#connect#clicked window#destroy) ;
+ ignore
+  (okb#connect#clicked
+    (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
+ window#set_position `CENTER ;
+ window#show () ;
+ GMain.Main.main () ;
+ match !chosen with
+    None -> raise NoChoice
+  | Some n ->
+     if n = List.length list_of_must then
+      (* user provided constraints *)
+      !user_constraints
+     else
+      List.nth list_of_must n
 ;;
 
 let searchPattern () =
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let inputt = ((rendering_window ())#inputt : GEdit.text) in
-  let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen in
-  let level = int_of_string input in
-  let metasenv =
-   match !ProofEngine.proof with
-      None -> assert false
-    | Some (_,metasenv,_,_) -> metasenv
-  in
-   try
-    match !ProofEngine.goal with
-       None -> ()
-     | Some metano ->
-        let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
-         let result = MQueryGenerator.searchPattern metasenv ey ty level in
-         let uris =
-          List.map
-           (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
-           result in
-         let html =
-         " <h1>Backward Query: </h1>" ^
-         " <h2>Levels: </h2> " ^
-          MQueryGenerator.string_of_levels
-            (MQueryGenerator.levels_of_term metasenv ey ty) "<br>" ^
-          " <pre>" ^ get_last_query result ^ "</pre>"
-         in
-          output_html outputhtml html ;
-          let uris',exc =
-           let rec filter_out =
-            function
-               [] -> [],""
-             | uri::tl ->
-                let tl',exc = filter_out tl in
-                 try
-                  if
-                   ProofEngine.can_apply
-                    (term_of_cic_textual_parser_uri
-                     (cic_textual_parser_uri_of_string uri))
-                  then
-                   uri::tl',exc
-                  else
-                   tl',exc
-                 with
-                  e ->
-                   let exc' =
-                    "<h1 color=\"red\"> ^ Exception raised trying to apply " ^
-                     uri ^ ": " ^ Printexc.to_string e ^ " </h1>" ^ exc
-                   in
-                    tl',exc'
+  try
+    let metasenv =
+     match !ProofEngine.proof with
+        None -> assert false
+      | Some (_,metasenv,_,_) -> metasenv
+    in
+     match !ProofEngine.goal with
+        None -> ()
+      | Some metano ->
+         let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
+          let list_of_must,only = MQueryLevels.out_restr metasenv ey ty in
+         let must = choose_must list_of_must only in
+         let torigth_restriction (u,b) =
+          let p =
+            if b then
+             "http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion" 
+           else
+             "http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion"
            in
-            filter_out uris
+           (u,p,None)
+         in
+         let rigth_must = List.map torigth_restriction must in
+         let rigth_only = Some (List.map torigth_restriction only) in
+         let result =
+           MQueryGenerator.searchPattern
+            (rigth_must,[],[]) (rigth_only,None,None) in 
+          let uris =
+           List.map
+            (function uri,_ ->
+              Misc.wrong_xpointer_format_from_wrong_xpointer_format' uri
+            ) result in
+          let html =
+           " <h1>Backward Query: </h1>" ^
+          " <pre>" ^ get_last_query result ^ "</pre>"
           in
-           let html' =
-            " <h1>Objects that can actually be applied: </h1> " ^
-            String.concat "<br>" uris' ^ exc ^
-            " <h1>Number of false matches: " ^
-             string_of_int (List.length uris - List.length uris') ^ "</h1>" ^
-            " <h1>Number of good matches: " ^
-             string_of_int (List.length uris') ^ "</h1>"
+           output_html outputhtml html ;
+           let uris',exc =
+            let rec filter_out =
+             function
+                [] -> [],""
+              | uri::tl ->
+                 let tl',exc = filter_out tl in
+                  try
+                   if
+                    ProofEngine.can_apply
+                     (term_of_cic_textual_parser_uri
+                      (Misc.cic_textual_parser_uri_of_string uri))
+                   then
+                    uri::tl',exc
+                   else
+                    tl',exc
+                  with
+                   e ->
+                    let exc' =
+                     "<h1 color=\"red\"> ^ Exception raised trying to apply " ^
+                      uri ^ ": " ^ Printexc.to_string e ^ " </h1>" ^ exc
+                    in
+                     tl',exc'
+            in
+             filter_out uris
            in
-            output_html outputhtml html' ;
-            let uri' =
-             user_uri_choice ~title:"Ambiguous input."
-             ~msg:"Many lemmas can be successfully applied. Please, choose one:"
-              uris'
+            let html' =
+             " <h1>Objects that can actually be applied: </h1> " ^
+             String.concat "<br>" uris' ^ exc ^
+             " <h1>Number of false matches: " ^
+              string_of_int (List.length uris - List.length uris') ^ "</h1>" ^
+             " <h1>Number of good matches: " ^
+              string_of_int (List.length uris') ^ "</h1>"
             in
-             inputt#delete_text 0 inputlen ;
-             ignore ((inputt#insert_text uri') ~pos:0)
-    with
-     e -> 
-      output_html outputhtml 
-       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+             output_html outputhtml html' ;
+             let uri' =
+              user_uri_choice ~title:"Ambiguous input."
+              ~msg:
+                "Many lemmas can be successfully applied. Please, choose one:"
+               uris'
+             in
+              inputt#set_term uri' ;
+              apply ()
+  with
+   e -> 
+    output_html outputhtml 
+     ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
 ;;
       
-let choose_selection
-     (mmlwidget : GMathView.math_view) (element : Gdome.element option)
-=
+let choose_selection mmlwidget (element : Gdome.element option) =
  let module G = Gdome in
   let rec aux element =
    if element#hasAttributeNS
-       ~namespaceURI:helmns
+       ~namespaceURI:Misc.helmns
        ~localName:(G.domString "xref")
    then
      mmlwidget#set_selection (Some element)
    else
+    try
       match element#get_parentNode with
          None -> assert false
        (*CSC: OCAML DIVERGES!
        | Some p -> aux (new G.element_of_node p)
        *)
        | Some p -> aux (new Gdome.element_of_node p)
+    with
+       GdomeInit.DOMCastException _ ->
+        prerr_endline
+         "******* trying to select above the document root ********"
   in
    match element with
      Some x -> aux x
@@ -1562,7 +2816,7 @@ let choose_selection
 
 (* Stuff for the widget settings *)
 
-let export_to_postscript (output : GMathView.math_view) =
+let export_to_postscript (output : GMathViewAux.single_selection_math_view) =
  let lastdir = ref (Unix.getcwd ()) in
   function () ->
    match
@@ -1574,8 +2828,8 @@ let export_to_postscript (output : GMathView.math_view) =
        output#export_to_postscript ~filename:filename ();
 ;;
 
-let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
- button_set_kerning button_set_transparency export_to_postscript_menu_item
+let activate_t1 (output : GMathViewAux.single_selection_math_view) button_set_anti_aliasing
+ button_set_transparency export_to_postscript_menu_item
  button_t1 ()
 =
  let is_set = button_t1#active in
@@ -1584,14 +2838,12 @@ let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
   if is_set then
    begin
     button_set_anti_aliasing#misc#set_sensitive true ;
-    button_set_kerning#misc#set_sensitive true ;
     button_set_transparency#misc#set_sensitive true ;
     export_to_postscript_menu_item#misc#set_sensitive true ;
    end
   else
    begin
     button_set_anti_aliasing#misc#set_sensitive false ;
-    button_set_kerning#misc#set_sensitive false ;
     button_set_transparency#misc#set_sensitive false ;
     export_to_postscript_menu_item#misc#set_sensitive false ;
    end
@@ -1601,10 +2853,6 @@ let set_anti_aliasing output button_set_anti_aliasing () =
  output#set_anti_aliasing button_set_anti_aliasing#active
 ;;
 
-let set_kerning output button_set_kerning () =
- output#set_kerning button_set_kerning#active
-;;
-
 let set_transparency output button_set_transparency () =
  output#set_transparency button_set_transparency#active
 ;;
@@ -1617,7 +2865,7 @@ let set_log_verbosity output log_verbosity_spinb () =
  output#set_log_verbosity log_verbosity_spinb#value_as_int
 ;;
 
-class settings_window (output : GMathView.math_view) sw
+class settings_window (output : GMathViewAux.single_selection_math_view) sw
  export_to_postscript_menu_item selection_changed_callback
 =
  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
@@ -1633,9 +2881,6 @@ class settings_window (output : GMathView.math_view) sw
  let button_set_anti_aliasing =
   GButton.toggle_button ~label:"set_anti_aliasing"
    ~packing:(table#attach ~left:0 ~top:1) () in
- let button_set_kerning =
-  GButton.toggle_button ~label:"set_kerning"
-   ~packing:(table#attach ~left:1 ~top:1) () in
  let button_set_transparency =
   GButton.toggle_button ~label:"set_transparency"
    ~packing:(table#attach ~left:2 ~top:1) () in
@@ -1670,17 +2915,14 @@ object(self)
  method show = settings_window#show
  initializer
   button_set_anti_aliasing#misc#set_sensitive false ;
-  button_set_kerning#misc#set_sensitive false ;
   button_set_transparency#misc#set_sensitive false ;
   (* Signals connection *)
   ignore(button_t1#connect#clicked
-   (activate_t1 output button_set_anti_aliasing button_set_kerning
+   (activate_t1 output button_set_anti_aliasing
     button_set_transparency export_to_postscript_menu_item button_t1)) ;
   ignore(font_size_spinb#connect#changed (changefont output font_size_spinb)) ;
   ignore(button_set_anti_aliasing#connect#toggled
    (set_anti_aliasing output button_set_anti_aliasing));
-  ignore(button_set_kerning#connect#toggled
-   (set_kerning output button_set_kerning)) ;
   ignore(button_set_transparency#connect#toggled
    (set_transparency output button_set_transparency)) ;
   ignore(log_verbosity_spinb#connect#changed
@@ -1690,7 +2932,7 @@ end;;
 
 (* Scratch window *)
 
-class scratch_window outputhtml =
+class scratch_window =
  let window =
   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
  let vbox =
@@ -1710,10 +2952,9 @@ class scratch_window outputhtml =
   GBin.scrolled_window ~border_width:10
    ~packing:(vbox#pack ~expand:true ~padding:5) () in
  let mmlwidget =
-  GMathView.math_view
+  GMathViewAux.multi_selection_math_view
    ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
 object(self)
- method outputhtml = outputhtml
  method mmlwidget = mmlwidget
  method show () = window#misc#hide () ; window#show ()
  initializer
@@ -1724,145 +2965,277 @@ object(self)
   ignore(simplb#connect#clicked (simpl_in_scratch self))
 end;;
 
+let open_contextual_menu_for_selected_terms mmlwidget infos =
+ let button = GdkEvent.Button.button infos in 
+ let terms_selected = List.length mmlwidget#get_selections > 0 in
+  if button = 3 then
+   begin
+    let time = GdkEvent.Button.time infos in
+    let menu = GMenu.menu () in
+    let f = new GMenu.factory menu in
+    let whd_menu_item =
+     f#add_item "Whd" ~key:GdkKeysyms._W ~callback:whd in
+    let reduce_menu_item =
+     f#add_item "Reduce" ~key:GdkKeysyms._R ~callback:reduce in
+    let simpl_menu_item =
+     f#add_item "Simpl" ~key:GdkKeysyms._S ~callback:simpl in
+    let _ = f#add_separator () in
+    let generalize_menu_item =
+     f#add_item "Generalize" ~key:GdkKeysyms._G ~callback:generalize in
+    let _ = f#add_separator () in
+    let clear_menu_item =
+     f#add_item "Clear" ~key:GdkKeysyms._C ~callback:clear in
+    let clearbody_menu_item =
+     f#add_item "ClearBody" ~key:GdkKeysyms._B ~callback:clearbody
+    in
+     whd_menu_item#misc#set_sensitive terms_selected ; 
+     reduce_menu_item#misc#set_sensitive terms_selected ; 
+     simpl_menu_item#misc#set_sensitive terms_selected ;
+     generalize_menu_item#misc#set_sensitive terms_selected ;
+     clear_menu_item#misc#set_sensitive terms_selected ;
+     clearbody_menu_item#misc#set_sensitive terms_selected ;
+     menu#popup ~button ~time
+   end ;
+  true
+;;
+
 class page () =
  let vbox1 = GPack.vbox () in
+object(self)
+ val mutable proofw_ref = None
+ val mutable compute_ref = None
+ method proofw =
+  Lazy.force self#compute ;
+  match proofw_ref with
+     None -> assert false
+   | Some proofw -> proofw
+ method content = vbox1
+ method compute =
+  match compute_ref with
+     None -> assert false
+   | Some compute -> compute
+ initializer
+  compute_ref <-
+   Some (lazy (
+   let scrolled_window1 =
+    GBin.scrolled_window ~border_width:10
+     ~packing:(vbox1#pack ~expand:true ~padding:5) () in
+   let proofw =
+    GMathViewAux.multi_selection_math_view ~width:400 ~height:275
+     ~packing:(scrolled_window1#add) () in
+   let _ = proofw_ref <- Some proofw in
+   let hbox3 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let ringb =
+    GButton.button ~label:"Ring"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let fourierb =
+    GButton.button ~label:"Fourier"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let reflexivityb =
+    GButton.button ~label:"Reflexivity"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let symmetryb =
+    GButton.button ~label:"Symmetry"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let assumptionb =
+    GButton.button ~label:"Assumption"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let contradictionb =
+    GButton.button ~label:"Contradiction"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let hbox4 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let existsb =
+    GButton.button ~label:"Exists"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let splitb =
+    GButton.button ~label:"Split"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let leftb =
+    GButton.button ~label:"Left"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let rightb =
+    GButton.button ~label:"Right"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let searchpatternb =
+    GButton.button ~label:"SearchPattern_Apply"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let hbox5 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let exactb =
+    GButton.button ~label:"Exact"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let introsb =
+    GButton.button ~label:"Intros"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let applyb =
+    GButton.button ~label:"Apply"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let elimintrossimplb =
+    GButton.button ~label:"ElimIntrosSimpl"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let elimtypeb =
+    GButton.button ~label:"ElimType"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let foldwhdb =
+    GButton.button ~label:"Fold_whd"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let foldreduceb =
+    GButton.button ~label:"Fold_reduce"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let hbox6 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let foldsimplb =
+    GButton.button ~label:"Fold_simpl"
+     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
+   let cutb =
+    GButton.button ~label:"Cut"
+     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
+   let changeb =
+    GButton.button ~label:"Change"
+     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
+   let letinb =
+    GButton.button ~label:"Let ... In"
+     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
+   let rewritesimplb =
+    GButton.button ~label:"RewriteSimpl ->"
+     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
+   let rewritebacksimplb =
+    GButton.button ~label:"RewriteSimpl <-"
+     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
+   let hbox7 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let absurdb =
+    GButton.button ~label:"Absurd"
+     ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
+   let decomposeb =
+    GButton.button ~label:"Decompose"
+     ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
+   let transitivityb =
+    GButton.button ~label:"Transitivity"
+     ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
+   let replaceb =
+    GButton.button ~label:"Replace"
+     ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
+(* Zack: spostare in una toolbar
+   let generalizeb =
+    GButton.button ~label:"Generalize"
+     ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
+   let clearbodyb =
+    GButton.button ~label:"ClearBody"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let clearb =
+    GButton.button ~label:"Clear"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let whdb =
+    GButton.button ~label:"Whd"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let reduceb =
+    GButton.button ~label:"Reduce"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let simplb =
+    GButton.button ~label:"Simpl"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+*)
+
+   ignore(exactb#connect#clicked exact) ;
+   ignore(applyb#connect#clicked apply) ;
+   ignore(elimintrossimplb#connect#clicked elimintrossimpl) ;
+   ignore(elimtypeb#connect#clicked elimtype) ;
+   ignore(foldwhdb#connect#clicked fold_whd) ;
+   ignore(foldreduceb#connect#clicked fold_reduce) ;
+   ignore(foldsimplb#connect#clicked fold_simpl) ;
+   ignore(cutb#connect#clicked cut) ;
+   ignore(changeb#connect#clicked change) ;
+   ignore(letinb#connect#clicked letin) ;
+   ignore(ringb#connect#clicked ring) ;
+   ignore(fourierb#connect#clicked fourier) ;
+   ignore(rewritesimplb#connect#clicked rewritesimpl) ;
+   ignore(rewritebacksimplb#connect#clicked rewritebacksimpl) ;
+   ignore(replaceb#connect#clicked replace) ;
+   ignore(reflexivityb#connect#clicked reflexivity) ;
+   ignore(symmetryb#connect#clicked symmetry) ;
+   ignore(transitivityb#connect#clicked transitivity) ;
+   ignore(existsb#connect#clicked exists) ;
+   ignore(splitb#connect#clicked split) ;
+   ignore(leftb#connect#clicked left) ;
+   ignore(rightb#connect#clicked right) ;
+   ignore(assumptionb#connect#clicked assumption) ;
+   ignore(absurdb#connect#clicked absurd) ;
+   ignore(contradictionb#connect#clicked contradiction) ;
+   ignore(introsb#connect#clicked intros) ;
+   ignore(searchpatternb#connect#clicked searchPattern) ;
+   ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
+   ignore
+     ((new GObj.event_ops proofw#as_widget)#connect#button_press
+        (open_contextual_menu_for_selected_terms proofw)) ;
+   ignore(decomposeb#connect#clicked decompose) ;
+(* Zack: spostare in una toolbar
+   ignore(whdb#connect#clicked whd) ;
+   ignore(reduceb#connect#clicked reduce) ;
+   ignore(simplb#connect#clicked simpl) ;
+   ignore(clearbodyb#connect#clicked clearbody) ;
+   ignore(clearb#connect#clicked clear) ;
+   ignore(generalizeb#connect#clicked generalize) ;
+*)
+  ))
+end
+;;
+
+class empty_page =
+ let vbox1 = GPack.vbox () in
  let scrolled_window1 =
   GBin.scrolled_window ~border_width:10
    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
  let proofw =
-  GMathView.math_view ~width:400 ~height:275
+  GMathViewAux.single_selection_math_view ~width:400 ~height:275
    ~packing:(scrolled_window1#add) () in
- let hbox3 =
-  GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let exactb =
-  GButton.button ~label:"Exact"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let introsb =
-  GButton.button ~label:"Intros"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let applyb =
-  GButton.button ~label:"Apply"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let elimsimplintrosb =
-  GButton.button ~label:"ElimSimplIntros"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let elimtypeb =
-  GButton.button ~label:"ElimType"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let whdb =
-  GButton.button ~label:"Whd"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let reduceb =
-  GButton.button ~label:"Reduce"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let simplb =
-  GButton.button ~label:"Simpl"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let foldb =
-  GButton.button ~label:"Fold"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let cutb =
-  GButton.button ~label:"Cut"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let hbox4 =
-  GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let changeb =
-  GButton.button ~label:"Change"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let letinb =
-  GButton.button ~label:"Let ... In"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let ringb =
-  GButton.button ~label:"Ring"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let clearbodyb =
-  GButton.button ~label:"ClearBody"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let clearb =
-  GButton.button ~label:"Clear"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let fourierb =
-  GButton.button ~label:"Fourier"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let rewritesimplb =
-  GButton.button ~label:"RewriteSimpl ->"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let reflexivityb =
-  GButton.button ~label:"Reflexivity"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let hbox5 =
-  GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let symmetryb =
-  GButton.button ~label:"Symmetry"
-   ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
- let transitivityb =
-  GButton.button ~label:"Transitivity"
-   ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
- let leftb =
-  GButton.button ~label:"Left"
-   ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
- let rightb =
-  GButton.button ~label:"Right"
-   ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
- let assumptionb =
-  GButton.button ~label:"Assumption"
-   ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
-object
- method proofw = proofw
+object(self)
+ method proofw = (assert false : GMathViewAux.single_selection_math_view)
  method content = vbox1
- initializer
-  ignore(exactb#connect#clicked exact) ;
-  ignore(applyb#connect#clicked apply) ;
-  ignore(elimsimplintrosb#connect#clicked elimsimplintros) ;
-  ignore(elimtypeb#connect#clicked elimtype) ;
-  ignore(whdb#connect#clicked whd) ;
-  ignore(reduceb#connect#clicked reduce) ;
-  ignore(simplb#connect#clicked simpl) ;
-  ignore(foldb#connect#clicked fold) ;
-  ignore(cutb#connect#clicked cut) ;
-  ignore(changeb#connect#clicked change) ;
-  ignore(letinb#connect#clicked letin) ;
-  ignore(ringb#connect#clicked ring) ;
-  ignore(clearbodyb#connect#clicked clearbody) ;
-  ignore(clearb#connect#clicked clear) ;
-  ignore(fourierb#connect#clicked fourier) ;
-  ignore(rewritesimplb#connect#clicked rewritesimpl) ;
-  ignore(reflexivityb#connect#clicked reflexivity) ;
-  ignore(symmetryb#connect#clicked symmetry) ;
-  ignore(transitivityb#connect#clicked transitivity) ;
-  ignore(leftb#connect#clicked left) ;
-  ignore(rightb#connect#clicked right) ;
-  ignore(assumptionb#connect#clicked assumption) ;
-  ignore(introsb#connect#clicked intros) ;
- initializer
-  ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
+ method compute = (assert false : unit)
 end
 ;;
 
+let empty_page = new empty_page;;
+
 class notebook =
 object(self)
  val notebook = GPack.notebook ()
  val pages = ref []
  val mutable skip_switch_page_event = false 
+ val mutable empty = true
  method notebook = notebook
  method add_page n =
   let new_page = new page () in
-   pages := !pages @ [n,new_page] ;
+   empty <- false ;
+   pages := !pages @ [n,lazy (setgoal n),new_page] ;
    notebook#append_page
     ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
     new_page#content#coerce
- method remove_all_pages =
-  List.iter (function _ -> notebook#remove_page 0) !pages ;
+ method remove_all_pages ~skip_switch_page_event:skip =
+  if empty then
+   notebook#remove_page 0 (* let's remove the empty page *)
+  else
+   List.iter (function _ -> notebook#remove_page 0) !pages ;
   pages := [] ;
- method set_current_page n =
-  let (_,page) = List.find (function (m,_) -> m=n) !pages in
+  skip_switch_page_event <- skip
+ method set_current_page ~may_skip_switch_page_event n =
+  let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
    let new_page = notebook#page_num page#content#coerce in
-    if new_page <> notebook#current_page then
+    if may_skip_switch_page_event && new_page <> notebook#current_page then
      skip_switch_page_event <- true ;
     notebook#goto_page new_page
- method set_empty_page = self#add_page (-1)
+ method set_empty_page =
+  empty <- true ;
+  pages := [] ;
+  notebook#append_page
+   ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
+   empty_page#content#coerce
  method proofw =
-  (snd (List.nth !pages notebook#current_page))#proofw
+  let (_,_,page) = List.nth !pages notebook#current_page in
+   page#proofw
  initializer
   ignore
    (notebook#connect#switch_page
@@ -1871,8 +3244,10 @@ object(self)
        skip_switch_page_event <- false ;
        if not skip then
         try
-         let metano = fst (List.nth !pages i) in
-          setgoal metano
+         let (metano,setgoal,page) = List.nth !pages i in
+          ProofEngine.goal := Some metano ;
+          Lazy.force (page#compute) ;
+          Lazy.force setgoal
         with _ -> ()
     ))
 end
@@ -1881,12 +3256,15 @@ end
 (* Main window *)
 
 class rendering_window output (notebook : notebook) =
+ let scratch_window = new scratch_window in
  let window =
-  GWindow.window ~title:"MathML viewer" ~border_width:2
+  GWindow.window ~title:"MathML viewer" ~border_width:0
    ~allow_shrink:false () in
  let vbox_for_menu = GPack.vbox ~packing:window#add () in
  (* menus *)
- let menubar = GMenu.menu_bar ~packing:vbox_for_menu#pack () in
+ let handle_box = GBin.handle_box ~border_width:2
+  ~packing:(vbox_for_menu#pack ~padding:0) () in
+ let menubar = GMenu.menu_bar ~packing:handle_box#add () in
  let factory0 = new GMenu.factory menubar in
  let accel_group = factory0#accel_group in
  (* file menu *)
@@ -1894,20 +3272,43 @@ class rendering_window output (notebook : notebook) =
  let factory1 = new GMenu.factory file_menu ~accel_group in
  let export_to_postscript_menu_item =
   begin
+   let _ =
+    factory1#add_item "New Block of (Co)Inductive Definitions..."
+     ~key:GdkKeysyms._B ~callback:new_inductive
+   in
+   let _ =
+    factory1#add_item "New Proof or Definition..." ~key:GdkKeysyms._N
+     ~callback:new_proof
+   in
+   let reopen_menu_item =
+    factory1#add_item "Reopen a Finished Proof..." ~key:GdkKeysyms._R
+     ~callback:open_
+   in
+   let qed_menu_item =
+    factory1#add_item "Qed" ~key:GdkKeysyms._E ~callback:qed in
+   ignore (factory1#add_separator ()) ;
+   ignore
+    (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
+      ~callback:load) ;
+   let save_menu_item =
+    factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S ~callback:save
+   in
    ignore
-    (factory1#add_item "Load" ~key:GdkKeysyms._L ~callback:load) ;
-   ignore (factory1#add_item "Save" ~key:GdkKeysyms._S ~callback:save) ;
+    (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
+   ignore (!save_set_sensitive false);
+   ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
+   ignore (!qed_set_sensitive false);
    ignore (factory1#add_separator ()) ;
    let export_to_postscript_menu_item =
-    factory1#add_item "Export to PostScript..." ~key:GdkKeysyms._E
+    factory1#add_item "Export to PostScript..."
      ~callback:(export_to_postscript output) in
    ignore (factory1#add_separator ()) ;
    ignore
-    (factory1#add_item "Exit" ~key:GdkKeysyms._C ~callback:GMain.Main.quit) ;
+    (factory1#add_item "Exit" ~key:GdkKeysyms._Q ~callback:GMain.Main.quit) ;
    export_to_postscript_menu_item
   end in
  (* edit menu *)
- let edit_menu = factory0#add_submenu "Edit" in
+ let edit_menu = factory0#add_submenu "Edit Current Proof" in
  let factory2 = new GMenu.factory edit_menu ~accel_group in
  let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
  let proveit_menu_item =
@@ -1924,9 +3325,30 @@ class rendering_window output (notebook : notebook) =
     proveit_menu_item#misc#set_sensitive b ;
     focus_menu_item#misc#set_sensitive b
  in
- let _ = factory2#add_separator () in
- let _ = factory2#add_item "Qed" ~key:GdkKeysyms._Q ~callback:qed in
  let _ = !focus_and_proveit_set_sensitive false in
+ (* edit term menu *)
+ let edit_term_menu = factory0#add_submenu "Edit Term" in
+ let factory5 = new GMenu.factory edit_term_menu ~accel_group in
+ let check_menu_item =
+  factory5#add_item "Check Term" ~key:GdkKeysyms._C
+   ~callback:(check scratch_window) in
+ let _ = check_menu_item#misc#set_sensitive false in
+ (* search menu *)
+ let settings_menu = factory0#add_submenu "Search" in
+ let factory4 = new GMenu.factory settings_menu ~accel_group in
+ let _ =
+  factory4#add_item "Locate..." ~key:GdkKeysyms._T
+   ~callback:locate in
+ let searchPattern_menu_item =
+  factory4#add_item "SearchPattern..." ~key:GdkKeysyms._D
+   ~callback:completeSearchPattern in
+ let _ = searchPattern_menu_item#misc#set_sensitive false in
+ let show_menu_item =
+  factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
+ in
+ let insert_query_item =
+  factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._U
+   ~callback:insertQuery in
  (* settings menu *)
  let settings_menu = factory0#add_submenu "Settings" in
  let factory3 = new GMenu.factory settings_menu ~accel_group in
@@ -1949,44 +3371,37 @@ class rendering_window output (notebook : notebook) =
   GBin.scrolled_window ~border_width:10
    ~packing:(vbox#pack ~expand:true ~padding:5) () in
  let _ = scrolled_window0#add output#coerce in
- let hbox4 =
-  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
- let stateb =
-  GButton.button ~label:"State"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let openb =
-  GButton.button ~label:"Open"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let checkb =
-  GButton.button ~label:"Check"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let locateb =
-  GButton.button ~label:"Locate"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let searchpatternb =
-  GButton.button ~label:"SearchPattern"
-   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+ let frame =
+  GBin.frame ~label:"Insert Term"
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
  let scrolled_window1 =
-  GBin.scrolled_window ~border_width:10
-   ~packing:(vbox#pack ~expand:true ~padding:5) () in
- let inputt = GEdit.text ~editable:true ~width:400 ~height:100
-   ~packing:scrolled_window1#add () in
+  GBin.scrolled_window ~border_width:5
+   ~packing:frame#add () in
+ let inputt =
+  TermEditor'.term_editor
+   ~width:400 ~height:100 ~packing:scrolled_window1#add ()
+   ~isnotempty_callback:
+    (function b ->
+      check_menu_item#misc#set_sensitive b ;
+      searchPattern_menu_item#misc#set_sensitive b) in
  let vboxl =
   GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
  let _ =
   vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
+ let frame =
+  GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
+ in
  let outputhtml =
   GHtml.xmhtml
    ~source:"<html><body bgColor=\"white\"></body></html>"
    ~width:400 ~height: 100
    ~border_width:20
-   ~packing:(vboxl#pack ~expand:true ~padding:5)
+   ~packing:frame#add
    ~show:true () in
- let scratch_window = new scratch_window outputhtml in
 object
  method outputhtml = outputhtml
  method inputt = inputt
- method output = (output : GMathView.math_view)
+ method output = (output : GMathViewAux.single_selection_math_view)
  method notebook = notebook
  method show = window#show
  initializer
@@ -1997,19 +3412,15 @@ object
   (* signal handlers here *)
   ignore(output#connect#selection_changed
    (function elem ->
-     notebook#proofw#unload ;
      choose_selection output elem ;
      !focus_and_proveit_set_sensitive true
    )) ;
+  ignore (output#connect#click (show_in_show_window_callback output)) ;
   let settings_window = new settings_window output scrolled_window0
    export_to_postscript_menu_item (choose_selection output) in
   set_settings_window settings_window ;
+  set_outputhtml outputhtml ;
   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
-  ignore(stateb#connect#clicked state) ;
-  ignore(openb#connect#clicked open_) ;
-  ignore(checkb#connect#clicked (check scratch_window)) ;
-  ignore(locateb#connect#clicked locate) ;
-  ignore(searchpatternb#connect#clicked searchPattern) ;
   Logger.log_callback :=
    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
 end;;
@@ -2018,18 +3429,21 @@ end;;
 
 let initialize_everything () =
  let module U = Unix in
-  let output = GMathView.math_view ~width:350 ~height:280 () in
+  let output = GMathViewAux.single_selection_math_view ~width:350 ~height:280 () in
   let notebook = new notebook in
    let rendering_window' = new rendering_window output notebook in
     set_rendering_window rendering_window' ;
+    mml_of_cic_term_ref := mml_of_cic_term ;
     rendering_window'#show () ;
     GMain.Main.main ()
 ;;
 
 let _ =
  if !usedb then
- Mqint.init "dbname=helm_mowgli" ; 
-(* Mqint.init "host=mowgli.cs.unibo.it dbname=helm_mowgli user=helm" ; *)
+  begin
+   Mqint.set_database Mqint.postgres_db ;
+   Mqint.init postgresqlconnectionstring ;
+  end ;
  ignore (GtkMain.Main.init ()) ;
  initialize_everything () ;
  if !usedb then Mqint.close ();