]> matita.cs.unibo.it Git - helm.git/blobdiff - matitaB/matita/matitadaemon.ml
update in basic_2
[helm.git] / matitaB / matita / matitadaemon.ml
index a53d24f676ae3c3ec9a86e8182700e1a4aa9942c..fc8c9684e87534819f855ba1786723c347738e2a 100644 (file)
@@ -2,10 +2,15 @@ open Printf;;
 open Http_types;;
 
 exception Emphasized_error of string
-exception Ambiguous of string
+exception Disamb_error of string
+exception Generic_error of string
 
 module Stack = Continuationals.Stack
 
+let debug = prerr_endline
+(* disable for debug *)
+let prerr_endline _ = ()
+
 let rt_path () = Helm_registry.get "matita.rt_base_dir" 
 
 let libdir uid = (rt_path ()) ^ "/users/" ^ uid 
@@ -16,6 +21,18 @@ let mutex = Mutex.create ();;
 
 let to_be_committed = ref [];;
 
+let html_of_matita s =
+  let patt1 = Str.regexp "\005" in
+  let patt2 = Str.regexp "\006" in
+  let patt3 = Str.regexp "<" in
+  let patt4 = Str.regexp ">" in
+  let res = Str.global_replace patt4 "&gt;" s in
+  let res = Str.global_replace patt3 "&lt;" res in
+  let res = Str.global_replace patt2 ">" res in
+  let res = Str.global_replace patt1 "<" res in
+  res
+;;
+
 (* adds a user to the commit queue; concurrent instances possible, so we
  * enclose the update in a CS
  *)
@@ -25,7 +42,7 @@ let add_user_for_commit uid =
   Mutex.unlock mutex;
 ;;
 
