]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/gTopLevel/gTopLevel.ml
- New interface for the MathQL interpreter (1.3 version)
[helm.git] / helm / gTopLevel / gTopLevel.ml
index f81dffc8543df69c1760235f6c12647bf3cb44f7..cfc11e921f79252b711180d13945a36e2ee46789 100644 (file)
 (*                                                                            *)
 (******************************************************************************)
 
+open Printf;;
 
-(* 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
-;;
+(* DEBUGGING *)
+
+module MQICallbacks =
+   struct
+      let log s = prerr_string s
+   end
+
+module MQI = MQueryInterpreter.Make(MQICallbacks)
 
 (* GLOBAL CONSTANTS *)
 
-let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
+let mqi_options = "" (* default MathQL interpreter options *)
+
 let xlinkns = Gdome.domString "http://www.w3.org/1999/xlink";;
 
 let htmlheader =
@@ -74,44 +74,11 @@ let prooffiletype =
   Not_found -> "/public/currentprooftype"
 ;;
 
-(*CSC: the getter should handle the innertypes, not the FS *)
-
-let innertypesfile =
- try
-  Sys.getenv "GTOPLEVEL_INNERTYPESFILE"
- with
-  Not_found -> "/public/innertypes"
-;;
-
-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"
-;;
-
-let empty_id_to_uris = ([],function _ -> None);;
-
-
 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
 
 let htmlheader_and_content = ref htmlheader;;
 
-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;;
 
@@ -172,33 +139,6 @@ Arg.parse argspec ignore ""
 
 (* MISC FUNCTIONS *)
 
-exception IllFormedUri of string;;
-
-let cic_textual_parser_uri_of_string uri' =
- try
-  (* 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)
-    )
- with
-  _ -> raise (IllFormedUri uri')
-;;
-
 let term_of_cic_textual_parser_uri uri =
  let module C = Cic in
  let module CTP = CicTextualParser0 in
@@ -254,17 +194,17 @@ let check_window outputhtml uris =
      in
       lazy 
        (let mmlwidget =
-         GMathView.math_view
+         TermViewer.sequent_viewer
           ~packing:scrolled_window#add ~width:400 ~height:280 () in
         let expr =
          let term =
-          term_of_cic_textual_parser_uri (cic_textual_parser_uri_of_string uri)
+          term_of_cic_textual_parser_uri
+           (MQueryMisc.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_tree ~dom:mml
+          mmlwidget#load_sequent [] (111,[],expr)
          with
           e ->
            output_html outputhtml
@@ -280,7 +220,7 @@ let check_window outputhtml uris =
 exception NoChoice;;
 
 let
- interactive_user_uri_choice ~selection_mode ?(ok="Ok")
+ interactive_user_uri_choice ~(selection_mode:[`SINGLE|`EXTENDED]) ?(ok="Ok")
   ?(enable_button_for_non_vars=false) ~title ~msg uris
 =
  let choices = ref [] in
@@ -298,7 +238,7 @@ let
   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 () in
+     ~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
@@ -377,7 +317,7 @@ let
         end));
   window#set_position `CENTER ;
   window#show () ;
-  GMain.Main.main () ;
+  GtkThread.main ();
   if !chosen then
    if !use_only_constants then
     List.filter
@@ -438,7 +378,7 @@ let interactive_interpretation_choice interpretations =
     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
  window#set_position `CENTER ;
  window#show () ;
- GMain.Main.main () ;
+ GtkThread.main ();
  match !chosen with
     None -> raise NoChoice
   | Some n -> n
@@ -448,121 +388,16 @@ let interactive_interpretation_choice interpretations =
 (* MISC FUNCTIONS *)
 
 (* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
+(* FG : THIS FUNCTION IS BECOMING A REAL NONSENSE                   *)
 let get_last_query = 
  let query = ref "" in
+  let out s = query := ! query ^ s in
   MQueryGenerator.set_confirm_query
-   (function q -> query := MQueryUtil.text_of_query q ; true) ;
-  function result -> !query ^ " <h1>Result:</h1> " ^ MQueryUtil.text_of_result result "<br>"
-;;
-
-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 ~explode_all =
- ("explodeall",(if explode_all then "true()" else "false()"))::
-  ["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'" ;
-   "URLs_or_URIs", "'URIs'" ;
-   "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()" ;
-  "URLs_or_URIs", "'URIs'" ;
-  "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 ~explode_all uri annobj ids_to_inner_sorts ids_to_inner_types
-=
-(*CSC: ????????????????? *)
- let xml, bodyxml =
-  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
-   ~ask_dtd_to_the_getter:true
- in
-  let input =
-   match bodyxml with
-      None -> Xml2Gdome.document_of_xml domImpl xml
-    | Some bodyxml' ->
-       Xml.pp xml (Some constanttypefile) ;
-       Xml2Gdome.document_of_xml 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 ~explode_all) in
-    output
+   (function q -> 
+    query := ""; MQueryUtil.text_of_query out q ""; true);
+  function result ->
+   out (!query ^ " <h1>Result:</h1> "); MQueryUtil.text_of_result out result "<br>";
+   !query
 ;;
 
 let
@@ -617,42 +452,150 @@ let
 
 (* CALLBACKS *)
 
-exception RefreshSequentException of exn;;
-exception RefreshProofException of exn;;
+exception OpenConjecturesStillThere;;
+exception WrongProof;;
+
+let pathname_of_annuri uristring =
+ Configuration.annotations_dir ^    
+  Str.replace_first (Str.regexp "^cic:") "" uristring
+;;
+
+let make_dirs dirpath =
+ ignore (Unix.system ("mkdir -p " ^ dirpath))
+;;
+
+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
+;;
+
+let qed () =
+ match !ProofEngine.proof with
+    None -> assert false
+  | Some (uri,[],bo,ty) ->
+     if
+      CicReduction.are_convertible []
+       (CicTypeChecker.type_of_aux' [] [] bo) ty
+     then
+      begin
+       (*CSC: Wrong: [] is just plainly wrong *)
+       let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
+       let (acic,ids_to_inner_types,ids_to_inner_sorts) =
+        (rendering_window ())#output#load_proof uri proof
+       in
+        !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
+      end
+     else
+      raise WrongProof
+  | _ -> raise OpenConjecturesStillThere
+;;
+
+  (** save an unfinished proof on the filesystem *)
+let save_unfinished_proof () =
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let (xml, bodyxml) = ProofEngine.get_current_status_as_xml () in
+ Xml.pp ~quiet:true xml (Some prooffiletype) ;
+ output_html outputhtml
+  ("<h1 color=\"Green\">Current proof type saved to " ^
+   prooffiletype ^ "</h1>") ;
+ Xml.pp ~quiet:true bodyxml (Some prooffile) ;
+ output_html outputhtml
+  ("<h1 color=\"Green\">Current proof body saved to " ^
+   prooffile ^ "</h1>")
+;;
 
-let refresh_proof (output : GMathView.math_view) =
+(* Used to typecheck the loaded proofs *)
+let typecheck_loaded_proof metasenv bo ty =
+ let module T = CicTypeChecker in
+  ignore (
+   List.fold_left
+    (fun metasenv ((_,context,ty) as conj) ->
+      ignore (T.type_of_aux' metasenv context ty) ;
+      metasenv @ [conj]
+    ) [] metasenv) ;
+  ignore (T.type_of_aux' metasenv [] ty) ;
+  ignore (T.type_of_aux' metasenv [] bo)
+;;
+
+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 MQueryMisc.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)
+    ) 
+;;
+
+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 refresh_proof (output : TermViewer.proof_viewer) =
  try
   let uri,currentproof =
    match !ProofEngine.proof with
       None -> assert false
     | Some (uri,metasenv,bo,ty) ->
-       !qed_set_sensitive (List.length metasenv = 0) ;
+       if List.length metasenv = 0 then
+        begin
+         !qed_set_sensitive true ;
+prerr_endline "CSC: ###### REFRESH_PROOF, Hbugs.clear ()" ;
+         Hbugs.clear ()
+        end
+       else
+begin
+prerr_endline "CSC: ###### REFRESH_PROOF, Hbugs.notify ()" ;
+        Hbugs.notify () ;
+end ;
        (*CSC: Wrong: [] is just plainly wrong *)
-       uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
+       uri,
+        (Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
   in
-   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 currentproof
-   in
-    let mml =
-     mml_of_cic_object ~explode_all:true uri acic ids_to_inner_sorts
-      ids_to_inner_types
-    in
-     output#load_tree mml ;
-     current_cic_infos :=
-      Some (ids_to_terms,ids_to_father_ids,ids_to_conjectures,ids_to_hypotheses)
+   ignore (output#load_proof uri currentproof)
  with
   e ->
  match !ProofEngine.proof with
     None -> assert false
   | Some (uri,metasenv,bo,ty) ->
 prerr_endline ("Offending proof: " ^ CicPp.ppobj (Cic.CurrentProof ("questa",metasenv,bo,ty,[]))) ; flush stderr ;
-   raise (RefreshProofException e)
-;;
+   raise (InvokeTactics.RefreshProofException e)
 
-let refresh_sequent ?(empty_notebook=true) notebook =
+let refresh_goals ?(empty_notebook=true) notebook =
  try
   match !ProofEngine.goal with
      None ->
@@ -669,10 +612,9 @@ let refresh_sequent ?(empty_notebook=true) notebook =
           None -> assert false
         | Some (_,metasenv,_,_) -> metasenv
       in
-      let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
-       let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
-        SequentPp.XmlPp.print_sequent metasenv currentsequent
-       in
+      let currentsequent =
+       List.find (function (m,_,_) -> m=metano) metasenv
+      in
         let regenerate_notebook () = 
          let skip_switch_page_event =
           match metasenv with
@@ -685,19 +627,15 @@ let refresh_sequent ?(empty_notebook=true) notebook =
           if empty_notebook then
            begin
             regenerate_notebook () ;
-            notebook#set_current_page ~may_skip_switch_page_event:false metano
+            notebook#set_current_page
+             ~may_skip_switch_page_event:false metano
            end
           else
            begin
-            let sequent_doc = Xml2Gdome.document_of_xml domImpl sequent_gdome in
-            let sequent_mml =
-             applyStylesheets sequent_doc sequent_styles sequent_args
-            in
-             notebook#set_current_page ~may_skip_switch_page_event:true metano;
-             notebook#proofw#load_tree ~dom:sequent_mml
-           end ;
-          current_goal_infos :=
-           Some (ids_to_terms,ids_to_father_ids,ids_to_hypotheses)
+            notebook#set_current_page
+             ~may_skip_switch_page_event:true metano ;
+            notebook#proofw#load_sequent metasenv currentsequent
+           end
  with
   e ->
 let metano =
@@ -712,155 +650,37 @@ let 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)
-;;
-
-(*
-ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
- ~name:"/home/galata/miohelm/guruguru1" ~indent:true ()) ;
-*)
-
-let mml_of_cic_term metano term =
- 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
-   let sequent_gdome,ids_to_terms,ids_to_father_ids,ids_to_hypotheses =
-    SequentPp.XmlPp.print_sequent metasenv (metano,context,term)
-   in
-    let sequent_doc =
-     Xml2Gdome.document_of_xml domImpl sequent_gdome
-    in
-     let res =
-      applyStylesheets sequent_doc sequent_styles sequent_args ;
-     in
-      current_scratch_infos :=
-       Some (term,ids_to_terms,ids_to_father_ids,ids_to_hypotheses) ;
-      res
-;;
-
-exception OpenConjecturesStillThere;;
-exception WrongProof;;
+   prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
+      raise (InvokeTactics.RefreshSequentException e)
+with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unknown."); raise (InvokeTactics.RefreshSequentException e)
+
+module InvokeTacticsCallbacks =
+ struct
+  let sequent_viewer () = (rendering_window ())#notebook#proofw
+  let term_editor () = (rendering_window ())#inputt
+  let scratch_window () = (rendering_window ())#scratch_window
+
+  let refresh_proof () =
+   let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
+    refresh_proof output
 
-let pathname_of_annuri uristring =
- Configuration.annotations_dir ^    
-  Str.replace_first (Str.regexp "^cic:") "" uristring
-;;
+  let refresh_goals () =
+   let notebook = (rendering_window ())#notebook in
+    refresh_goals notebook
 
-let make_dirs dirpath =
- ignore (Unix.system ("mkdir -p " ^ dirpath))
+  let decompose_uris_choice_callback = decompose_uris_choice_callback
+  let mk_fresh_name_callback = mk_fresh_name_callback
+  let output_html msg = output_html (outputhtml ()) msg
+ end
 ;;
+module InvokeTactics' = InvokeTactics.Make (InvokeTacticsCallbacks);;
+(* Just to initialize the Hbugs module *)
+module Ignore = Hbugs.Initialize (InvokeTactics');;
 
-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
-;;
-
-let qed () =
- match !ProofEngine.proof with
-    None -> assert false
-  | Some (uri,[],bo,ty) ->
-     if
-      CicReduction.are_convertible []
-       (CicTypeChecker.type_of_aux' [] [] bo) ty
-     then
-      begin
-       (*CSC: Wrong: [] is just plainly wrong *)
-       let proof = Cic.Constant (UriManager.name_of_uri uri,Some bo,ty,[]) in
-        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 proof
-        in
-         let mml =
-          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 ;
-          !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,
-             ids_to_hypotheses)
-      end
-     else
-      raise WrongProof
-  | _ -> raise OpenConjecturesStillThere
-;;
-
-let save () =
+  (** load an unfinished proof from filesystem *)
+let load_unfinished_proof () =
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  match !ProofEngine.proof with
-     None -> assert false
-   | Some (uri, metasenv, bo, ty) ->
-      let currentproof =
-       (*CSC: Wrong: [] is just plainly wrong *)
-       Cic.CurrentProof (UriManager.name_of_uri uri,metasenv,bo,ty,[])
-      in
-       let (acurrentproof,_,_,ids_to_inner_sorts,_,_,_) =
-        Cic2acic.acic_object_of_cic_object currentproof
-       in
-        let xml, bodyxml =
-         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
-         Xml.pp ~quiet:true xml (Some prooffiletype) ;
-         output_html outputhtml
-          ("<h1 color=\"Green\">Current proof type saved to " ^
-           prooffiletype ^ "</h1>") ;
-         Xml.pp ~quiet:true bodyxml (Some prooffile) ;
-         output_html outputhtml
-          ("<h1 color=\"Green\">Current proof body saved to " ^
-           prooffile ^ "</h1>")
-;;
-
-(* Used to typecheck the loaded proofs *)
-let typecheck_loaded_proof metasenv bo ty =
- let module T = CicTypeChecker in
-  ignore (
-   List.fold_left
-    (fun metasenv ((_,context,ty) as conj) ->
-      ignore (T.type_of_aux' metasenv context ty) ;
-      metasenv @ [conj]
-    ) [] metasenv) ;
-  ignore (T.type_of_aux' metasenv [] ty) ;
-  ignore (T.type_of_aux' metasenv [] bo)
-;;
-
-let load () =
- let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let output = ((rendering_window ())#output : GMathView.math_view) in
+ let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
  let notebook = (rendering_window ())#notebook in
   try
    match 
@@ -881,21 +701,21 @@ let load () =
                | (metano,_,_)::_ -> Some metano
              ) ;
             refresh_proof output ;
-            refresh_sequent notebook ;
+            refresh_goals 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
+            !save_set_sensitive true;
          | _ -> assert false
   with
-     RefreshSequentException e ->
+     InvokeTactics.RefreshSequentException e ->
       output_html outputhtml
        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
         "sequent: " ^ Printexc.to_string e ^ "</h1>")
-   | RefreshProofException e ->
+   | InvokeTactics.RefreshProofException e ->
       output_html outputhtml
        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
         "proof: " ^ Printexc.to_string e ^ "</h1>")
@@ -905,6 +725,8 @@ let load () =
 ;;
 
 let edit_aliases () =
+ 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
@@ -938,13 +760,20 @@ let edit_aliases () =
           let uri =
            match resolve_id v with
               None -> assert false
-            | Some uri -> uri
+            | Some (CicTextualParser0.Uri uri) -> uri
+            | Some (CicTextualParser0.Term _)
+            | Some CicTextualParser0.Implicit -> assert false
           in
-           "alias " ^ v ^ " " ^
-             (string_of_cic_textual_parser_uri uri)
+           "alias " ^
+            (match v with
+                CicTextualParser0.Id id -> id
+              | CicTextualParser0.Symbol (descr,_) ->
+                 (* CSC: To be implemented *)
+                 assert false
+            )^ " " ^ (string_of_cic_textual_parser_uri uri)
         ) dom))) ;
   window#show () ;
-  GMain.Main.main () ;
+  GtkThread.main ();
   if !chosen then
    let dom,resolve_id =
     let inputtext = input#get_chars 0 input#length in
@@ -961,9 +790,9 @@ let edit_aliases () =
      let rec aux n =
       try
        let n' = Str.search_forward regexpr inputtext n in
-        let id = Str.matched_group 2 inputtext in
+        let id = CicTextualParser0.Id (Str.matched_group 2 inputtext) in
         let uri =
-         cic_textual_parser_uri_of_string
+         MQueryMisc.cic_textual_parser_uri_of_string
           ("cic:" ^ (Str.matched_group 5 inputtext))
         in
          let dom,resolve_id = aux (n' + 1) in
@@ -971,13 +800,16 @@ let edit_aliases () =
            dom,resolve_id
           else
            id::dom,
-            (function id' -> if id = id' then Some uri else resolve_id id')
+            (function id' ->
+              if id = id' then
+               Some (CicTextualParser0.Uri uri)
+              else resolve_id id')
       with
-       Not_found -> empty_id_to_uris
+       Not_found -> TermEditor.empty_id_to_uris
      in
       aux 0
    in
-    id_to_uris := dom,resolve_id
+    id_to_uris := (dom,resolve_id)
 ;;
 
 let proveit () =
@@ -986,41 +818,22 @@ let proveit () =
  let notebook = (rendering_window ())#notebook in
  let output = (rendering_window ())#output in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  match (rendering_window ())#output#get_selection with
-    Some node ->
-     let xpath =
-      ((node : Gdome.element)#getAttributeNS
-      (*CSC: OCAML DIVERGE
-      ((element : G.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_cic_infos with
-            Some (ids_to_terms, ids_to_father_ids, _, _) ->
-             let id = xpath in
-              L.to_sequent id ids_to_terms ids_to_father_ids ;
-              refresh_proof output ;
-              refresh_sequent notebook
-          | 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>")
-         | 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>")
-       end
-  | None -> assert false (* "ERROR: No selection!!!" *)
+  try
+   output#make_sequent_of_selected_term ;
+   refresh_proof output ;
+   refresh_goals notebook
+  with
+     InvokeTactics.RefreshSequentException e ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+        "sequent: " ^ Printexc.to_string e ^ "</h1>")
+   | InvokeTactics.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 focus () =
@@ -1028,40 +841,22 @@ let focus () =
  let module G = Gdome in
  let notebook = (rendering_window ())#notebook in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
-  match (rendering_window ())#output#get_selection with
-    Some node ->
-     let xpath =
-      ((node : Gdome.element)#getAttributeNS
-      (*CSC: OCAML DIVERGE
-      ((element : G.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_cic_infos with
-            Some (ids_to_terms, ids_to_father_ids, _, _) ->
-             let id = xpath in
-              L.focus id ids_to_terms ids_to_father_ids ;
-              refresh_sequent notebook
-          | 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>")
-         | 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>")
-       end
-  | None -> assert false (* "ERROR: No selection!!!" *)
+ let output = (rendering_window ())#output in
+  try
+   output#focus_sequent_of_selected_term ;
+   refresh_goals notebook
+  with
+     InvokeTactics.RefreshSequentException e ->
+      output_html outputhtml
+       ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+        "sequent: " ^ Printexc.to_string e ^ "</h1>")
+   | InvokeTactics.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>")
 ;;
 
 exception NoPrevGoal;;
@@ -1078,9 +873,9 @@ let setgoal metano =
     | Some (_,metasenv,_,_) -> metasenv
   in
    try
-    refresh_sequent ~empty_notebook:false notebook
+    refresh_goals ~empty_notebook:false notebook
    with
-      RefreshSequentException e ->
+      InvokeTactics.RefreshSequentException e ->
        output_html outputhtml
         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
          "sequent: " ^ Printexc.to_string e ^ "</h1>")
@@ -1097,7 +892,9 @@ let
  let scrolled_window =
   GBin.scrolled_window ~border_width:10 ~packing:window#add () in
  let mmlwidget =
-  GMathView.math_view ~packing:scrolled_window#add ~width:600 ~height:400 () in
+  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 =
@@ -1110,12 +907,12 @@ let
       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
+       ApplyStylesheets.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_tree mml ;
+       mmlwidget#load_doc mml ;
     with
      e ->
       output_html outputhtml
@@ -1125,18 +922,20 @@ let
    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
-     if mmlwidget#get_action <> None then
-      mmlwidget#action_toggle
+   let show_in_show_window_callback mmlwidget (n : Gdome.element option) _ =
+    match n with
+       None -> ()
+     | Some n' ->
+        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#clicked (show_in_show_window_callback mmlwidget)
+     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
@@ -1164,7 +963,8 @@ let locate_callback id =
  let result = MQueryGenerator.locate id in
  let uris =
   List.map
-   (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
+   (function uri,_ ->
+     MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format' uri)
    result in
  let html =
   (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>")
@@ -1276,194 +1076,44 @@ let input_or_locate_uri ~title =
         locate_input#delete_text 0 (String.length id)
    )) ;
   window#show () ;
-  GMain.Main.main () ;
+  GtkThread.main ();
   match !uri with
      None -> raise NoChoice
    | Some uri -> UriManager.uri_of_string ("cic:" ^ uri)
 ;;
 
-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
-      [] ->
-       [UriManager.string_of_uri
-         (input_or_locate_uri ~title:("URI matching \"" ^ id ^ "\" unknown."))]
-    | [uri] -> [uri]
-    | _ ->
-      interactive_user_uri_choice
-       ~selection_mode:`EXTENDED
-       ~ok:"Try every selection."
-       ~enable_button_for_non_vars:true
-       ~title:"Ambiguous input."
-       ~msg:
-         ("Ambiguous input \"" ^ id ^
-          "\". Please, choose one or more interpretations:")
-       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
-   let tests_no = List.length resolve_ids in
-    if tests_no > 1 then
-     output_html (outputhtml ())
-      ("<h1>Disambiguation phase started: " ^
-        string_of_int (List.length resolve_ids) ^ " cases will be tried.") ;
-   (* 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' *)
-           let term,_,_,metasenv'' =
-            CicRefine.type_of_aux' metasenv' context expr
-           in
-            (* If metasen <> metasenv'' is a normal condition, we should *)
-            (* be prepared to apply the returned substitution to the     *)
-            (* whole current proof.                                      *)
-            if metasenv <> metasenv'' then
-             begin
-              prerr_endline
-               ("+++++ ASSERTION FAILED: " ^
-                "a refine operation should not modify the metasenv") ;
-              (* an assert would raise an exception that could be caught *)
-              exit 1
-             end ;
-            (resolve,term,metasenv'')::(filter tl)
-          with
-             CicRefine.MutCaseFixAndCofixRefineNotImplemented ->
-              (try
-                let term = CicTypeChecker.type_of_aux' metasenv' context expr in
-                 (resolve,term,metasenv')::(filter tl)
-               with _ -> filter tl
-              )
-           | _ -> filter tl
-    in
-     filter resolve_ids
-   in
-    let resolve_id',term,metasenv' =
-     match resolve_ids' with
-        [] -> raise ThereDoesNotExistAnyWellTypedInterpretationOfTheInput
-      | [resolve_id] -> resolve_id
-      | _ ->
-        let choices =
-         List.map
-          (function (resolve,_,_) ->
-            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 index = interactive_interpretation_choice choices in
-          List.nth resolve_ids' index
-    in
-     id_to_uris := known_ids @ dom', resolve_id' ;
-     metasenv',term
-;;
-
 (* A WIDGET TO ENTER CIC TERMS *)
 
-class term_editor ?packing ?width ?height ?isnotempty_callback () =
- let input = GEdit.text ~editable:true ?width ?height ?packing () in
- let _ =
-  match isnotempty_callback with
-     None -> ()
-   | Some callback ->
-      ignore(input#connect#changed (function () -> callback (input#length > 0)))
- in
-object(self)
- method coerce = input#coerce
- method reset =
-  input#delete_text 0 input#length
- (* CSC: txt is now a string, but should be of type Cic.term *)
- method set_term txt =
-  self#reset ;
-  ignore ((input#insert_text txt) ~pos:0)
- (* CSC: this method should disappear *)
- method get_as_string =
-  input#get_chars 0 input#length
- method get_metasenv_and_term ~context ~metasenv =
-  let name_context =
-   List.map
-    (function
-        Some (n,_) -> Some n
-      | None -> None
-    ) context
-  in
-   let lexbuf = Lexing.from_string (input#get_chars 0 input#length) in
-    let dom,mk_metasenv_and_expr =
-     CicTextualParserContext.main
-      ~context:name_context ~metasenv CicTextualLexer.token lexbuf
-    in
-     disambiguate_input context metasenv dom mk_metasenv_and_expr
-end
+module ChosenTermEditor  = TexTermEditor;;
+module ChosenTextualParser0 = TexCicTextualParser0;;
+(*
+module ChosenTermEditor = TermEditor;;
+module ChosenTextualParser0 = CicTextualParser0;;
+*)
+
+module Callbacks =
+ struct
+  let get_metasenv () = !ChosenTextualParser0.metasenv
+  let set_metasenv metasenv = ChosenTextualParser0.metasenv := metasenv
+
+  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 TexTermEditor' = ChosenTermEditor.Make(Callbacks);;
+
 (* OTHER FUNCTIONS *)
 
 let locate () =
- let inputt = ((rendering_window ())#inputt : term_editor) in
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
    try
     match
@@ -1484,8 +1134,9 @@ 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 : GMathView.math_view) in
+ let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
  let notebook = (rendering_window ())#notebook in
 
  let chosen = ref false in
@@ -1603,7 +1254,9 @@ let new_inductive () =
        GBin.scrolled_window ~border_width:5
         ~packing:(vbox#pack ~expand:true ~padding:0) () in
       let newinputt =
-       new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
+       TexTermEditor'.term_editor
+        ~width:400 ~height:20 ~packing:scrolled_window#add 
+        ~share_id_to_uris_with:inputt ()
         ~isnotempty_callback:
          (function b ->
            (*non_empty_type := b ;*)
@@ -1712,7 +1365,9 @@ let new_inductive () =
        GBin.scrolled_window ~border_width:5
         ~packing:(vbox#pack ~expand:true ~padding:0) () in
       let newinputt =
-       new term_editor ~width:400 ~height:20 ~packing:scrolled_window#add ()
+       TexTermEditor'.term_editor
+        ~width:400 ~height:20 ~packing:scrolled_window#add
+        ~share_id_to_uris_with:inputt ()
         ~isnotempty_callback:
          (function b ->
            (* (*non_empty_type := b ;*)
@@ -1762,7 +1417,7 @@ let new_inductive () =
           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
      )) ;
   window2#show () ;
-  GMain.Main.main () ;
+  GtkThread.main ();
   let okb_pressed = !chosen in
    chosen := false ;
    if (not okb_pressed) then
@@ -1776,7 +1431,7 @@ let new_inductive () =
   phase1 () ;
   (* No more phases left or Abort pressed *) 
   window#show () ;
-  GMain.Main.main () ;
+  GtkThread.main ();
   window#destroy () ;
   if !chosen then
    try
@@ -1809,9 +1464,9 @@ let new_inductive () =
 ;;
 
 let new_proof () =
- let inputt = ((rendering_window ())#inputt : term_editor) in
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let output = ((rendering_window ())#output : GMathView.math_view) in
+ let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
  let notebook = (rendering_window ())#notebook in
 
  let chosen = ref false in
@@ -1854,7 +1509,8 @@ let new_proof () =
    ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
  (* moved here to have visibility of the ok button *)
  let newinputt =
-  new term_editor ~width:400 ~height:100 ~packing:scrolled_window#add ()
+  TexTermEditor'.term_editor ~width:400 ~height:100 ~packing:scrolled_window#add
+   ~share_id_to_uris_with:inputt ()
    ~isnotempty_callback:
     (function b ->
       non_empty_type := b ;
@@ -1897,435 +1553,75 @@ let new_proof () =
          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
   )) ;
  window#show () ;
- GMain.Main.main () ;
+ GtkThread.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
-  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_tree ~dom:mml
- with
-  e ->
-   print_endline ("? " ^ CicPp.ppterm expr) ;
-   raise e
-;;
-
-let check scratch_window () =
- let inputt = ((rendering_window ())#inputt : 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>") ;
-;;
-
-
-(***********************)
-(*       TACTICS       *)
-(***********************)
-
-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 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 : 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 : 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 : term_editor) 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 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
-   | None ->
+     ProofEngine.proof :=
+      Some (!get_uri (), (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
+     ProofEngine.goal := Some 1 ;
+     refresh_goals notebook ;
+     refresh_proof output ;
+     !save_set_sensitive true ;
+     inputt#reset ;
+     ProofEngine.intros ~mk_fresh_name_callback () ;
+     refresh_goals notebook ;
+     refresh_proof output
+  with
+     InvokeTactics.RefreshSequentException e ->
       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 = ((rendering_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 ->
+       ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+        "sequent: " ^ Printexc.to_string e ^ "</h1>")
+   | InvokeTactics.RefreshProofException e ->
       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 ->
+       ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+        "proof: " ^ Printexc.to_string e ^ "</h1>")
+   | e ->
       output_html outputhtml
-       ("<h1 color=\"red\">No term selected</h1>")
+       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
-
-let intros = call_tactic ProofEngine.intros;;
-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_input ProofEngine.whd;;
-let reduce = call_tactic_with_goal_input ProofEngine.reduce;;
-let simpl = call_tactic_with_goal_input 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;;
-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 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_input ProofEngine.generalize;;
-let absurd = call_tactic_with_input ProofEngine.absurd;;
-let contradiction = call_tactic ProofEngine.contradiction;;
-(* Galla chiede: come dare alla tattica la lista di termini da decomporre?
-let decompose = call_tactic_with_input_and_goal_input ProofEngine.decompose;;
-*)
-
-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 check_term_in_scratch scratch_window metasenv context expr = 
+ try
+  let ty = CicTypeChecker.type_of_aux' metasenv context expr in
+  let expr = Cic.Cast (expr,ty) in
+   scratch_window#show () ;
+   scratch_window#set_term expr ;
+   scratch_window#set_context context ;
+   scratch_window#set_metasenv metasenv ;
+   scratch_window#sequent_viewer#load_sequent metasenv (111,context,expr)
+ with
+  e ->
+   print_endline ("? " ^ CicPp.ppterm expr) ;
+   raise e
 ;;
 
-
-
-(**********************)
-(*   END OF TACTICS   *)
-(**********************)
-
+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 show () =
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
@@ -2341,7 +1637,7 @@ exception NotADefinition;;
 
 let open_ () =
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
- let output = ((rendering_window ())#output : GMathView.math_view) in
+ let output = ((rendering_window ())#output : TermViewer.proof_viewer) in
  let notebook = (rendering_window ())#notebook in
    try
     let uri = input_or_locate_uri ~title:"Open" in
@@ -2357,14 +1653,14 @@ let open_ () =
       ProofEngine.proof :=
        Some (uri, metasenv, bo, ty) ;
       ProofEngine.goal := None ;
-      refresh_sequent notebook ;
+      refresh_goals notebook ;
       refresh_proof output
    with
-      RefreshSequentException e ->
+      InvokeTactics.RefreshSequentException e ->
        output_html outputhtml
         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
          "sequent: " ^ Printexc.to_string e ^ "</h1>")
-    | RefreshProofException e ->
+    | InvokeTactics.RefreshProofException e ->
        output_html outputhtml
         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
          "proof: " ^ Printexc.to_string e ^ "</h1>")
@@ -2403,8 +1699,9 @@ let show_query_results results =
      (fun ~row ~column ~event ->
        let (uristr,_) = List.nth results row in
         match
-         cic_textual_parser_uri_of_string
-          (wrong_xpointer_format_from_wrong_xpointer_format' uristr)
+         MQueryMisc.cic_textual_parser_uri_of_string
+          (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
+            uristr)
         with
            CicTextualParser0.ConUri uri
          | CicTextualParser0.VarUri uri
@@ -2594,7 +1891,7 @@ let refine_constraints (must_obj,must_rel,must_sort) =
    (okb#connect#clicked (function () -> chosen := true ; window#destroy ()));
   window#set_position `CENTER ;
   window#show () ;
-  GMain.Main.main () ;
+  GtkThread.main ();
   if !chosen then
    let chosen_must_rel =
     List.map
@@ -2621,7 +1918,7 @@ let refine_constraints (must_obj,must_rel,must_sort) =
 ;;
 
 let completeSearchPattern () =
- let inputt = ((rendering_window ())#inputt : term_editor) in
+ 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
@@ -2689,12 +1986,12 @@ let insertQuery () =
                ignore (input#insert_text text ~pos:0))) ;
    window#set_position `CENTER ;
    window#show () ;
-   GMain.Main.main () ;
+   GtkThread.main ();
    match !chosen with
       None -> ()
     | Some q ->
        let results =
-        Mqint.execute (MQueryUtil.query_of_text (Lexing.from_string q))
+        MQI.execute mqi_options (MQueryUtil.query_of_text (Lexing.from_string q))
        in
         show_query_results results
   with
@@ -2817,7 +2114,7 @@ let choose_must list_of_must only =
     (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
  window#set_position `CENTER ;
  window#show () ;
- GMain.Main.main () ;
+ GtkThread.main ();
  match !chosen with
     None -> raise NoChoice
   | Some n ->
@@ -2829,109 +2126,55 @@ let choose_must list_of_must only =
 ;;
 
 let searchPattern () =
- let inputt = ((rendering_window ())#inputt : term_editor) in
+ let inputt = ((rendering_window ())#inputt : TermEditor.term_editor) in
  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
   try
-    let metasenv =
+    let proof =
      match !ProofEngine.proof with
         None -> assert false
-      | Some (_,metasenv,_,_) -> metasenv
+      | Some proof -> proof
     in
      match !ProofEngine.goal with
-        None -> ()
+      | 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
-           (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,_ ->
-              wrong_xpointer_format_from_wrong_xpointer_format' uri
-            ) result in
-          let html =
-           " <h1>Backward Query: </h1>" ^
-          " <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'
-            in
-             filter_out uris
-           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>"
-            in
-             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 ()
+         let uris' =
+           TacticChaser.searchPattern
+            ~output_html:(output_html outputhtml) ~choose_must ()
+            ~status:(proof, metano)
+         in
+         let uri' =
+          user_uri_choice ~title:"Ambiguous input."
+          ~msg: "Many lemmas can be successfully applied. Please, choose one:"
+           uris'
+         in
+          inputt#set_term uri' ;
+          InvokeTactics'.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
@@ -2942,7 +2185,7 @@ let choose_selection
 
 (* Stuff for the widget settings *)
 
-let export_to_postscript (output : GMathView.math_view) =
+let export_to_postscript output =
  let lastdir = ref (Unix.getcwd ()) in
   function () ->
    match
@@ -2951,27 +2194,26 @@ let export_to_postscript (output : GMathView.math_view) =
    with
       None -> ()
     | Some filename ->
-       output#export_to_postscript ~filename:filename ();
+       (output :> GMathView.math_view)#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 button_set_anti_aliasing
+ button_set_transparency export_to_postscript_menu_item
  button_t1 ()
 =
  let is_set = button_t1#active in
   output#set_font_manager_type
-   (if is_set then `font_manager_t1 else `font_manager_gtk) ;
+   ~fm_type:(if is_set then `font_manager_t1 else `font_manager_gtk) ;
   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
@@ -2981,10 +2223,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
 ;;
@@ -2997,7 +2235,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 sw
  export_to_postscript_menu_item selection_changed_callback
 =
  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
@@ -3013,9 +2251,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
@@ -3050,17 +2285,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
@@ -3072,7 +2304,9 @@ end;;
 
 class scratch_window =
  let window =
-  GWindow.window ~title:"MathML viewer" ~border_width:2 () in
+  GWindow.window
+    ~title:"MathML viewer"
+    ~border_width:2 () in
  let vbox =
   GPack.vbox ~packing:window#add () in
  let hbox =
@@ -3089,20 +2323,66 @@ class scratch_window =
  let scrolled_window =
   GBin.scrolled_window ~border_width:10
    ~packing:(vbox#pack ~expand:true ~padding:5) () in
- let mmlwidget =
-  GMathView.math_view
+ let sequent_viewer =
+  TermViewer.sequent_viewer
    ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
 object(self)
- method mmlwidget = mmlwidget
+ val mutable term = Cic.Rel 1                 (* dummy value *)
+ val mutable context = ([] : Cic.context)     (* dummy value *)
+ val mutable metasenv = ([] : Cic.metasenv)   (* dummy value *)
+ method sequent_viewer = sequent_viewer
  method show () = window#misc#hide () ; window#show ()
+ method term = term
+ method set_term t = term <- t
+ method context = context
+ method set_context t = context <- t
+ method metasenv = metasenv
+ method set_metasenv t = metasenv <- t
  initializer
-  ignore(mmlwidget#connect#selection_changed (choose_selection mmlwidget)) ;
+  ignore
+   (sequent_viewer#connect#selection_changed (choose_selection sequent_viewer));
   ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
-  ignore(whdb#connect#clicked (whd_in_scratch self)) ;
-  ignore(reduceb#connect#clicked (reduce_in_scratch self)) ;
-  ignore(simplb#connect#clicked (simpl_in_scratch self))
+  ignore(whdb#connect#clicked InvokeTactics'.whd_in_scratch) ;
+  ignore(reduceb#connect#clicked InvokeTactics'.reduce_in_scratch) ;
+  ignore(simplb#connect#clicked InvokeTactics'.simpl_in_scratch)
 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:InvokeTactics'.whd in
+    let reduce_menu_item =
+     f#add_item "Reduce" ~key:GdkKeysyms._R ~callback:InvokeTactics'.reduce in
+    let simpl_menu_item =
+     f#add_item "Simpl" ~key:GdkKeysyms._S ~callback:InvokeTactics'.simpl in
+    let _ = f#add_separator () in
+    let generalize_menu_item =
+     f#add_item "Generalize"
+      ~key:GdkKeysyms._G ~callback:InvokeTactics'.generalize in
+    let _ = f#add_separator () in
+    let clear_menu_item =
+     f#add_item "Clear" ~key:GdkKeysyms._C ~callback:InvokeTactics'.clear in
+    let clearbody_menu_item =
+     f#add_item "ClearBody"
+      ~key:GdkKeysyms._B ~callback:InvokeTactics'.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)
@@ -3125,153 +2405,172 @@ object(self)
     GBin.scrolled_window ~border_width:10
      ~packing:(vbox1#pack ~expand:true ~padding:5) () in
    let proofw =
-    GMathView.math_view ~width:400 ~height:275
+    TermViewer.sequent_viewer ~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 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"
+   let ringb =
+    GButton.button ~label:"Ring"
      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
-   let elimintrossimplb =
-    GButton.button ~label:"ElimIntrosSimpl"
+   let fourierb =
+    GButton.button ~label:"Fourier"
      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
-   let elimtypeb =
-    GButton.button ~label:"ElimType"
+   let reflexivityb =
+    GButton.button ~label:"Reflexivity"
      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
-   let whdb =
-    GButton.button ~label:"Whd"
+   let symmetryb =
+    GButton.button ~label:"Symmetry"
      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
-   let reduceb =
-    GButton.button ~label:"Reduce"
+   let assumptionb =
+    GButton.button ~label:"Assumption"
      ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
-   let simplb =
-    GButton.button ~label:"Simpl"
+   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 foldwhdb =
-    GButton.button ~label:"Fold_whd"
-     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
-   let foldreduceb =
-    GButton.button ~label:"Fold_reduce"
-     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
-   let foldsimplb =
-    GButton.button ~label:"Fold_simpl"
+   let existsb =
+    GButton.button ~label:"Exists"
      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
-   let cutb =
-    GButton.button ~label:"Cut"
+   let splitb =
+    GButton.button ~label:"Split"
      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
-   let changeb =
-    GButton.button ~label:"Change"
+   let leftb =
+    GButton.button ~label:"Left"
      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
-   let letinb =
-    GButton.button ~label:"Let ... In"
+   let rightb =
+    GButton.button ~label:"Right"
      ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
-   let ringb =
-    GButton.button ~label:"Ring"
+   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 clearbodyb =
-    GButton.button ~label:"ClearBody"
+   let exactb =
+    GButton.button ~label:"Exact"
      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
-   let clearb =
-    GButton.button ~label:"Clear"
+   let introsb =
+    GButton.button ~label:"Intros"
      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
-   let fourierb =
-    GButton.button ~label:"Fourier"
+   let applyb =
+    GButton.button ~label:"Apply"
      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
-   let rewritesimplb =
-    GButton.button ~label:"RewriteSimpl ->"
+   let elimintrossimplb =
+    GButton.button ~label:"ElimIntrosSimpl"
      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
-   let rewritebacksimplb =
-    GButton.button ~label:"RewriteSimpl <-"
+   let elimtypeb =
+    GButton.button ~label:"ElimType"
      ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
-   let replaceb =
-    GButton.button ~label:"Replace"
+   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 reflexivityb =
-    GButton.button ~label:"Reflexivity"
-     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let symmetryb =
-    GButton.button ~label:"Symmetry"
-     ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let transitivityb =
-    GButton.button ~label:"Transitivity"
+   let foldsimplb =
+    GButton.button ~label:"Fold_simpl"
      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let existsb =
-    GButton.button ~label:"Exists"
+   let cutb =
+    GButton.button ~label:"Cut"
      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let splitb =
-    GButton.button ~label:"Split"
+   let changeb =
+    GButton.button ~label:"Change"
      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let leftb =
-    GButton.button ~label:"Left"
+   let letinb =
+    GButton.button ~label:"Let ... In"
      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let rightb =
-    GButton.button ~label:"Right"
+   let rewritesimplb =
+    GButton.button ~label:"RewriteSimpl ->"
      ~packing:(hbox6#pack ~expand:false ~fill:false ~padding:5) () in
-   let assumptionb =
-    GButton.button ~label:"Assumption"
+   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 generalizeb =
-    GButton.button ~label:"Generalize"
-     ~packing:(hbox7#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 contradictionb =
-    GButton.button ~label:"Contradiction"
+   let decomposeb =
+    GButton.button ~label:"Decompose"
      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
-   let searchpatternb =
-    GButton.button ~label:"SearchPattern_Apply"
+   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
+   let injectionb =
+    GButton.button ~label:"Injection"
      ~packing:(hbox7#pack ~expand:false ~fill:false ~padding:5) () in
+   let discriminateb =
+    GButton.button ~label:"Discriminate"
+     ~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(exactb#connect#clicked InvokeTactics'.exact) ;
+   ignore(applyb#connect#clicked InvokeTactics'.apply) ;
+   ignore(elimintrossimplb#connect#clicked InvokeTactics'.elimintrossimpl) ;
+   ignore(elimtypeb#connect#clicked InvokeTactics'.elimtype) ;
+   ignore(foldwhdb#connect#clicked InvokeTactics'.fold_whd) ;
+   ignore(foldreduceb#connect#clicked InvokeTactics'.fold_reduce) ;
+   ignore(foldsimplb#connect#clicked InvokeTactics'.fold_simpl) ;
+   ignore(cutb#connect#clicked InvokeTactics'.cut) ;
+   ignore(changeb#connect#clicked InvokeTactics'.change) ;
+   ignore(letinb#connect#clicked InvokeTactics'.letin) ;
+   ignore(ringb#connect#clicked InvokeTactics'.ring) ;
+   ignore(fourierb#connect#clicked InvokeTactics'.fourier) ;
+   ignore(rewritesimplb#connect#clicked InvokeTactics'.rewritesimpl) ;
+   ignore(rewritebacksimplb#connect#clicked InvokeTactics'.rewritebacksimpl) ;
+   ignore(replaceb#connect#clicked InvokeTactics'.replace) ;
+   ignore(reflexivityb#connect#clicked InvokeTactics'.reflexivity) ;
+   ignore(symmetryb#connect#clicked InvokeTactics'.symmetry) ;
+   ignore(transitivityb#connect#clicked InvokeTactics'.transitivity) ;
+   ignore(existsb#connect#clicked InvokeTactics'.exists) ;
+   ignore(splitb#connect#clicked InvokeTactics'.split) ;
+   ignore(leftb#connect#clicked InvokeTactics'.left) ;
+   ignore(rightb#connect#clicked InvokeTactics'.right) ;
+   ignore(assumptionb#connect#clicked InvokeTactics'.assumption) ;
+   ignore(absurdb#connect#clicked InvokeTactics'.absurd) ;
+   ignore(contradictionb#connect#clicked InvokeTactics'.contradiction) ;
+   ignore(introsb#connect#clicked InvokeTactics'.intros) ;
+   ignore(decomposeb#connect#clicked InvokeTactics'.decompose) ;
+   ignore(searchpatternb#connect#clicked searchPattern) ;
+   ignore(injectionb#connect#clicked InvokeTactics'.injection) ;
+   ignore(discriminateb#connect#clicked InvokeTactics'.discriminate) ;
+(* Zack: spostare in una toolbar
    ignore(whdb#connect#clicked whd) ;
    ignore(reduceb#connect#clicked reduce) ;
    ignore(simplb#connect#clicked simpl) ;
-   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(clearbodyb#connect#clicked clearbody) ;
    ignore(clearb#connect#clicked clear) ;
-   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(generalizeb#connect#clicked generalize) ;
-   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)) ;
   ))
 end
 ;;
@@ -3282,10 +2581,10 @@ class empty_page =
   GBin.scrolled_window ~border_width:10
    ~packing:(vbox1#pack ~expand:true ~padding:5) () in
  let proofw =
-  GMathView.math_view ~width:400 ~height:275
+  TermViewer.sequent_viewer ~width:400 ~height:275
    ~packing:(scrolled_window1#add) () in
 object(self)
- method proofw = (assert false : GMathView.math_view)
+ method proofw = (assert false : TermViewer.sequent_viewer)
  method content = vbox1
  method compute = (assert false : unit)
 end
@@ -3351,8 +2650,9 @@ end
 class rendering_window output (notebook : notebook) =
  let scratch_window = new scratch_window in
  let window =
-  GWindow.window ~title:"MathML viewer" ~border_width:0
-   ~allow_shrink:false () in
+  GWindow.window
+   ~title:"gTopLevel - Helm's Proof Assistant"
+   ~border_width:0 ~allow_shrink:false () in
  let vbox_for_menu = GPack.vbox ~packing:window#add () in
  (* menus *)
  let handle_box = GBin.handle_box ~border_width:2
@@ -3382,9 +2682,10 @@ class rendering_window output (notebook : notebook) =
    ignore (factory1#add_separator ()) ;
    ignore
     (factory1#add_item "Load Unfinished Proof..." ~key:GdkKeysyms._L
-      ~callback:load) ;
+      ~callback:load_unfinished_proof) ;
    let save_menu_item =
-    factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S ~callback:save
+    factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S
+      ~callback:save_unfinished_proof
    in
    ignore
     (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
@@ -3427,8 +2728,8 @@ class rendering_window output (notebook : notebook) =
    ~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 search_menu = factory0#add_submenu "Search" in
+ let factory4 = new GMenu.factory search_menu ~accel_group in
  let _ =
   factory4#add_item "Locate..." ~key:GdkKeysyms._T
    ~callback:locate in
@@ -3440,8 +2741,15 @@ class rendering_window output (notebook : notebook) =
   factory4#add_item "Show..." ~key:GdkKeysyms._H ~callback:show
  in
  let insert_query_item =
-  factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._U
+  factory4#add_item "Insert Query (Experts Only)..." ~key:GdkKeysyms._Y
    ~callback:insertQuery in
+ (* hbugs menu *)
+ let hbugs_menu = factory0#add_submenu "HBugs" in
+ let factory6 = new GMenu.factory hbugs_menu ~accel_group in
+ let toggle_hbugs_menu_item =
+  factory6#add_check_item
+    ~active:false ~key:GdkKeysyms._F5 ~callback:Hbugs.toggle "HBugs enabled"
+ in
  (* settings menu *)
  let settings_menu = factory0#add_submenu "Settings" in
  let factory3 = new GMenu.factory settings_menu ~accel_group in
@@ -3471,7 +2779,8 @@ class rendering_window output (notebook : notebook) =
   GBin.scrolled_window ~border_width:5
    ~packing:frame#add () in
  let inputt =
-  new term_editor ~width:400 ~height:100 ~packing:scrolled_window1#add ()
+  TexTermEditor'.term_editor
+   ~width:400 ~height:100 ~packing:scrolled_window1#add ()
    ~isnotempty_callback:
     (function b ->
       check_menu_item#misc#set_sensitive b ;
@@ -3493,7 +2802,8 @@ class rendering_window output (notebook : notebook) =
 object
  method outputhtml = outputhtml
  method inputt = inputt
- method output = (output : GMathView.math_view)
+ method output = (output : TermViewer.proof_viewer)
+ method scratch_window = scratch_window
  method notebook = notebook
  method show = window#show
  initializer
@@ -3507,7 +2817,7 @@ object
      choose_selection output elem ;
      !focus_and_proveit_set_sensitive true
    )) ;
-  ignore (output#connect#clicked (show_in_show_window_callback output)) ;
+  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 ;
@@ -3521,22 +2831,32 @@ end;;
 
 let initialize_everything () =
  let module U = Unix in
-  let output = GMathView.math_view ~width:350 ~height:280 () in
+  let output = TermViewer.proof_viewer ~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 print_error_as_html prefix msg =
+     output_html (outputhtml ())
+      ("<h1 color=\"red\">" ^ prefix ^ msg ^ "</h1>")
+    in
+     Gdome_xslt.setErrorCallback (Some (print_error_as_html "XSLT Error: "));
+     Gdome_xslt.setDebugCallback
+      (Some (print_error_as_html "XSLT Debug Message: "));
+     rendering_window'#show () ;
+(*      Hbugs.toggle true; *)
+     GtkThread.main ()
 ;;
 
-let _ =
- if !usedb then
-  begin
-   Mqint.set_database Mqint.postgres_db ;
-   Mqint.init postgresqlconnectionstring ;
-  end ;
+let main () =
+ if !usedb then ignore (MQI.init mqi_options) ;
  ignore (GtkMain.Main.init ()) ;
  initialize_everything () ;
- if !usedb then Mqint.close ();
+ if !usedb then MQI.close mqi_options;
+ Hbugs.quit ()
 ;;
+
+try
+  Sys.catch_break true;
+  main ();
+with Sys.Break -> ()  (* exit nicely, invoking at_exit functions *)
+