]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/gTopLevel/gTopLevel.ml
Rendering of InductiveDefinitions, Variables and Axioms implemented.
[helm.git] / helm / gTopLevel / gTopLevel.ml
index 47c416d8b60b9ad472098d883f4cacf2f2026345..58e785dec3ef37c5ff6cf8dfc4dad4d2819b3ba5 100644 (file)
@@ -1,4 +1,4 @@
-(* Copyright (C) 2000, HELM Team.
+(* Copyright (C) 2000-2002, HELM Team.
  * 
  * This file is part of HELM, an Hypertextual, Electronic
  * Library of Mathematics, developed at the Computer Science
 (*                                                                            *)
 (******************************************************************************)
 
+
+(* CSC: quick fix: a function from [uri#xpointer(path)] to [uri#path] *)
+let wrong_xpointer_format_from_wrong_xpointer_format' uri =
+ try
+  let index_sharp =  String.index uri '#' in
+  let index_rest = index_sharp + 10 in
+   let baseuri = String.sub uri 0 index_sharp in
+   let rest = String.sub uri index_rest (String.length uri - index_rest - 1) in
+    baseuri ^ "#" ^ rest
+ with Not_found -> uri
+;;
+
 (* GLOBAL CONSTANTS *)
 
 let helmns = Gdome.domString "http://www.cs.unibo.it/helm";;
@@ -47,6 +59,26 @@ let htmlfooter =
  "</html>"
 ;;
 
+(*
+let prooffile = "/home/tassi/miohelm/tmp/currentproof";;
+let prooffile = "/public/sacerdot/currentproof";;
+*)
+
+let prooffile = "/public/sacerdot/currentproof";;
+let prooffiletype = "/public/sacerdot/currentprooftype";;
+
+(*CSC: the getter should handle the innertypes, not the FS *)
+(*
+let innertypesfile = "/home/tassi/miohelm/tmp/innertypes";;
+let innertypesfile = "/public/sacerdot/innertypes";;
+*)
+
+let innertypesfile = "/public/sacerdot/innertypes";;
+let constanttypefile = "/public/sacerdot/constanttype";;
+
+let empty_id_to_uris = ([],function _ -> None);;
+
+
 (* GLOBAL REFERENCES (USED BY CALLBACKS) *)
 
 let htmlheader_and_content = ref htmlheader;;
@@ -55,9 +87,460 @@ 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;;
+
+let set_rendering_window,rendering_window =
+ let rendering_window_ref = ref None in
+  (function rw -> rendering_window_ref := Some rw),
+  (function () ->
+    match !rendering_window_ref with
+       None -> raise RenderingWindowsNotInitialized
+     | Some rw -> rw
+  )
+;;
+
+exception SettingsWindowsNotInitialized;;
+
+let set_settings_window,settings_window =
+ let settings_window_ref = ref None in
+  (function rw -> settings_window_ref := Some rw),
+  (function () ->
+    match !settings_window_ref with
+       None -> raise SettingsWindowsNotInitialized
+     | Some rw -> rw
+  )
+;;
+
+exception OutputHtmlNotInitialized;;
+
+let set_outputhtml,outputhtml =
+ let outputhtml_ref = ref None in
+  (function rw -> outputhtml_ref := Some rw),
+  (function () ->
+    match !outputhtml_ref with
+       None -> raise OutputHtmlNotInitialized
+     | Some outputhtml -> outputhtml
+  )
+;;
+
+exception QedSetSensitiveNotInitialized;;
+let qed_set_sensitive =
+ ref (function _ -> raise QedSetSensitiveNotInitialized)
+;;
+
+exception SaveSetSensitiveNotInitialized;;
+let save_set_sensitive =
+ ref (function _ -> raise SaveSetSensitiveNotInitialized)
+;;
+
+(* COMMAND LINE OPTIONS *)
+
+let usedb = ref true
+
+let argspec =
+  [
+    "-nodb", Arg.Clear usedb, "disable use of MathQL DB"
+  ]
+in
+Arg.parse argspec ignore ""
+
 
 (* MISC FUNCTIONS *)
 
+let cic_textual_parser_uri_of_string uri' =
+ (* Constant *)
+ if String.sub uri' (String.length uri' - 4) 4 = ".con" then
+  CicTextualParser0.ConUri (UriManager.uri_of_string uri')
+ else
+  if String.sub uri' (String.length uri' - 4) 4 = ".var" then
+   CicTextualParser0.VarUri (UriManager.uri_of_string uri')
+  else
+   (try
+     (* Inductive Type *)
+     let uri'',typeno = CicTextualLexer.indtyuri_of_uri uri' in
+      CicTextualParser0.IndTyUri (uri'',typeno)
+    with
+     _ ->
+      (* Constructor of an Inductive Type *)
+      let uri'',typeno,consno =
+       CicTextualLexer.indconuri_of_uri uri'
+      in
+       CicTextualParser0.IndConUri (uri'',typeno,consno)
+   )
+;;
+
+let term_of_cic_textual_parser_uri uri =
+ let module C = Cic in
+ let module CTP = CicTextualParser0 in
+  match uri with
+     CTP.ConUri uri -> C.Const (uri,[])
+   | CTP.VarUri uri -> C.Var (uri,[])
+   | CTP.IndTyUri (uri,tyno) -> C.MutInd (uri,tyno,[])
+   | CTP.IndConUri (uri,tyno,consno) -> C.MutConstruct (uri,tyno,consno,[])
+;;
+
+let string_of_cic_textual_parser_uri uri =
+ let module C = Cic in
+ let module CTP = CicTextualParser0 in
+  let uri' =
+   match uri with
+      CTP.ConUri uri -> UriManager.string_of_uri uri
+    | CTP.VarUri uri -> UriManager.string_of_uri uri
+    | CTP.IndTyUri (uri,tyno) ->
+       UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1)
+    | CTP.IndConUri (uri,tyno,consno) ->
+       UriManager.string_of_uri uri ^ "#1/" ^ string_of_int (tyno + 1) ^ "/" ^
+        string_of_int consno
+  in
+   (* 4 = String.length "cic:" *)
+   String.sub uri' 4 (String.length uri' - 4)
+;;
+
+let output_html outputhtml msg =
+ htmlheader_and_content := !htmlheader_and_content ^ msg ;
+ outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
+ outputhtml#set_topline (-1)
+;;
+
+(* UTILITY FUNCTIONS TO DISAMBIGUATE AN URI *)
+
+(* Check window *)
+
+let check_window outputhtml uris =
+ let window =
+  GWindow.window
+   ~width:800 ~modal:true ~title:"Check" ~border_width:2 () in
+ let notebook =
+  GPack.notebook ~scrollable:true ~packing:window#add () in
+ window#show () ;
+ let render_terms =
+  List.map
+   (function uri ->
+     let scrolled_window =
+      GBin.scrolled_window ~border_width:10
+       ~packing:
+         (notebook#append_page ~tab_label:((GMisc.label ~text:uri ())#coerce))
+       ()
+     in
+      lazy 
+       (let mmlwidget =
+         GMathView.math_view
+          ~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)
+         in
+          (Cic.Cast (term, CicTypeChecker.type_of_aux' [] [] term))
+        in
+         try
+          let mml = !mml_of_cic_term_ref 111 expr in
+prerr_endline ("### " ^ CicPp.ppterm expr) ;
+           mmlwidget#load_tree ~dom:mml
+         with
+          e ->
+           output_html outputhtml
+            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+       )
+   ) uris
+ in
+  ignore
+   (notebook#connect#switch_page
+     (function i -> Lazy.force (List.nth render_terms i)))
+;;
+
+exception NoChoice;;
+
+let
+ interactive_user_uri_choice ~selection_mode ?(ok="Ok") ~title ~msg uris
+=
+ let choices = ref [] in
+ let chosen = ref false in
+ let window =
+  GWindow.dialog ~modal:true ~title ~width:600 () in
+ let lMessage =
+  GMisc.label ~text:msg
+   ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10
+   ~packing:(window#vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let clist =
+  let expected_height = 18 * List.length uris in
+   let height = if expected_height > 400 then 400 else expected_height in
+    GList.clist ~columns:1 ~packing:scrolled_window#add
+     ~height ~selection_mode () in
+ let _ = List.map (function x -> clist#append [x]) uris in
+ let hbox2 =
+  GPack.hbox ~border_width:0
+   ~packing:(window#vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let explain_label =
+  GMisc.label ~text:"None of the above. Try this one:"
+   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
+ let manual_input =
+  GEdit.entry ~editable:true
+   ~packing:(hbox2#pack ~expand:true ~fill:true ~padding:5) () in
+ let hbox =
+  GPack.hbox ~border_width:0 ~packing:window#action_area#add () in
+ let okb =
+  GButton.button ~label:ok
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let _ = okb#misc#set_sensitive false in
+ let checkb =
+  GButton.button ~label:"Check"
+   ~packing:(hbox#pack ~padding:5) () in
+ let _ = checkb#misc#set_sensitive false in
+ let cancelb =
+  GButton.button ~label:"Abort"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ (* actions *)
+ let check_callback () =
+  assert (List.length !choices > 0) ;
+  check_window (outputhtml ()) !choices
+ in
+  ignore (window#connect#destroy GMain.Main.quit) ;
+  ignore (cancelb#connect#clicked window#destroy) ;
+  ignore
+   (okb#connect#clicked (function () -> chosen := true ; window#destroy ())) ;
+  ignore (checkb#connect#clicked check_callback) ;
+  ignore
+   (clist#connect#select_row
+     (fun ~row ~column ~event ->
+       checkb#misc#set_sensitive true ;
+       okb#misc#set_sensitive true ;
+       choices := (List.nth uris row)::!choices)) ;
+  ignore
+   (clist#connect#unselect_row
+     (fun ~row ~column ~event ->
+       choices :=
+        List.filter (function uri -> uri != (List.nth uris row)) !choices)) ;
+  ignore
+   (manual_input#connect#changed
+     (fun _ ->
+       if manual_input#text = "" then
+        begin
+         choices := [] ;
+         checkb#misc#set_sensitive false ;
+         okb#misc#set_sensitive false ;
+         clist#misc#set_sensitive true
+        end
+       else
+        begin
+         choices := [manual_input#text] ;
+         clist#unselect_all () ;
+         checkb#misc#set_sensitive true ;
+         okb#misc#set_sensitive true ;
+         clist#misc#set_sensitive false
+        end));
+  window#set_position `CENTER ;
+  window#show () ;
+  GMain.Main.main () ;
+  if !chosen && List.length !choices > 0 then
+   !choices
+  else
+   raise NoChoice
+;;
+
+let interactive_interpretation_choice interpretations =
+ let chosen = ref None in
+ let window =
+  GWindow.window
+   ~modal:true ~title:"Ambiguous well-typed input." ~border_width:2 () in
+ let vbox = GPack.vbox ~packing:window#add () in
+ let lMessage =
+  GMisc.label
+   ~text:
+    ("Ambiguous input since there are many well-typed interpretations." ^
+     " Please, choose one of them.")
+   ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let notebook =
+  GPack.notebook ~scrollable:true
+   ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let _ =
+  List.map
+   (function interpretation ->
+     let clist =
+      let expected_height = 18 * List.length interpretation in
+       let height = if expected_height > 400 then 400 else expected_height in
+        GList.clist ~columns:2 ~packing:notebook#append_page ~height
+         ~titles:["id" ; "URI"] ()
+     in
+      ignore
+       (List.map
+         (function (id,uri) ->
+           let n = clist#append [id;uri] in
+            clist#set_row ~selectable:false n
+         ) interpretation
+       ) ;
+      clist#columns_autosize ()
+   ) interpretations in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let okb =
+  GButton.button ~label:"Ok"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let cancelb =
+  GButton.button ~label:"Abort"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ (* actions *)
+ ignore (window#connect#destroy GMain.Main.quit) ;
+ ignore (cancelb#connect#clicked window#destroy) ;
+ ignore
+  (okb#connect#clicked
+    (function () -> chosen := Some notebook#current_page ; window#destroy ())) ;
+ window#set_position `CENTER ;
+ window#show () ;
+ GMain.Main.main () ;
+ match !chosen with
+    None -> raise NoChoice
+  | Some n -> n
+;;
+
+(* MISC FUNCTIONS *)
+
+(* CSC: IMPERATIVE AND NOT VERY CLEAN, TO GET THE LAST ISSUED QUERY *)
+let get_last_query = 
+ let query = ref "" 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 register_alias (id,uri) =
+ let dom,resolve_id = !id_to_uris in
+  id_to_uris :=
+   (if List.mem id dom then dom else id::dom),
+    function id' -> if id' = id then Some uri else resolve_id id'
+;;  
+
+let locate_one_id id =
+ let result = MQueryGenerator.locate id in
+ let uris =
+  List.map
+   (function uri,_ ->
+     wrong_xpointer_format_from_wrong_xpointer_format' uri
+   ) result in
+ let html= " <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>" in
+  output_html (rendering_window ())#outputhtml html ;
+  let uris' =
+   match uris with
+      [] ->
+       (match
+         (GToolbox.input_string ~title:"Unknown input"
+          ("No URI matching \"" ^ id ^ "\" found. Please enter its URI"))
+        with
+           None -> raise NoChoice
+         | Some uri -> ["cic:" ^ uri]
+       )
+    | [uri] -> [uri]
+    | _ ->
+      interactive_user_uri_choice
+       ~selection_mode:`EXTENDED
+       ~ok:"Try every selection."
+       ~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' *)
+           ignore
+            (CicTypeChecker.type_of_aux' metasenv context expr) ;
+           resolve::(filter tl)
+          with
+           _ -> filter tl
+    in
+     filter resolve_ids
+   in
+    let resolve_id' =
+     match resolve_ids' with
+        [] -> raise ThereDoesNotExistAnyWellTypedInterpretationOfTheInput
+      | [resolve_id] -> resolve_id
+      | _ ->
+        let choices =
+         List.map
+          (function resolve ->
+            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' ;
+     mk_metasenv_and_expr resolve_id'
+;;
+
 let domImpl = Gdome.domImplementation ();;
 
 let parseStyle name =
@@ -140,18 +623,25 @@ let applyStylesheets input styles args =
 ;;
 
 let mml_of_cic_object uri annobj ids_to_inner_sorts ids_to_inner_types =
- let xml =
-  Cic2Xml.print_object uri ids_to_inner_sorts annobj 
+(*CSC: ????????????????? *)
+ let xml, bodyxml =
+  Cic2Xml.print_object uri ~ids_to_inner_sorts annobj 
  in
  let xmlinnertypes =
-  Cic2Xml.print_inner_types uri ids_to_inner_sorts
-   ids_to_inner_types
+  Cic2Xml.print_inner_types uri ~ids_to_inner_sorts
+   ~ids_to_inner_types
  in
-  let input = Xml2Gdome.document_of_xml domImpl xml 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 "/public/fguidi/innertypes") ;
+   Xml.pp xmlinnertypes (Some innertypesfile) ;
    let output = applyStylesheets input mml_styles mml_args in
     output
 ;;
@@ -168,10 +658,13 @@ let refresh_proof (output : GMathView.math_view) =
    match !ProofEngine.proof with
       None -> assert false
     | Some (uri,metasenv,bo,ty) ->
-       uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty))
+       !qed_set_sensitive (List.length metasenv = 0) ;
+       (*CSC: Wrong: [] is just plainly wrong *)
+       uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty, []))
   in
    let
-    (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,ids_to_inner_types)
+    (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
@@ -179,54 +672,104 @@ let refresh_proof (output : GMathView.math_view) =
      mml_of_cic_object 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)
+     current_cic_infos :=
+      Some (ids_to_terms,ids_to_father_ids,ids_to_conjectures,ids_to_hypotheses)
  with
-  e -> raise (RefreshProofException e)
+  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)
 ;;
 
-let refresh_sequent (proofw : GMathView.math_view) =
+let refresh_sequent ?(empty_notebook=true) notebook =
  try
   match !ProofEngine.goal with
-     None -> proofw#unload
-   | Some (_,currentsequent) ->
+     None ->
+      if empty_notebook then
+       begin 
+        notebook#remove_all_pages ~skip_switch_page_event:false ;
+        notebook#set_empty_page
+       end
+      else
+       notebook#proofw#unload
+   | Some metano ->
       let metasenv =
        match !ProofEngine.proof with
           None -> assert false
         | Some (_,metasenv,_,_) -> metasenv
       in
-       let sequent_gdome,ids_to_terms,ids_to_father_ids =
+      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 sequent_doc =
-         Xml2Gdome.document_of_xml domImpl sequent_gdome
-        in
-         let sequent_mml =
-          applyStylesheets sequent_doc sequent_styles sequent_args
+        let regenerate_notebook () = 
+         let skip_switch_page_event =
+          match metasenv with
+             (m,_,_)::_ when m = metano -> false
+           | _ -> true
          in
-          proofw#load_tree ~dom:sequent_mml ;
-          current_goal_infos := Some (ids_to_terms,ids_to_father_ids)
+          notebook#remove_all_pages ~skip_switch_page_event ;
+          List.iter (function (m,_,_) -> notebook#add_page m) metasenv ;
+        in
+          if empty_notebook then
+           begin
+            regenerate_notebook () ;
+            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)
  with
-  e -> raise (RefreshSequentException e)
+  e ->
+let metano =
+  match !ProofEngine.goal with
+     None -> assert false
+   | Some m -> m
+in
+let metasenv =
+ match !ProofEngine.proof with
+    None -> assert false
+  | Some (_,metasenv,_,_) -> metasenv
+in
+try
+let currentsequent = List.find (function (m,_,_) -> m=metano) metasenv in
+prerr_endline ("Offending sequent: " ^ SequentPp.TextualPp.print_sequent currentsequent) ; flush stderr ;
+   raise (RefreshSequentException e)
+with Not_found -> prerr_endline ("Offending sequent " ^ string_of_int metano ^ " unkown."); raise (RefreshSequentException e)
 ;;
 
 (*
 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
- ~name:"/public/sacerdot/guruguru1" ~indent:true ()) ;
+ ~name:"/home/galata/miohelm/guruguru1" ~indent:true ()) ;
 *)
 
-let mml_of_cic_term term =
+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 (_,(context,_)) -> context
+   | Some metano ->
+      let (_,canonical_context,_) =
+       List.find (function (m,_,_) -> m=metano) metasenv
+      in
+       canonical_context
  in
-  let metasenv =
-   match !ProofEngine.proof with
-      None -> []
-    | Some (_,metasenv,_,_) -> metasenv
-  in
-   let sequent_gdome,ids_to_terms,ids_to_father_ids =
-    SequentPp.XmlPp.print_sequent metasenv (context,term)
+   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
@@ -234,30 +777,25 @@ let mml_of_cic_term term =
      let res =
       applyStylesheets sequent_doc sequent_styles sequent_args ;
      in
-      current_scratch_infos := Some (term,ids_to_terms,ids_to_father_ids) ;
+      current_scratch_infos :=
+       Some (term,ids_to_terms,ids_to_father_ids,ids_to_hypotheses) ;
       res
 ;;
 
-let output_html outputhtml msg =
- htmlheader_and_content := !htmlheader_and_content ^ msg ;
- outputhtml#source (!htmlheader_and_content ^ htmlfooter) ;
- outputhtml#set_topline (-1)
-;;
-
 (***********************)
 (*       TACTICS       *)
 (***********************)
 
-let call_tactic tactic rendering_window () =
- let proofw = (rendering_window#proofw : GMathView.math_view) in
- let output = (rendering_window#output : GMathView.math_view) in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
+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 proofw ;
+    refresh_sequent notebook ;
     refresh_proof output
    with
       RefreshSequentException e ->
@@ -266,14 +804,14 @@ let call_tactic tactic rendering_window () =
          "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
        ProofEngine.proof := savedproof ;
        ProofEngine.goal := savedgoal ;
-       refresh_sequent proofw
+       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 proofw ;
+       refresh_sequent notebook ;
        refresh_proof output
     | e ->
        output_html outputhtml
@@ -283,11 +821,11 @@ let call_tactic tactic rendering_window () =
   end
 ;;
 
-let call_tactic_with_input tactic rendering_window () =
- let proofw = (rendering_window#proofw : GMathView.math_view) in
- let output = (rendering_window#output : GMathView.math_view) in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
- let inputt = (rendering_window#inputt : GEdit.text) in
+let call_tactic_with_input tactic () =
+ let notebook = (rendering_window ())#notebook in
+ let output = ((rendering_window ())#output : GMathView.math_view) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
  let savedproof = !ProofEngine.proof in
  let savedgoal  = !ProofEngine.goal in
 (*CSC: Gran cut&paste da sotto... *)
@@ -299,26 +837,43 @@ let call_tactic_with_input tactic rendering_window () =
        None -> assert false
      | Some (curi,_,_,_) -> curi
    in
+   let uri,metasenv,bo,ty =
+    match !ProofEngine.proof with
+       None -> assert false
+     | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
+   in
+   let canonical_context =
+    match !ProofEngine.goal with
+       None -> assert false
+     | Some metano ->
+        let (_,canonical_context,_) =
+         List.find (function (m,_,_) -> m=metano) metasenv
+        in
+         canonical_context
+   in
    let context =
     List.map
      (function
-         ProofEngine.Definition (n,_)
-       | ProofEngine.Declaration (n,_) -> n)
-     (match !ProofEngine.goal with
-         None -> assert false
-       | Some (_,(ctx,_)) -> ctx
-     )
+         Some (n,_) -> Some n
+       | None -> None
+     ) canonical_context
    in
     try
      while true do
       match
-       CicTextualParserContext.main curi context CicTextualLexer.token lexbuf
+       CicTextualParserContext.main context metasenv CicTextualLexer.token
+        lexbuf register_alias
       with
          None -> ()
-       | Some expr ->
-          tactic expr ;
-          refresh_sequent proofw ;
-          refresh_proof output
+       | Some (dom,mk_metasenv_and_expr) ->
+          let (metasenv',expr) =
+           disambiguate_input canonical_context metasenv dom
+            mk_metasenv_and_expr
+          in
+           ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
+           tactic expr ;
+           refresh_sequent notebook ;
+           refresh_proof output
      done
     with
        CicTextualParser0.Eof ->
@@ -329,14 +884,14 @@ let call_tactic_with_input tactic rendering_window () =
           "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
         ProofEngine.proof := savedproof ;
         ProofEngine.goal := savedgoal ;
-        refresh_sequent proofw
+        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 proofw ;
+        refresh_sequent notebook ;
         refresh_proof output
      | e ->
         output_html outputhtml
@@ -345,15 +900,15 @@ let call_tactic_with_input tactic rendering_window () =
         ProofEngine.goal := savedgoal ;
 ;;
 
-let call_tactic_with_goal_input tactic rendering_window () =
+let call_tactic_with_goal_input tactic () =
  let module L = LogicalOperations in
  let module G = Gdome in
-  let proofw = (rendering_window#proofw : GMathView.math_view) in
-  let output = (rendering_window#output : GMathView.math_view) in
-  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) 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 proofw#get_selection with
+   match notebook#proofw#get_selection with
      Some node ->
       let xpath =
        ((node : Gdome.element)#getAttributeNS
@@ -365,11 +920,11 @@ let call_tactic_with_goal_input tactic rendering_window () =
         begin
          try
           match !current_goal_infos with
-             Some (ids_to_terms, ids_to_father_ids) ->
+             Some (ids_to_terms, ids_to_father_ids,_) ->
               let id = xpath in
                tactic (Hashtbl.find ids_to_terms id) ;
-               refresh_sequent rendering_window#proofw ;
-               refresh_proof rendering_window#output
+               refresh_sequent notebook ;
+               refresh_proof output
            | None -> assert false (* "ERROR: No current term!!!" *)
          with
             RefreshSequentException e ->
@@ -378,14 +933,14 @@ let call_tactic_with_goal_input tactic rendering_window () =
                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
              ProofEngine.proof := savedproof ;
              ProofEngine.goal := savedgoal ;
-             refresh_sequent proofw
+             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 proofw ;
+             refresh_sequent notebook ;
              refresh_proof output
           | e ->
              output_html outputhtml
@@ -398,16 +953,16 @@ let call_tactic_with_goal_input tactic rendering_window () =
        ("<h1 color=\"red\">No term selected</h1>")
 ;;
 
-let call_tactic_with_input_and_goal_input tactic rendering_window () =
+let call_tactic_with_input_and_goal_input tactic () =
  let module L = LogicalOperations in
  let module G = Gdome in
-  let proofw = (rendering_window#proofw : GMathView.math_view) in
-  let output = (rendering_window#output : GMathView.math_view) in
-  let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
-  let inputt = (rendering_window#inputt : GEdit.text) in
+  let notebook = (rendering_window ())#notebook in
+  let output = ((rendering_window ())#output : GMathView.math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let inputt = ((rendering_window ())#inputt : GEdit.text) in
   let savedproof = !ProofEngine.proof in
   let savedgoal  = !ProofEngine.goal in
-   match proofw#get_selection with
+   match notebook#proofw#get_selection with
      Some node ->
       let xpath =
        ((node : Gdome.element)#getAttributeNS
@@ -419,7 +974,7 @@ let call_tactic_with_input_and_goal_input tactic rendering_window () =
         begin
          try
           match !current_goal_infos with
-             Some (ids_to_terms, ids_to_father_ids) ->
+             Some (ids_to_terms, ids_to_father_ids,_) ->
               let id = xpath in
                (* Let's parse the input *)
                let inputlen = inputt#length in
@@ -430,29 +985,44 @@ let call_tactic_with_input_and_goal_input tactic rendering_window () =
                     None -> assert false
                   | Some (curi,_,_,_) -> curi
                 in
+                let uri,metasenv,bo,ty =
+                 match !ProofEngine.proof with
+                    None -> assert false
+                  | Some (uri,metasenv,bo,ty) -> uri,metasenv,bo,ty
+                in
+                let canonical_context =
+                 match !ProofEngine.goal with
+                    None -> assert false
+                  | Some metano ->
+                     let (_,canonical_context,_) =
+                      List.find (function (m,_,_) -> m=metano) metasenv
+                     in
+                      canonical_context in
                 let context =
                  List.map
                   (function
-                      ProofEngine.Definition (n,_)
-                    | ProofEngine.Declaration (n,_) -> n)
-                  (match !ProofEngine.goal with
-                      None -> assert false
-                    | Some (_,(ctx,_)) -> ctx
-                  )
+                      Some (n,_) -> Some n
+                    | None -> None
+                  ) canonical_context
                 in
                  begin
                   try
                    while true do
                     match
-                     CicTextualParserContext.main curi context
-                      CicTextualLexer.token lexbuf
+                     CicTextualParserContext.main context metasenv
+                      CicTextualLexer.token lexbuf register_alias
                     with
                        None -> ()
-                     | Some expr ->
-                        tactic ~goal_input:(Hashtbl.find ids_to_terms id)
-                         ~input:expr ;
-                        refresh_sequent proofw ;
-                        refresh_proof output
+                     | Some (dom,mk_metasenv_and_expr) ->
+                        let (metasenv',expr) =
+                         disambiguate_input canonical_context metasenv dom
+                          mk_metasenv_and_expr
+                        in
+                         ProofEngine.proof := Some (uri,metasenv',bo,ty) ;
+                         tactic ~goal_input:(Hashtbl.find ids_to_terms id)
+                          ~input:expr ;
+                         refresh_sequent notebook ;
+                         refresh_proof output
                    done
                   with
                      CicTextualParser0.Eof ->
@@ -466,14 +1036,14 @@ let call_tactic_with_input_and_goal_input tactic rendering_window () =
                "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
              ProofEngine.proof := savedproof ;
              ProofEngine.goal := savedgoal ;
-             refresh_sequent proofw
+             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 proofw ;
+             refresh_sequent notebook ;
              refresh_proof output
           | e ->
              output_html outputhtml
@@ -506,10 +1076,10 @@ let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
          try
           match !current_scratch_infos with
              (* term is the whole goal in the scratch_area *)
-             Some (term,ids_to_terms, ids_to_father_ids) ->
+             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 expr 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!!!" *)
@@ -523,39 +1093,84 @@ let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
        ("<h1 color=\"red\">No term selected</h1>")
 ;;
 
-let intros rendering_window = call_tactic ProofEngine.intros rendering_window;;
-let exact rendering_window =
- call_tactic_with_input ProofEngine.exact rendering_window
-;;
-let apply rendering_window =
- call_tactic_with_input ProofEngine.apply rendering_window
-;;
-let elimintros rendering_window =
- call_tactic_with_input ProofEngine.elim_intros rendering_window
-;;
-let whd rendering_window =
- call_tactic_with_goal_input ProofEngine.whd rendering_window
-;;
-let reduce rendering_window =
- call_tactic_with_goal_input ProofEngine.reduce rendering_window
-;;
-let simpl rendering_window =
- call_tactic_with_goal_input ProofEngine.simpl rendering_window
-;;
-let fold rendering_window =
- call_tactic_with_input ProofEngine.fold rendering_window
-;;
-let cut rendering_window =
- call_tactic_with_input ProofEngine.cut rendering_window
-;;
-let change rendering_window =
- call_tactic_with_input_and_goal_input ProofEngine.change rendering_window
-;;
-let letin rendering_window =
- call_tactic_with_input ProofEngine.letin rendering_window
+let call_tactic_with_hypothesis_input tactic () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let notebook = (rendering_window ())#notebook in
+  let output = ((rendering_window ())#output : GMathView.math_view) in
+  let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match notebook#proofw#get_selection with
+     Some node ->
+      let xpath =
+       ((node : Gdome.element)#getAttributeNS
+         ~namespaceURI:helmns
+         ~localName:(G.domString "xref"))#to_string
+      in
+       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+       else
+        begin
+         try
+          match !current_goal_infos with
+             Some (_,_,ids_to_hypotheses) ->
+              let id = xpath in
+               tactic (Hashtbl.find ids_to_hypotheses id) ;
+               refresh_sequent notebook ;
+               refresh_proof output
+           | None -> assert false (* "ERROR: No current term!!!" *)
+         with
+            RefreshSequentException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook
+          | RefreshProofException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent notebook ;
+             refresh_proof output
+          | e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+        end
+   | None ->
+      output_html outputhtml
+       ("<h1 color=\"red\">No term selected</h1>")
 ;;
 
 
+let intros = call_tactic ProofEngine.intros;;
+let exact = call_tactic_with_input ProofEngine.exact;;
+let apply = call_tactic_with_input ProofEngine.apply;;
+let elimsimplintros = call_tactic_with_input ProofEngine.elim_simpl_intros;;
+let elimtype = call_tactic_with_input ProofEngine.elim_type;;
+let whd = call_tactic_with_goal_input ProofEngine.whd;;
+let reduce = call_tactic_with_goal_input ProofEngine.reduce;;
+let simpl = call_tactic_with_goal_input ProofEngine.simpl;;
+let fold = call_tactic_with_input ProofEngine.fold;;
+let cut = call_tactic_with_input ProofEngine.cut;;
+let change = call_tactic_with_input_and_goal_input ProofEngine.change;;
+let letin = call_tactic_with_input ProofEngine.letin;;
+let ring = call_tactic ProofEngine.ring;;
+let clearbody = call_tactic_with_hypothesis_input ProofEngine.clearbody;;
+let clear = call_tactic_with_hypothesis_input ProofEngine.clear;;
+let fourier = call_tactic ProofEngine.fourier;;
+let rewritesimpl = call_tactic_with_input ProofEngine.rewrite_simpl;;
+let reflexivity = call_tactic ProofEngine.reflexivity;;
+let symmetry = call_tactic ProofEngine.symmetry;;
+let transitivity = call_tactic_with_input ProofEngine.transitivity;;
+let left = call_tactic ProofEngine.left;;
+let right = call_tactic ProofEngine.right;;
+let assumption = call_tactic ProofEngine.assumption;;
+
 let whd_in_scratch scratch_window =
  call_tactic_with_goal_input_in_scratch ProofEngine.whd_in_scratch
   scratch_window
@@ -578,7 +1193,7 @@ let simpl_in_scratch scratch_window =
 exception OpenConjecturesStillThere;;
 exception WrongProof;;
 
-let save rendering_window () =
+let qed () =
  match !ProofEngine.proof with
     None -> assert false
   | Some (uri,[],bo,ty) ->
@@ -588,29 +1203,184 @@ let save rendering_window () =
      then
       begin
        (*CSC: Wrong: [] is just plainly wrong *)
-       let proof = Cic.Definition (UriManager.name_of_uri uri,bo,ty,[]) in
+       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_inner_types,ids_to_conjectures,ids_to_hypotheses)
         =
          Cic2acic.acic_object_of_cic_object proof
         in
          let mml =
           mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types
          in
-          (rendering_window#output : GMathView.math_view)#load_tree mml ;
-          current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
+          ((rendering_window ())#output : GMathView.math_view)#load_tree mml ;
+          current_cic_infos :=
+           Some
+            (ids_to_terms,ids_to_father_ids,ids_to_conjectures,
+             ids_to_hypotheses)
       end
      else
       raise WrongProof
   | _ -> raise OpenConjecturesStillThere
 ;;
 
-let proveit rendering_window () =
+(*????
+let dtdname = "http://www.cs.unibo.it/helm/dtd/cic.dtd";;
+let dtdname = "/home/tassi/miohelm/helm/dtd/cic.dtd";;
+*)
+let dtdname = "/projects/helm/V7_mowgli/dtd/cic.dtd";;
+
+let save () =
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  match !ProofEngine.proof with
+     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 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 notebook = (rendering_window ())#notebook in
+  try
+   let uri = UriManager.uri_of_string "cic:/dummy.con" in
+    match CicParser.obj_of_xml prooffiletype (Some prooffile) with
+       Cic.CurrentProof (_,metasenv,bo,ty,_) ->
+        typecheck_loaded_proof metasenv bo ty ;
+        ProofEngine.proof :=
+         Some (uri, metasenv, bo, ty) ;
+        ProofEngine.goal :=
+         (match metasenv with
+             [] -> None
+           | (metano,_,_)::_ -> Some metano
+         ) ;
+        refresh_proof output ;
+        refresh_sequent notebook ;
+         output_html outputhtml
+          ("<h1 color=\"Green\">Current proof type loaded from " ^
+            prooffiletype ^ "</h1>") ;
+         output_html outputhtml
+          ("<h1 color=\"Green\">Current proof body loaded from " ^
+            prooffile ^ "</h1>") ;
+        !save_set_sensitive true
+     | _ -> assert false
+  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 edit_aliases () =
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
+ let dom,resolve_id = !id_to_uris in
+  let inputlen = inputt#length in
+   inputt#delete_text 0 inputlen ;
+   let _ =
+    inputt#insert_text ~pos:0
+     (String.concat "\n"
+       (List.map
+         (function v ->
+           let uri =
+            match resolve_id v with
+               None -> assert false
+             | Some uri -> uri
+           in
+            "alias " ^ v ^ " " ^
+              (string_of_cic_textual_parser_uri uri)
+         ) dom))
+   in
+    id_to_uris := empty_id_to_uris
+;;
+
+let proveit () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+ 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!!!" *)
+;;
+
+let focus () =
  let module L = LogicalOperations in
  let module G = Gdome in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
-  match rendering_window#output#get_selection with
+ 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
@@ -625,11 +1395,10 @@ let proveit rendering_window () =
        begin
         try
          match !current_cic_infos with
-            Some (ids_to_terms, ids_to_father_ids) ->
+            Some (ids_to_terms, ids_to_father_ids, _, _) ->
              let id = xpath in
-              if L.to_sequent id ids_to_terms ids_to_father_ids then
-               refresh_proof rendering_window#output ;
-              refresh_sequent rendering_window#proofw
+              L.focus id ids_to_terms ids_to_father_ids ;
+              refresh_sequent notebook
           | None -> assert false (* "ERROR: No current term!!!" *)
         with
            RefreshSequentException e ->
@@ -647,34 +1416,57 @@ let proveit rendering_window () =
   | None -> assert false (* "ERROR: No selection!!!" *)
 ;;
 
+exception NoPrevGoal;;
+exception NoNextGoal;;
+
+let setgoal metano =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+ let notebook = (rendering_window ())#notebook in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+  let metasenv =
+   match !ProofEngine.proof with
+      None -> assert false
+    | Some (_,metasenv,_,_) -> metasenv
+  in
+   try
+    refresh_sequent ~empty_notebook:false notebook
+   with
+      RefreshSequentException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "sequent: " ^ Printexc.to_string e ^ "</h1>")
+    | e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+;;
+
 exception NotADefinition;;
 
-let open_ rendering_window () =
- let inputt = (rendering_window#inputt : GEdit.text) in
- let oldinputt = (rendering_window#oldinputt : GEdit.text) in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
- let output = (rendering_window#output : GMathView.math_view) in
- let proofw = (rendering_window#proofw : GMathView.math_view) in
+let open_ () =
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let output = ((rendering_window ())#output : GMathView.math_view) in
+ let notebook = (rendering_window ())#notebook in
   let inputlen = inputt#length in
-  let input = inputt#get_chars 0 inputlen ^ "\n" in
+  let input = inputt#get_chars 0 inputlen in
    try
     let uri = UriManager.uri_of_string ("cic:" ^ input) in
      CicTypeChecker.typecheck uri ;
      let metasenv,bo,ty =
-      match CicEnvironment.get_cooked_obj uri with
-         Cic.Definition (_,bo,ty,_) -> [],bo,ty
-       | Cic.CurrentProof (_,metasenv,bo,ty) -> metasenv,bo,ty
-       | Cic.Axiom _
+      match CicEnvironment.get_cooked_obj uri with
+         Cic.Constant (_,Some bo,ty,_) -> [],bo,ty
+       | Cic.CurrentProof (_,metasenv,bo,ty,_) -> metasenv,bo,ty
+       | Cic.Constant _
        | Cic.Variable _
        | Cic.InductiveDefinition _ -> raise NotADefinition
      in
       ProofEngine.proof :=
        Some (uri, metasenv, bo, ty) ;
       ProofEngine.goal := None ;
-      refresh_sequent proofw ;
+      refresh_sequent notebook ;
       refresh_proof output ;
-      inputt#delete_text 0 inputlen ;
-      ignore(oldinputt#insert_text input oldinputt#length)
+      inputt#delete_text 0 inputlen
    with
       RefreshSequentException e ->
        output_html outputhtml
@@ -689,12 +1481,11 @@ let open_ rendering_window () =
         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
-let state rendering_window () =
- let inputt = (rendering_window#inputt : GEdit.text) in
- let oldinputt = (rendering_window#oldinputt : GEdit.text) in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
- let output = (rendering_window#output : GMathView.math_view) in
- let proofw = (rendering_window#proofw : GMathView.math_view) in
+let state () =
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let output = ((rendering_window ())#output : GMathView.math_view) in
+ let notebook = (rendering_window ())#notebook in
   let inputlen = inputt#length in
   let input = inputt#get_chars 0 inputlen ^ "\n" in
    (* Do something interesting *)
@@ -702,21 +1493,27 @@ let state rendering_window () =
     try
      while true do
       (* Execute the actions *)
-      match CicTextualParser.main CicTextualLexer.token lexbuf with
+      match
+       CicTextualParserContext.main [] [] CicTextualLexer.token
+        lexbuf register_alias
+      with
          None -> ()
-       | Some expr ->
-          let _  = CicTypeChecker.type_of_aux' [] [] expr in
-           ProofEngine.proof :=
-            Some (UriManager.uri_of_string "cic:/dummy.con",
-                   [1,expr], Cic.Meta 1, expr) ;
-           ProofEngine.goal := Some (1,([],expr)) ;
-           refresh_sequent proofw ;
-           refresh_proof output ;
+       | Some (dom,mk_metasenv_and_expr) ->
+          let metasenv,expr =
+           disambiguate_input [] [] dom mk_metasenv_and_expr
+          in
+           let _  = CicTypeChecker.type_of_aux' metasenv [] expr in
+            ProofEngine.proof :=
+             Some (UriManager.uri_of_string "cic:/dummy.con",
+                    (1,[],expr)::metasenv, Cic.Meta (1,[]), expr) ;
+            ProofEngine.goal := Some 1 ;
+            refresh_sequent notebook ;
+            refresh_proof output ;
+            !save_set_sensitive true
      done
     with
        CicTextualParser0.Eof ->
-        inputt#delete_text 0 inputlen ;
-        ignore(oldinputt#insert_text input oldinputt#length)
+        inputt#delete_text 0 inputlen
      | RefreshSequentException e ->
         output_html outputhtml
          ("<h1 color=\"red\">Exception raised during the refresh of the " ^
@@ -730,11 +1527,22 @@ let state rendering_window () =
          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
-let check rendering_window scratch_window () =
- let inputt = (rendering_window#inputt : GEdit.text) in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
- let output = (rendering_window#output : GMathView.math_view) in
- let proofw = (rendering_window#proofw : GMathView.math_view) in
+let check_term_in_scratch scratch_window metasenv context expr = 
+ try
+  let ty  = CicTypeChecker.type_of_aux' metasenv context expr in
+   let mml = mml_of_cic_term 111 (Cic.Cast (expr,ty)) in
+prerr_endline ("### " ^ CicPp.ppterm expr ^ " ==> " ^ CicPp.ppterm ty) ;
+    scratch_window#show () ;
+    scratch_window#mmlwidget#load_tree ~dom:mml
+ with
+  e ->
+   print_endline ("? " ^ CicPp.ppterm expr) ;
+   raise e
+;;
+
+let check scratch_window () =
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
   let inputlen = inputt#length in
   let input = inputt#get_chars 0 inputlen ^ "\n" in
   let curi,metasenv =
@@ -742,39 +1550,37 @@ let check rendering_window scratch_window () =
       None -> UriManager.uri_of_string "cic:/dummy.con", []
     | Some (curi,metasenv,_,_) -> curi,metasenv
   in
-  let ciccontext,names_context =
+  let context,names_context =
    let context =
     match !ProofEngine.goal with
        None -> []
-     | Some (_,(ctx,_)) -> ctx
+     | Some metano ->
+        let (_,canonical_context,_) =
+         List.find (function (m,_,_) -> m=metano) metasenv
+        in
+         canonical_context
    in
-    ProofEngine.cic_context_of_named_context context,
-     List.map
-      (function
-          ProofEngine.Declaration (n,_)
-        | ProofEngine.Definition (n,_) -> n
-      ) context
+    context,
+    List.map
+     (function
+         Some (n,_) -> Some n
+       | None -> None
+     ) context
   in
-   (* Do something interesting *)
    let lexbuf = Lexing.from_string input in
     try
      while true do
       (* Execute the actions *)
       match
-       CicTextualParserContext.main curi names_context CicTextualLexer.token
-        lexbuf
+       CicTextualParserContext.main names_context metasenv CicTextualLexer.token
+        lexbuf register_alias
       with
          None -> ()
-       | Some expr ->
-          try
-           let ty  = CicTypeChecker.type_of_aux' metasenv ciccontext expr in
-            let mml = mml_of_cic_term (Cic.Cast (expr,ty)) in
-             scratch_window#show () ;
-             scratch_window#mmlwidget#load_tree ~dom:mml
-          with
-           e ->
-            print_endline ("? " ^ CicPp.ppterm expr) ;
-            raise e
+       | Some (dom,mk_metasenv_and_expr) ->
+          let (metasenv',expr) =
+           disambiguate_input context metasenv dom mk_metasenv_and_expr
+          in
+           check_term_in_scratch scratch_window metasenv' context expr
      done
     with
        CicTextualParser0.Eof -> ()
@@ -783,28 +1589,129 @@ let check rendering_window scratch_window () =
         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
-let locate rendering_window () =
- let inputt = (rendering_window#inputt : GEdit.text) in
- let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
+exception NoObjectsLocated;;
+
+let user_uri_choice ~title ~msg uris =
+ let uri =
+  match uris with
+     [] -> raise NoObjectsLocated
+   | [uri] -> uri
+   | uris ->
+      match
+       interactive_user_uri_choice ~selection_mode:`SINGLE ~title ~msg uris
+      with
+         [uri] -> uri
+       | _ -> assert false
+ in
+  String.sub uri 4 (String.length uri - 4)
+;;
+
+let locate () =
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
   let inputlen = inputt#length in
   let input = inputt#get_chars 0 inputlen in
-   try   
-    output_html outputhtml (Mquery.locate input) ;
-    inputt#delete_text 0 inputlen 
+   try
+    match Str.split (Str.regexp "[ \t]+") input with
+       [] -> ()
+     | head :: tail ->
+        inputt#delete_text 0 inputlen ;
+        let result = MQueryGenerator.locate head in
+       let uris =
+         List.map
+          (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
+          result in
+       let html = (" <h1>Locate Query: </h1><pre>" ^ get_last_query result ^ "</pre>") in
+         output_html outputhtml html ;
+         let uri' =
+          user_uri_choice ~title:"Ambiguous input."
+           ~msg:
+             ("Ambiguous input \"" ^ head ^
+              "\". Please, choose one interpetation:")
+           uris
+         in
+          ignore ((inputt#insert_text uri') ~pos:0)
    with
-    e -> 
+    e ->
      output_html outputhtml
       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
 ;;
 
-let backward rendering_window () =
-   let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
-   let result =
-      match !ProofEngine.goal with
-         | None -> ""
-         | Some (_, (_, t)) -> (Mquery.backward t)
-      in 
-   output_html outputhtml result
+let searchPattern () =
+ let outputhtml = ((rendering_window ())#outputhtml : GHtml.xmhtml) in
+ let inputt = ((rendering_window ())#inputt : GEdit.text) in
+  let inputlen = inputt#length in
+  let input = inputt#get_chars 0 inputlen in
+  let level = int_of_string input in
+  let metasenv =
+   match !ProofEngine.proof with
+      None -> assert false
+    | Some (_,metasenv,_,_) -> metasenv
+  in
+   try
+    match !ProofEngine.goal with
+       None -> ()
+     | Some metano ->
+        let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
+         let result = MQueryGenerator.searchPattern metasenv ey ty level in
+         let uris =
+          List.map
+           (function uri,_ -> wrong_xpointer_format_from_wrong_xpointer_format' uri)
+           result in
+         let html =
+         " <h1>Backward Query: </h1>" ^
+         " <h2>Levels: </h2> " ^
+          MQueryGenerator.string_of_levels
+            (MQueryGenerator.levels_of_term metasenv ey ty) "<br>" ^
+          " <pre>" ^ get_last_query result ^ "</pre>"
+         in
+          output_html outputhtml html ;
+          let uris',exc =
+           let rec filter_out =
+            function
+               [] -> [],""
+             | uri::tl ->
+                let tl',exc = filter_out tl in
+                 try
+                  if
+                   ProofEngine.can_apply
+                    (term_of_cic_textual_parser_uri
+                     (cic_textual_parser_uri_of_string uri))
+                  then
+                   uri::tl',exc
+                  else
+                   tl',exc
+                 with
+                  e ->
+                   let exc' =
+                    "<h1 color=\"red\"> ^ Exception raised trying to apply " ^
+                     uri ^ ": " ^ Printexc.to_string e ^ " </h1>" ^ exc
+                   in
+                    tl',exc'
+           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#delete_text 0 inputlen ;
+             ignore ((inputt#insert_text uri') ~pos:0)
+    with
+     e -> 
+      output_html outputhtml 
+       ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+;;
       
 let choose_selection
      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
@@ -833,12 +1740,20 @@ let choose_selection
 
 (* Stuff for the widget settings *)
 
-let export_to_postscript (output : GMathView.math_view) () =
- output#export_to_postscript ~filename:"output.ps" ();
+let export_to_postscript (output : GMathView.math_view) =
+ let lastdir = ref (Unix.getcwd ()) in
+  function () ->
+   match
+    GToolbox.select_file ~title:"Export to PostScript"
+     ~dir:lastdir ~filename:"screenshot.ps" ()
+   with
+      None -> ()
+    | Some filename ->
+       output#export_to_postscript ~filename:filename ();
 ;;
 
 let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
- button_set_kerning button_set_transparency button_export_to_postscript
+ button_set_kerning button_set_transparency export_to_postscript_menu_item
  button_t1 ()
 =
  let is_set = button_t1#active in
@@ -849,14 +1764,14 @@ let activate_t1 (output : GMathView.math_view) button_set_anti_aliasing
     button_set_anti_aliasing#misc#set_sensitive true ;
     button_set_kerning#misc#set_sensitive true ;
     button_set_transparency#misc#set_sensitive true ;
-    button_export_to_postscript#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 ;
-    button_export_to_postscript#misc#set_sensitive false ;
+    export_to_postscript_menu_item#misc#set_sensitive false ;
    end
 ;;
 
@@ -881,7 +1796,7 @@ let set_log_verbosity output log_verbosity_spinb () =
 ;;
 
 class settings_window (output : GMathView.math_view) sw
button_export_to_postscript selection_changed_callback
export_to_postscript_menu_item selection_changed_callback
 =
  let settings_window = GWindow.window ~title:"GtkMathView settings" () in
  let vbox =
@@ -938,7 +1853,7 @@ object(self)
   (* Signals connection *)
   ignore(button_t1#connect#clicked
    (activate_t1 output button_set_anti_aliasing button_set_kerning
-    button_set_transparency button_export_to_postscript button_t1)) ;
+    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));
@@ -987,43 +1902,289 @@ object(self)
   ignore(simplb#connect#clicked (simpl_in_scratch self))
 end;;
 
+class page () =
+ let vbox1 = GPack.vbox () in
+object(self)
+ val mutable proofw_ref = None
+ val mutable compute_ref = None
+ method proofw =
+  Lazy.force self#compute ;
+  match proofw_ref with
+     None -> assert false
+   | Some proofw -> proofw
+ method content = vbox1
+ method compute =
+  match compute_ref with
+     None -> assert false
+   | Some compute -> compute
+ initializer
+  compute_ref <-
+   Some (lazy (
+   let scrolled_window1 =
+    GBin.scrolled_window ~border_width:10
+     ~packing:(vbox1#pack ~expand:true ~padding:5) () in
+   let proofw =
+    GMathView.math_view ~width:400 ~height:275
+     ~packing:(scrolled_window1#add) () in
+   let _ = proofw_ref <- Some proofw in
+   let hbox3 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let exactb =
+    GButton.button ~label:"Exact"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let introsb =
+    GButton.button ~label:"Intros"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let applyb =
+    GButton.button ~label:"Apply"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let elimsimplintrosb =
+    GButton.button ~label:"ElimSimplIntros"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let elimtypeb =
+    GButton.button ~label:"ElimType"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let whdb =
+    GButton.button ~label:"Whd"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let reduceb =
+    GButton.button ~label:"Reduce"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let simplb =
+    GButton.button ~label:"Simpl"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let foldb =
+    GButton.button ~label:"Fold"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let cutb =
+    GButton.button ~label:"Cut"
+     ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+   let hbox4 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let changeb =
+    GButton.button ~label:"Change"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let letinb =
+    GButton.button ~label:"Let ... In"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let ringb =
+    GButton.button ~label:"Ring"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let clearbodyb =
+    GButton.button ~label:"ClearBody"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let clearb =
+    GButton.button ~label:"Clear"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let fourierb =
+    GButton.button ~label:"Fourier"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let rewritesimplb =
+    GButton.button ~label:"RewriteSimpl ->"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let reflexivityb =
+    GButton.button ~label:"Reflexivity"
+     ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+   let hbox5 =
+    GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
+   let symmetryb =
+    GButton.button ~label:"Symmetry"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let transitivityb =
+    GButton.button ~label:"Transitivity"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let leftb =
+    GButton.button ~label:"Left"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let rightb =
+    GButton.button ~label:"Right"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   let assumptionb =
+    GButton.button ~label:"Assumption"
+     ~packing:(hbox5#pack ~expand:false ~fill:false ~padding:5) () in
+   ignore(exactb#connect#clicked exact) ;
+   ignore(applyb#connect#clicked apply) ;
+   ignore(elimsimplintrosb#connect#clicked elimsimplintros) ;
+   ignore(elimtypeb#connect#clicked elimtype) ;
+   ignore(whdb#connect#clicked whd) ;
+   ignore(reduceb#connect#clicked reduce) ;
+   ignore(simplb#connect#clicked simpl) ;
+   ignore(foldb#connect#clicked fold) ;
+   ignore(cutb#connect#clicked cut) ;
+   ignore(changeb#connect#clicked change) ;
+   ignore(letinb#connect#clicked letin) ;
+   ignore(ringb#connect#clicked ring) ;
+   ignore(clearbodyb#connect#clicked clearbody) ;
+   ignore(clearb#connect#clicked clear) ;
+   ignore(fourierb#connect#clicked fourier) ;
+   ignore(rewritesimplb#connect#clicked rewritesimpl) ;
+   ignore(reflexivityb#connect#clicked reflexivity) ;
+   ignore(symmetryb#connect#clicked symmetry) ;
+   ignore(transitivityb#connect#clicked transitivity) ;
+   ignore(leftb#connect#clicked left) ;
+   ignore(rightb#connect#clicked right) ;
+   ignore(assumptionb#connect#clicked assumption) ;
+   ignore(introsb#connect#clicked intros) ;
+   ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
+  ))
+end
+;;
+
+class empty_page =
+ let vbox1 = GPack.vbox () in
+ let scrolled_window1 =
+  GBin.scrolled_window ~border_width:10
+   ~packing:(vbox1#pack ~expand:true ~padding:5) () in
+ let proofw =
+  GMathView.math_view ~width:400 ~height:275
+   ~packing:(scrolled_window1#add) () in
+object(self)
+ method proofw = (assert false : GMathView.math_view)
+ method content = vbox1
+ method compute = (assert false : unit)
+end
+;;
+
+let empty_page = new empty_page;;
+
+class notebook =
+object(self)
+ val notebook = GPack.notebook ()
+ val pages = ref []
+ val mutable skip_switch_page_event = false 
+ val mutable empty = true
+ method notebook = notebook
+ method add_page n =
+  let new_page = new page () in
+   empty <- false ;
+   pages := !pages @ [n,lazy (setgoal n),new_page] ;
+   notebook#append_page
+    ~tab_label:((GMisc.label ~text:("?" ^ string_of_int n) ())#coerce)
+    new_page#content#coerce
+ method remove_all_pages ~skip_switch_page_event:skip =
+  if empty then
+   notebook#remove_page 0 (* let's remove the empty page *)
+  else
+   List.iter (function _ -> notebook#remove_page 0) !pages ;
+  pages := [] ;
+  skip_switch_page_event <- skip
+ method set_current_page ~may_skip_switch_page_event n =
+  let (_,_,page) = List.find (function (m,_,_) -> m=n) !pages in
+   let new_page = notebook#page_num page#content#coerce in
+    if may_skip_switch_page_event && new_page <> notebook#current_page then
+     skip_switch_page_event <- true ;
+    notebook#goto_page new_page
+ method set_empty_page =
+  empty <- true ;
+  pages := [] ;
+  notebook#append_page
+   ~tab_label:((GMisc.label ~text:"No proof in progress" ())#coerce)
+   empty_page#content#coerce
+ method proofw =
+  let (_,_,page) = List.nth !pages notebook#current_page in
+   page#proofw
+ initializer
+  ignore
+   (notebook#connect#switch_page
+    (function i ->
+      let skip = skip_switch_page_event in
+       skip_switch_page_event <- false ;
+       if not skip then
+        try
+         let (metano,setgoal,page) = List.nth !pages i in
+          ProofEngine.goal := Some metano ;
+          Lazy.force (page#compute) ;
+          Lazy.force setgoal
+        with _ -> ()
+    ))
+end
+;;
+
 (* Main window *)
 
-class rendering_window output proofw (label : GMisc.label) =
+class rendering_window output (notebook : notebook) =
  let window =
-  GWindow.window ~title:"MathML viewer" ~border_width:2 () in
+  GWindow.window ~title:"MathML viewer" ~border_width:2
+   ~allow_shrink:false () in
+ let vbox_for_menu = GPack.vbox ~packing:window#add () in
+ (* menus *)
+ let menubar = GMenu.menu_bar ~packing:vbox_for_menu#pack () in
+ let factory0 = new GMenu.factory menubar in
+ let accel_group = factory0#accel_group in
+ (* file menu *)
+ let file_menu = factory0#add_submenu "File" in
+ let factory1 = new GMenu.factory file_menu ~accel_group in
+ let export_to_postscript_menu_item =
+  begin
+   ignore
+    (factory1#add_item "Load Unfinished Proof" ~key:GdkKeysyms._L
+      ~callback:load) ;
+   let save_menu_item =
+    factory1#add_item "Save Unfinished Proof" ~key:GdkKeysyms._S ~callback:save
+   in
+   let qed_menu_item =
+    factory1#add_item "Qed" ~key:GdkKeysyms._Q ~callback:qed in
+   ignore
+    (save_set_sensitive := function b -> save_menu_item#misc#set_sensitive b);
+   ignore (!save_set_sensitive false);
+   ignore (qed_set_sensitive:=function b -> qed_menu_item#misc#set_sensitive b);
+   ignore (!qed_set_sensitive false);
+   ignore (factory1#add_separator ()) ;
+   let export_to_postscript_menu_item =
+    factory1#add_item "Export to PostScript..." ~key:GdkKeysyms._E
+     ~callback:(export_to_postscript output) in
+   ignore (factory1#add_separator ()) ;
+   ignore
+    (factory1#add_item "Exit" ~key:GdkKeysyms._C ~callback:GMain.Main.quit) ;
+   export_to_postscript_menu_item
+  end in
+ (* edit menu *)
+ let edit_menu = factory0#add_submenu "Edit" in
+ let factory2 = new GMenu.factory edit_menu ~accel_group in
+ let focus_and_proveit_set_sensitive = ref (function _ -> assert false) in
+ let proveit_menu_item =
+  factory2#add_item "Prove It" ~key:GdkKeysyms._I
+   ~callback:(function () -> proveit ();!focus_and_proveit_set_sensitive false)
+ in
+ let focus_menu_item =
+  factory2#add_item "Focus" ~key:GdkKeysyms._F
+   ~callback:(function () -> focus () ; !focus_and_proveit_set_sensitive false)
+ in
+ let _ =
+  focus_and_proveit_set_sensitive :=
+   function b ->
+    proveit_menu_item#misc#set_sensitive b ;
+    focus_menu_item#misc#set_sensitive b
+ in
+ let _ = !focus_and_proveit_set_sensitive false in
+ (* settings menu *)
+ let settings_menu = factory0#add_submenu "Settings" in
+ let factory3 = new GMenu.factory settings_menu ~accel_group in
+ let _ =
+  factory3#add_item "Edit Aliases" ~key:GdkKeysyms._A
+   ~callback:edit_aliases in
+ let _ = factory3#add_separator () in
+ let _ =
+  factory3#add_item "MathML Widget Preferences..." ~key:GdkKeysyms._P
+   ~callback:(function _ -> (settings_window ())#show ()) in
+ (* accel group *)
+ let _ = window#add_accel_group accel_group in
+ (* end of menus *)
  let hbox0 =
-  GPack.hbox ~packing:window#add () in
+  GPack.hbox
+   ~packing:(vbox_for_menu#pack ~expand:true ~fill:true ~padding:5) () in
  let vbox =
-  GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
- let _ = vbox#pack ~expand:false ~fill:false ~padding:5 label#coerce in
+  GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
  let scrolled_window0 =
   GBin.scrolled_window ~border_width:10
    ~packing:(vbox#pack ~expand:true ~padding:5) () in
  let _ = scrolled_window0#add output#coerce in
- let hbox1 =
-  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
- let settingsb =
-  GButton.button ~label:"Settings"
-   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let button_export_to_postscript =
-  GButton.button ~label:"export_to_postscript"
-  ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let saveb =
-  GButton.button ~label:"Save"
-   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let closeb =
-  GButton.button ~label:"Close"
-   ~packing:(hbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let hbox2 =
-  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
- let proveitb =
-  GButton.button ~label:"Prove It"
-   ~packing:(hbox2#pack ~expand:false ~fill:false ~padding:5) () in
- let oldinputt = GEdit.text ~editable:false ~width:400 ~height:180
-   ~packing:(vbox#pack ~padding:5) () in
+ let frame =
+  GBin.frame ~packing:(vbox#pack ~expand:true ~fill:true ~padding:5) () in
+ let vbox' =
+  GPack.vbox ~packing:frame#add () in
  let hbox4 =
-  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+  GPack.hbox ~border_width:5 ~packing:(vbox'#pack ~expand:false ~fill:false ~padding:5) () in
  let stateb =
   GButton.button ~label:"State"
    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
@@ -1036,97 +2197,56 @@ class rendering_window output proofw (label : GMisc.label) =
  let locateb =
   GButton.button ~label:"Locate"
    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let backwardb =
-  GButton.button ~label:"Backward"
+ let searchpatternb =
+  GButton.button ~label:"SearchPattern"
    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
- let inputt = GEdit.text ~editable:true ~width:400 ~height: 100
-   ~packing:(vbox#pack ~padding:5) () in
- let vbox1 =
-  GPack.vbox ~packing:(hbox0#pack ~expand:false ~fill:false ~padding:5) () in
  let scrolled_window1 =
-  GBin.scrolled_window ~border_width:10
-   ~packing:(vbox1#pack ~expand:true ~padding:5) () in
- let _ = scrolled_window1#add proofw#coerce in
- let hbox3 =
-  GPack.hbox ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5) () in
- let exactb =
-  GButton.button ~label:"Exact"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let introsb =
-  GButton.button ~label:"Intros"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let applyb =
-  GButton.button ~label:"Apply"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let elimintrosb =
-  GButton.button ~label:"ElimIntros"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let whdb =
-  GButton.button ~label:"Whd"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let reduceb =
-  GButton.button ~label:"Reduce"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let simplb =
-  GButton.button ~label:"Simpl"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let foldb =
-  GButton.button ~label:"Fold"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let cutb =
-  GButton.button ~label:"Cut"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let changeb =
-  GButton.button ~label:"Change"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
- let letinb =
-  GButton.button ~label:"Let ... In"
-   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+  GBin.scrolled_window ~border_width:5
+   ~packing:(vbox'#pack ~expand:true ~padding:0) () in
+ let inputt = GEdit.text ~editable:true ~width:400 ~height:100
+   ~packing:scrolled_window1#add () in
+ let vboxl =
+  GPack.vbox ~packing:(hbox0#pack ~expand:true ~fill:true ~padding:5) () in
+ let _ =
+  vboxl#pack ~expand:true ~fill:true ~padding:5 notebook#notebook#coerce in
+ let frame =
+  GBin.frame ~shadow_type:`IN ~packing:(vboxl#pack ~expand:true ~padding:5) ()
+ in
  let outputhtml =
   GHtml.xmhtml
    ~source:"<html><body bgColor=\"white\"></body></html>"
-   ~width:400 ~height: 200
-   ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5)
+   ~width:400 ~height: 100
+   ~border_width:20
+   ~packing:frame#add
    ~show:true () in
  let scratch_window = new scratch_window outputhtml in
-object(self)
+object
  method outputhtml = outputhtml
- method oldinputt = oldinputt
  method inputt = inputt
  method output = (output : GMathView.math_view)
- method proofw = (proofw : GMathView.math_view)
+ method notebook = notebook
  method show = window#show
  initializer
-  button_export_to_postscript#misc#set_sensitive false ;
+  notebook#set_empty_page ;
+  export_to_postscript_menu_item#misc#set_sensitive false ;
+  check_term := (check_term_in_scratch scratch_window) ;
 
   (* signal handlers here *)
   ignore(output#connect#selection_changed
-   (function elem -> proofw#unload ; choose_selection output elem)) ;
-  ignore(proofw#connect#selection_changed (choose_selection proofw)) ;
-  ignore(closeb#connect#clicked (fun _ -> GMain.Main.quit ())) ;
+   (function elem ->
+     choose_selection output elem ;
+     !focus_and_proveit_set_sensitive true
+   )) ;
   let settings_window = new settings_window output scrolled_window0
-   button_export_to_postscript (choose_selection output) in
-  ignore(settingsb#connect#clicked settings_window#show) ;
-  ignore(button_export_to_postscript#connect#clicked (export_to_postscript output)) ;
-  ignore(saveb#connect#clicked (save self)) ;
-  ignore(proveitb#connect#clicked (proveit self)) ;
+   export_to_postscript_menu_item (choose_selection output) in
+  set_settings_window settings_window ;
+  set_outputhtml outputhtml ;
   ignore(window#event#connect#delete (fun _ -> GMain.Main.quit () ; true )) ;
-  ignore(stateb#connect#clicked (state self)) ;
-  ignore(openb#connect#clicked (open_ self)) ;
-  ignore(checkb#connect#clicked (check self scratch_window)) ;
-  ignore(locateb#connect#clicked (locate self)) ;
-  ignore(backwardb#connect#clicked (backward self)) ;
-  ignore(exactb#connect#clicked (exact self)) ;
-  ignore(applyb#connect#clicked (apply self)) ;
-  ignore(elimintrosb#connect#clicked (elimintros self)) ;
-  ignore(whdb#connect#clicked (whd self)) ;
-  ignore(reduceb#connect#clicked (reduce self)) ;
-  ignore(simplb#connect#clicked (simpl self)) ;
-  ignore(foldb#connect#clicked (fold self)) ;
-  ignore(cutb#connect#clicked (cut self)) ;
-  ignore(changeb#connect#clicked (change self)) ;
-  ignore(letinb#connect#clicked (letin self)) ;
-  ignore(introsb#connect#clicked (intros self)) ;
+  ignore(stateb#connect#clicked state) ;
+  ignore(openb#connect#clicked open_) ;
+  ignore(checkb#connect#clicked (check scratch_window)) ;
+  ignore(locateb#connect#clicked locate) ;
+  ignore(searchpatternb#connect#clicked searchPattern) ;
   Logger.log_callback :=
    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))
 end;;
@@ -1135,18 +2255,20 @@ end;;
 
 let initialize_everything () =
  let module U = Unix in
-  let output = GMathView.math_view ~width:400 ~height:280 ()
-  and proofw = GMathView.math_view ~width:400 ~height:275 ()
-  and label = GMisc.label ~text:"gTopLevel" () in
-    let rendering_window =
-     new rendering_window output proofw label
-    in
-     rendering_window#show () ;
-     GMain.Main.main ()
+  let output = GMathView.math_view ~width:350 ~height:280 () in
+  let notebook = new notebook in
+   let rendering_window' = new rendering_window output notebook in
+    set_rendering_window rendering_window' ;
+    mml_of_cic_term_ref := mml_of_cic_term ;
+    rendering_window'#show () ;
+    GMain.Main.main ()
 ;;
 
 let _ =
- CicCooking.init () ;
+ if !usedb then
+ Mqint.init "dbname=helm_mowgli" ; 
+(* Mqint.init "host=mowgli.cs.unibo.it dbname=helm_mowgli user=helm" ; *)
  ignore (GtkMain.Main.init ()) ;
- initialize_everything ()
+ initialize_everything () ;
+ if !usedb then Mqint.close ();
 ;;