-let do_global_commit () =
+let do_global_commit (* () *) uid =
   prerr_endline ("to be committed: " ^ String.concat " " !to_be_committed);
   List.fold_left
     (fun out u ->
@@ -130,7 +147,11 @@ let do_global_commit () =
   (* XXX: at the moment, we don't keep track of the order in which users have 
      scheduled their commits, but we should, otherwise we will get a 
      "first come, random served" policy *)
-  "" (* (List.rev !to_be_committed) *) (MatitaAuthentication.get_users ())
+  "" (* (List.rev !to_be_committed) *) 
+  (* replace [uid] to commit all users:
+    (MatitaAuthentication.get_users ())
+   *)
+  [uid]
 ;;
 
 (*** from matitaScript.ml ***)
@@ -143,31 +164,109 @@ let eval_statement include_paths (* (buffer : GText.buffer) *) status (* script
     match statement with
     | `Raw text ->
         (* if Pcre.pmatch ~rex:only_dust_RE text then raise Margin; *)
+        prerr_endline ("raw text = " ^ text);
         let strm =
          GrafiteParser.parsable_statement status
           (Ulexing.from_utf8_string text) in
+        prerr_endline "before get_ast";
         let ast = MatitaEngine.get_ast status include_paths strm in
+        prerr_endline "after get_ast";
          ast, text
     | `Ast (st, text) -> st, text
   in
+
+  (* do we want to generate a trace? *)
+  let is_auto (l,a) = 
+    not (List.mem_assoc "demod" a || List.mem_assoc "paramod" a ||
+      List.mem_assoc "fast_paramod" a || List.assoc "depth" a = "1" ||
+      l <> None)
+  in
+
+  let get_param a param = 
+     try 
+       Some (param ^ "=" ^ List.assoc param a)
+     with Not_found -> None
+  in
+
   let floc = match ast with
   | GrafiteAst.Executable (loc, _)
   | GrafiteAst.Comment (loc, _) -> loc in
   
-  let _,lend = HExtlib.loc_of_floc floc in 
+  let lstart,lend = HExtlib.loc_of_floc floc in 
   let parsed_text, _parsed_text_len = 
     HExtlib.utf8_parsed_text unparsed_text (HExtlib.floc_of_loc (0,lend)) in
+  let parsed_text_len = utf8_length parsed_text in
   let byte_parsed_text_len = String.length parsed_text in
   let unparsed_txt' = 
     String.sub unparsed_text byte_parsed_text_len 
       (String.length unparsed_text - byte_parsed_text_len)
   in
+  prerr_endline (Printf.sprintf "ustring_sub caso 1: lstart=%d, parsed=%s" lstart parsed_text);
+  let pre = Netconversion.ustring_sub `Enc_utf8  0 lstart parsed_text in
+
+  let mk_univ trace = 
+    let href r = 
+      Printf.sprintf "\005A href=\"%s\"\006%s\005/A\006"
+        (NReference.string_of_reference r) (NCicPp.r2s status true r)
+    in
+    (*if trace = [] then "{}"
+    else*) String.concat ", " 
+      (HExtlib.filter_map (function 
+        | NotationPt.NRef r -> Some (href r) 
+        | _ -> None)
+      trace)
+  in
   
-  let status = 
-    MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
-  in 
-  (status, parsed_text, unparsed_txt'),"",(*parsed_text_len*)
-    utf8_length parsed_text
+  match ast with
+  | GrafiteAst.Executable (_,
+      GrafiteAst.NCommand (_,
+        GrafiteAst.NObj (loc, astobj,_))) ->
+          let objname = NotationPt.name_of_obj astobj in
+          let status = 
+            MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
+          in
+          let new_parsed_text = Ulexing.from_utf8_string parsed_text in
+          let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
+          let outstr = ref "" in
+          ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
+          let x, y = HExtlib.loc_of_floc floc in
+          let pre = Netconversion.ustring_sub `Enc_utf8  0 x !outstr in
+          let post = Netconversion.ustring_sub `Enc_utf8 x
+           (Netconversion.ustring_length `Enc_utf8 !outstr - x) !outstr in
+          outstr := Printf.sprintf
+            "%s\005img class=\"anchor\" src=\"icons/tick.png\" id=\"%s\" /\006%s" pre objname post;
+          prerr_endline ("baseuri after advance = " ^ status#baseuri);
+          (* prerr_endline ("parser output: " ^ !outstr); *)
+          (status,!outstr, unparsed_txt'),parsed_text_len
+  | GrafiteAst.Executable (_,
+      GrafiteAst.NTactic (_,
+        [GrafiteAst.NAuto (_, (l,a as auto_params))])) when is_auto auto_params
+          ->
+          let l = match l with
+          | None -> None
+          | Some (_,l') -> Some (List.map (fun x -> "",0,x) l')
+          in
+          let trace_ref = ref [] in
+          let status = NnAuto.auto_tac ~params:(l,a) ~trace_ref status in
+          let new_parsed_text = pre ^ (Printf.sprintf 
+            "/\005span class='autotactic'\006%s\005span class='autotrace'\006 trace %s\005/span\006\005/span\006/"
+             (String.concat " " 
+               (List.assoc "depth" a::
+                HExtlib.filter_map (get_param a) ["width";"size"]))
+             (mk_univ !trace_ref))
+          in
+          (status,new_parsed_text, unparsed_txt'),parsed_text_len
+  | _ ->
+      let status = 
+        MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
+      in
+      let new_parsed_text = Ulexing.from_utf8_string parsed_text in
+      let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
+      let outstr = ref "" in
+      ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
+      prerr_endline ("baseuri after advance = " ^ status#baseuri);
+      (* prerr_endline ("parser output: " ^ !outstr); *)
+      (status,!outstr, unparsed_txt'),parsed_text_len
 
 (*let save_moo status = 
   let script = MatitaScript.current () in
@@ -239,18 +338,6 @@ let output_status s =
   (* prerr_endline ("sending metasenv:\n" ^ res); res *)
 ;;
 
-let html_of_matita s =
-  let patt1 = Str.regexp "\005" in
-  let patt2 = Str.regexp "\006" in
-  let patt3 = Str.regexp "<" in
-  let patt4 = Str.regexp ">" in
-  let res = Str.global_replace patt4 "&gt;" s in
-  let res = Str.global_replace patt3 "&lt;" res in
-  let res = Str.global_replace patt2 ">" res in
-  let res = Str.global_replace patt1 "<" res in
-  res
-;;
-
 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*";;
 
 let first_line s =
@@ -300,6 +387,7 @@ let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
     *)
+    let readonly = cgi # argument_value "readonly" in
     let filename = libdir uid ^ "/" ^ (cgi # argument_value "file") in
     (* prerr_endline ("reading file " ^ filename); *)
     let body = 
@@ -324,16 +412,23 @@ let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
        with 
          Librarian.NoRootFor _ | Librarian.FileNotFound _ -> "",[] in
     include_paths := incpaths;
-    let status = (MatitaAuthentication.get_status sid)#set_baseuri baseuri in
-    let history = [status] in
-    MatitaAuthentication.set_status sid status;
-    MatitaAuthentication.set_history sid history;
+    if readonly <> "true" then
+       (let status = new MatitaEngine.status (Some uid) baseuri in
+        let history = [status] in
+        MatitaAuthentication.set_status sid status;
+        MatitaAuthentication.set_history sid history);
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
     cgi#out_channel#output_string body;
   with
+  | Sys_error _ -> 
+    cgi # set_header 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ();
+    cgi#out_channel#output_string "<error />"
   | Not_found _ -> 
     cgi # set_header
       ~status:`Internal_server_error
@@ -343,34 +438,100 @@ let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   cgi#out_channel#commit_work()
 ;;
 
+let xml_of_disamb_error l =
+  let mk_alias = function
+  | GrafiteAst.Ident_alias (_,uri) -> "href=\"" ^ uri ^ "\""
+  | GrafiteAst.Symbol_alias (_,uri,desc) 
+  | GrafiteAst.Number_alias (uri,desc) -> 
+      let uri = try HExtlib.unopt uri with _ -> "cic:/fakeuri.def(1)" in
+        "href=\"" ^ uri ^ "\" title=\"" ^ 
+        (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
+        ^ "\""
+  in
+
+  let mk_interpr (loc,a) =
+    let x,y = HExtlib.loc_of_floc loc in
+    Printf.sprintf "<interpretation start=\"%d\" stop=\"%d\" %s />"
+      x y (mk_alias a)
+  in
+
+  let mk_failure (il,loc,msg) =
+    let x,y = HExtlib.loc_of_floc loc in
+    Printf.sprintf "<failure start=\"%d\" stop=\"%d\" title=\"%s\">%s</failure>"
+      x y (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () msg)
+      (String.concat "" (List.map mk_interpr il))
+  in
+
+  let mk_choice (a,fl) = 
+    let fl' = String.concat "" (List.map mk_failure fl) in
+    match a with
+    | None -> "<choice>" ^ fl' ^ "</choice>"
+    | Some a -> Printf.sprintf "<choice %s>%s</choice>" (mk_alias a) fl'
+  in
+
+  let mk_located (loc,cl) =
+    let x,y = HExtlib.loc_of_floc loc in
+    Printf.sprintf "<choicepoint start=\"%d\" stop=\"%d\">%s</choicepoint>"
+      x y (String.concat "" (List.map mk_choice cl))
+  in
+  "<disamberror>" ^ (String.concat "" (List.map mk_located l)) ^ "</disamberror>"
+;;
+
 let advance0 sid text =
   let status = MatitaAuthentication.get_status sid in
+  let history = MatitaAuthentication.get_history sid in
   let status = status#reset_disambiguate_db () in
-  let (st,new_statements,new_unparsed),(* newtext TODO *) _,parsed_len =
-    try
-    eval_statement !include_paths (*buffer*) status (`Raw text)
-    with
-    | HExtlib.Localized (floc,e) as exn ->
+  let (st,new_statements,new_unparsed),parsed_len =
+    let rec do_exc = function
+    | MatitaEngine.EnrichedWithStatus (e,_) -> do_exc e
+    | NCicTypeChecker.TypeCheckerFailure s -> raise (Generic_error (Lazy.force s))
+    | HExtlib.Localized (floc,e) -> 
       let x, y = HExtlib.loc_of_floc floc in
       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
       let post = Netconversion.ustring_sub `Enc_utf8 y 
          (Netconversion.ustring_length `Enc_utf8 text - y) text in
-      let _,title = MatitaExcPp.to_string exn in
+      let _,title = MatitaExcPp.to_string e in
       (* let title = "" in *)
       let marked = 
        pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
       () (html_of_matita marked) in
-      raise (Emphasized_error marked) 
+      raise (Emphasized_error marked)
+    | Disambiguate.NoWellTypedInterpretation (floc,e) ->
+      let x, y = HExtlib.loc_of_floc floc in
+      let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
+      let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
+      let post = Netconversion.ustring_sub `Enc_utf8 y 
+         (Netconversion.ustring_length `Enc_utf8 text - y) text in
+      (*let _,title = MatitaExcPp.to_string e in*)
+      (* let title = "" in *)
+      let marked = 
+       pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
+      let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
+      () (html_of_matita marked) in
+      raise (Emphasized_error marked)
+    | NCicRefiner.Uncertain m as exn ->
+      let floc, e = Lazy.force m in
+      let x, y = HExtlib.loc_of_floc floc in
+      let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
+      let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
+      let post = Netconversion.ustring_sub `Enc_utf8 y 
+         (Netconversion.ustring_length `Enc_utf8 text - y) text in
+      (* let _,title = MatitaExcPp.to_string e in *)
+      (* let title = "" in *)
+      let marked = 
+       pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
+      let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
+      () (html_of_matita marked) in
+      raise (Emphasized_error marked)
     | NTacStatus.Error (s,None) as e ->
         prerr_endline 
-          ("NTacStatus.Error " ^ (Lazy.force s));
-        raise e
+          ("NTacStatus.Error " ^ (Lazy.force s)); raise e
     | NTacStatus.Error (s,Some exc) as e ->
         prerr_endline 
           ("NTacStatus.Error " ^ Lazy.force s ^ " -- " ^ (Printexc.to_string exc));
-        raise e
+        do_exc exc
     | GrafiteDisambiguate.Ambiguous_input (loc,choices) ->
       let x,y = HExtlib.loc_of_floc loc in
       let choice_of_alias = function
@@ -411,19 +572,33 @@ let advance0 sid text =
       *)
       let strchoices = Printf.sprintf
         "<ambiguity start=\"%d\" stop=\"%d\">%s</ambiguity>" x y strchoices
-      in raise (Ambiguous strchoices) 
+      in raise (Disamb_error strchoices)
+   | GrafiteDisambiguate.Error l -> raise (Disamb_error (xml_of_disamb_error l))
    (* | End_of_file -> ...          *)
+   | e -> 
+      (* prerr_endline ("matitadaemon *** Unhandled exception " ^ Printexc.to_string e); *)
+      prerr_endline ("matitadaemon *** Unhandled exception " ^ snd (MatitaExcPp.to_string e));
+      raise e
+   in
+
+    try
+      eval_statement !include_paths (*buffer*) status (`Raw text)
+    with e -> do_exc e
   in
-  let stringbuf = Ulexing.from_utf8_string new_statements in
-  let interpr = GrafiteDisambiguate.get_interpr st#disambiguate_db in
-  let outstr = ref "" in
-  ignore (SmallLexer.mk_small_printer interpr outstr stringbuf);
-  prerr_endline ("baseuri after advance = " ^ st#baseuri);
-  (* prerr_endline ("parser output: " ^ !outstr); *)
+        debug "BEGIN PRINTGRAMMAR";
+        (*prerr_endline (Print_grammar.ebnf_of_term status);*)
+        (*let kwds = String.concat ", " status#get_kwds in
+        debug ("keywords = " ^ kwds );*)
+        debug "END PRINTGRAMMAR";
   MatitaAuthentication.set_status sid st;
+  MatitaAuthentication.set_history sid (st::history);
+(*  prerr_endline "previous timestamp";
+  status#print_timestamp();
+  prerr_endline "current timestamp";
+  st#print_timestamp(); *)
   parsed_len, 
     Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
-      () (html_of_matita !outstr), new_unparsed, st
+      () (html_of_matita new_statements), new_unparsed, st
 
 let register (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
@@ -432,8 +607,9 @@ let register (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   assert (cgi#arguments <> []);
   let uid = cgi#argument_value "userid" in
   let userpw = cgi#argument_value "password" in
-  (try 
-    MatitaAuthentication.add_user uid userpw;
+  (try
+    (* currently registering only unprivileged users *) 
+    MatitaAuthentication.add_user uid userpw false;
 (*    env#set_output_header_field "Location" "/index.html" *)
     cgi#out_channel#output_string
      ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/login.html\">"
@@ -464,34 +640,28 @@ let login (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   assert (cgi#arguments <> []);
   let uid = cgi#argument_value "userid" in
   let userpw = cgi#argument_value "password" in
-  let pw,_ = MatitaAuthentication.lookup_user uid in
-
-  if pw = userpw then
-   begin
-   let ft = MatitaAuthentication.read_ft uid in
-   let _ = MatitaFilesystem.html_of_library uid ft in
-    let sid = MatitaAuthentication.create_session uid in
-    (* let cookie = Netcgi.Cookie.make "session" (Uuidm.to_string sid) in
-       cgi#set_header ~set_cookies:[cookie] (); *)
-    env#set_output_header_field 
-      "Set-Cookie" ("session=" ^ (Uuidm.to_string sid));
-(*    env#set_output_header_field "Location" "/index.html" *)
-    cgi#out_channel#output_string
-     ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/index.html\">"
-     ^ "</head><body>Redirecting to Matita page...</body></html>")
-   end
-  else
-   begin
+  (try 
+      MatitaAuthentication.check_pw uid userpw;
+      NCicLibrary.init (Some uid);
+      let ft = MatitaAuthentication.read_ft uid in
+      let _ = MatitaFilesystem.html_of_library uid ft in
+       let sid = MatitaAuthentication.create_session uid in
+       (* let cookie = Netcgi.Cookie.make "session" (Uuidm.to_string sid) in
+          cgi#set_header ~set_cookies:[cookie] (); *)
+       env#set_output_header_field 
+         "Set-Cookie" ("session=" ^ (Uuidm.to_string sid));
+   (*    env#set_output_header_field "Location" "/index.html" *)
+       cgi#out_channel#output_string
+        ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/index.html\">"
+        ^ "</head><body>Redirecting to Matita page...</body></html>")
+  with MatitaAuthentication.InvalidPassword ->
     cgi#set_header
       ~cache:`No_cache 
       ~content_type:"text/html; charset=\"utf-8\""
       ();
     cgi#out_channel#output_string
-      "<html><head></head><body>Authentication error</body></html>"
-   end;
-    
+      "<html><head></head><body>Authentication error</body></html>");
   cgi#out_channel#commit_work()
-  
 ;;
 
 let logout (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
@@ -573,6 +743,10 @@ let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     cgi#out_channel#output_string "<response>ok</response>"
   with
   | File_already_exists ->
+      cgi # set_header 
+        ~cache:`No_cache 
+        ~content_type:"text/xml; charset=\"utf-8\""
+        ();
       cgi#out_channel#output_string "<response>cancelled</response>"
   | Sys_error _ -> 
     cgi # set_header
@@ -581,6 +755,10 @@ let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ~content_type:"text/xml; charset=\"utf-8\""
       ()
   | e ->
+      cgi # set_header 
+        ~cache:`No_cache 
+        ~content_type:"text/xml; charset=\"utf-8\""
+        ();
       let estr = Printexc.to_string e in
       cgi#out_channel#output_string ("<response>" ^ estr ^ "</response>"));
   cgi#out_channel#commit_work()
@@ -588,9 +766,13 @@ let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
 
 let initiate_commit (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
-  let _env = cgi#environment in
+  let env = cgi#environment in
   (try
-    let out = do_global_commit () in
+    let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
+    let sid = HExtlib.unopt sid in
+    MatitaAuthentication.probe_commit_priv sid;
+    let uid = MatitaAuthentication.user_of_session sid in
+    let out = do_global_commit (* () *) uid in
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
@@ -600,6 +782,13 @@ let initiate_commit (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     cgi#out_channel#output_string ("<details>" ^ out ^ "</details>");
     cgi#out_channel#output_string "</commit>"
   with
+  | Failure _ -> 
+      cgi # set_header 
+        ~cache:`No_cache 
+        ~content_type:"text/xml; charset=\"utf-8\""
+        ();
+      cgi#out_channel#output_string 
+        "<commit><error>no commit privileges</error></commit>"
   | Not_found _ -> 
     cgi # set_header
       ~status:`Internal_server_error
@@ -616,6 +805,7 @@ let svn_update (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let sid = HExtlib.unopt sid in
   let uid = MatitaAuthentication.user_of_session sid in
   (try
+    MatitaAuthentication.probe_commit_priv sid;
     let files,anomalies,(added,conflict,del,upd,merged) = 
       MatitaFilesystem.update_user uid 
     in
@@ -642,6 +832,13 @@ let svn_update (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     cgi#out_channel#output_string ("<details>" ^ details ^ "</details>");
     cgi#out_channel#output_string "</update>";
   with
+  | Failure _ -> 
+      cgi # set_header 
+        ~cache:`No_cache 
+        ~content_type:"text/xml; charset=\"utf-8\""
+        ();
+      cgi#out_channel#output_string 
+        "<commit><error>no commit privileges</error></commit>"
   | Not_found _ -> 
     cgi # set_header
       ~status:`Internal_server_error
@@ -653,6 +850,7 @@ let svn_update (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
 
 (* returns the length of the executed text and an html representation of the
  * current metasenv*)
+(*let advance  =*)
 let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
   let env = cgi#environment in
@@ -667,9 +865,7 @@ let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     *)
     let text = cgi#argument_value "body" in
     (* prerr_endline ("body =\n" ^ text); *)
-    let history = MatitaAuthentication.get_history sid in
     let parsed_len, new_parsed, new_unparsed, new_status = advance0 sid text in
-    MatitaAuthentication.set_history sid (new_status::history);
     let txt = output_status new_status in
     let body = 
        "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\">" ^
@@ -683,52 +879,73 @@ let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ();
     cgi#out_channel#output_string body
    with
+  | Generic_error text ->
+    let body = "<response><error>" ^ text ^ "</error></response>" in 
+    cgi # set_header 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ();
+    cgi#out_channel#output_string body
   | Emphasized_error text ->
 (* | MultiPassDisambiguator.DisambiguationError (offset,errorll) -> *)
-    let body = "<response><error>" ^ text ^ "</error></response>" in 
+    let body = "<response><localized>" ^ text ^ "</localized></response>" in 
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
     cgi#out_channel#output_string body
-  | Ambiguous text ->
+  | Disamb_error text -> 
     let body = "<response>" ^ text ^ "</response>" in 
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
     cgi#out_channel#output_string body
+  | End_of_file _ -> 
+    let body = "<response><parsed length=\"0\"></parsed></response>" in
+    cgi # set_header 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ();
+    cgi#out_channel#output_string body
   | Not_found _ -> 
     cgi # set_header
       ~status:`Internal_server_error
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
-      ());
+      ()
+  );
   cgi#out_channel#commit_work()
 ;;
 
 let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
   let env = cgi#environment in
-  (try 
+(*  (try  *)
     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
     let sid = HExtlib.unopt sid in
-    let history = MatitaAuthentication.get_history sid in
 
-    let rec aux parsed_len parsed_txt text =
+    let error_msg = function
+      | Emphasized_error text -> "<localized>" ^ text ^ "</localized>" 
+      | Disamb_error text -> text
+      | End_of_file _ -> (* not an error *) ""
+      | e -> (* unmanaged error *)
+          "<error>" ^ 
+          (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () 
+            (Printexc.to_string e)) ^ "</error>"
+    in
+
+    let rec aux acc text =
       try
         prerr_endline ("evaluating: " ^ first_line text);
         let plen,new_parsed,new_unparsed,_new_status = advance0 sid text in
-        aux (parsed_len+plen) (parsed_txt ^ new_parsed) new_unparsed
-      with 
-      | End_of_file -> 
+        aux ((plen,new_parsed)::acc) new_unparsed
+      with e -> acc, error_msg e 
+        (* DON'T SERIALIZE NOW!!!
           let status = MatitaAuthentication.get_status sid in
           GrafiteTypes.Serializer.serialize 
             ~baseuri:(NUri.uri_of_string status#baseuri) status;
-          if parsed_len > 0 then 
-            MatitaAuthentication.set_history sid (status::history);
-          parsed_len, parsed_txt
-      | _ -> parsed_len, parsed_txt
+          acc, error_msg e *)
     in
     (* 
     cgi # set_header 
@@ -738,27 +955,27 @@ let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     *)
     let text = cgi#argument_value "body" in
     (* prerr_endline ("body =\n" ^ text); *)
-    let parsed_len, new_parsed = aux 0 "" text in
+    let len_parsedlist, err_msg = aux [] text in
     let status = MatitaAuthentication.get_status sid in
     let txt = output_status status in
+    let parsed_tag (len,txt) = 
+       "<parsed length=\"" ^ (string_of_int len) ^ "\">" ^ txt ^ "</parsed>"
+    in
+    (* List.rev: the list begins with the older parsed txt *)
     let body = 
-       "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\">" ^
-       new_parsed ^ "</parsed>" ^ txt 
-       ^ "</response>"
-    in 
-    (*let body = 
-       "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\" />" ^ txt 
-       ^ "</response>"
-    in*) 
+       "<response>" ^
+       String.concat "" (List.rev (List.map parsed_tag len_parsedlist)) ^
+       txt ^ err_msg ^ "</response>"
+    in
     (* prerr_endline ("sending goto bottom response:\n" ^ body); *)
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
-    cgi#out_channel#output_string body
-   with Not_found -> cgi#set_header ~status:`Internal_server_error 
+    cgi#out_channel#output_string body;
+(*   with Not_found -> cgi#set_header ~status:`Internal_server_error 
       ~cache:`No_cache 
-      ~content_type:"text/xml; charset=\"utf-8\"" ());
+      ~content_type:"text/xml; charset=\"utf-8\"" ()); *)
   cgi#out_channel#commit_work() 
 ;;
 
@@ -780,12 +997,12 @@ let gotoTop (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     let baseuri = status#baseuri in
     let new_status = new MatitaEngine.status (Some uid) baseuri in
     prerr_endline "gototop prima della time travel";
-    NCicLibrary.time_travel new_status;
+    (* NCicLibrary.time_travel new_status; *)
     prerr_endline "gototop dopo della time travel";
     let new_history = [new_status] in 
     MatitaAuthentication.set_history sid new_history;
     MatitaAuthentication.set_status sid new_status;
-    NCicLibrary.time_travel new_status;
+    (* NCicLibrary.time_travel new_status; *)
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
@@ -802,7 +1019,7 @@ let gotoTop (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
 let retract (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
   let env = cgi#environment in
-  (try 
+  (try  
     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
     let sid = HExtlib.unopt sid in
     (*
@@ -812,13 +1029,18 @@ let retract (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ();
     *)
     let history = MatitaAuthentication.get_history sid in
+    let old_status = MatitaAuthentication.get_status sid in
     let new_history,new_status =
        match history with
          _::(status::_ as history) ->
           history, status
       | [_] -> (prerr_endline "singleton";failwith "retract")
       | _ -> (prerr_endline "nil"; assert false) in
-    prerr_endline ("prima della time travel");
+(*    prerr_endline "timestamp prima della retract";
+    old_status#print_timestamp ();
+    prerr_endline "timestamp della retract";
+    new_status#print_timestamp ();
+    prerr_endline ("prima della time travel"); *)
     NCicLibrary.time_travel new_status;
     prerr_endline ("dopo della time travel");
     MatitaAuthentication.set_history sid new_history;
@@ -830,7 +1052,9 @@ let retract (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
     cgi#out_channel#output_string body
-   with _ -> cgi#set_header ~status:`Internal_server_error 
+   with e -> 
+    prerr_endline ("error in retract: " ^ Printexc.to_string e);
+    cgi#set_header ~status:`Internal_server_error 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\"" ());
   cgi#out_channel#commit_work()