]> matita.cs.unibo.it Git - helm.git/blobdiff - matitaB/matita/matitadaemon.ml
Matitaweb: first attempt at web UI for disambiguation.
[helm.git] / matitaB / matita / matitadaemon.ml
index 5abb8ad07e8f90dd03f0e718556b0127d8aa72e5..9fc2b1bbcf05b30e9cc327f39ba847dc0d29b5d4 100644 (file)
@@ -1,6 +1,9 @@
 open Printf;;
 open Http_types;;
 
+exception Emphasized_error of string
+exception Ambiguous of string
+
 module Stack = Continuationals.Stack
 
 let rt_path () = Helm_registry.get "matita.rt_base_dir" 
@@ -9,6 +12,127 @@ let libdir uid = (rt_path ()) ^ "/users/" ^ uid
 
 let utf8_length = Netconversion.ustring_length `Enc_utf8
 
+let mutex = Mutex.create ();;
+
+let to_be_committed = ref [];;
+
+(* adds a user to the commit queue; concurrent instances possible, so we
+ * enclose the update in a CS
+ *)
+let add_user_for_commit uid =
+  Mutex.lock mutex;
+  to_be_committed := uid::List.filter (fun x -> x <> uid) !to_be_committed;
+  Mutex.unlock mutex;
+;;
+
+let do_global_commit () =
+  prerr_endline ("to be committed: " ^ String.concat " " !to_be_committed);
+  List.fold_left
+    (fun out u ->
+       let ft = MatitaAuthentication.read_ft u in
+
+       (* first we add new files/dirs to the repository *)
+       (* must take the reverse because svn requires the add to be performed in
+          the correct order
+          (otherwise run with --parents option) *)
+       let to_be_added = List.rev (List.map fst  
+         (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MAdd) ft))
+       in
+       prerr_endline ("@@@ ADDING files: " ^ String.concat ", " to_be_added);
+       let out = 
+         try
+           let newout = MatitaFilesystem.add_files u to_be_added in
+           out ^ "\n" ^ newout
+         with
+         | MatitaFilesystem.SvnError outstr -> 
+             prerr_endline ("ADD OF " ^ u ^ "FAILED:" ^ outstr);
+             out
+       in
+
+       (* now we update the local copy (to merge updates from other users) *)
+       let out = try
+         let files,anomalies,(added,conflict,del,upd,merged) = 
+           MatitaFilesystem.update_user u 
+         in
+         let anomalies = String.concat "\n" anomalies in
+         let details = Printf.sprintf 
+           ("%d new files\n"^^
+            "%d deleted files\n"^^
+            "%d updated files\n"^^
+            "%d merged files\n"^^
+            "%d conflicting files\n\n" ^^
+            "Anomalies:\n%s") added del upd merged conflict anomalies
+         in
+         prerr_endline ("update details:\n" ^ details);
+         MatitaAuthentication.set_file_flag u files;
+         out ^ "\n" ^ details 
+         with
+         | MatitaFilesystem.SvnError outstr -> 
+             prerr_endline ("UPDATE OF " ^ u ^ "FAILED:" ^ outstr);
+             out
+       in
+
+       (* we re-read the file table after updating *)
+       let ft = MatitaAuthentication.read_ft u in
+
+       (* finally we perform the real commit *)
+       let modified = (List.map fst
+         (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MModified) ft))
+       in
+       let to_be_committed = to_be_added @ modified
+       in
+       let out = try
+         let newout = MatitaFilesystem.commit u to_be_committed in
+         out ^ "\n" ^ newout
+         with
+         | MatitaFilesystem.SvnError outstr -> 
+             prerr_endline ("COMMIT OF " ^ u ^ "FAILED:" ^ outstr);
+             out
+       in
+
+       (* call stat to get the final status *)
+       let files, anomalies = MatitaFilesystem.stat_user u in
+       let added,not_added = List.fold_left 
+         (fun (a_acc, na_acc) fname ->
+            if List.mem fname (List.map fst files) then
+               a_acc, fname::na_acc
+            else
+               fname::a_acc, na_acc)
+         ([],[]) to_be_added
+       in
+       let committed,not_committed = List.fold_left 
+         (fun (c_acc, nc_acc) fname ->
+            if List.mem fname (List.map fst files) then
+               c_acc, fname::nc_acc
+            else
+               fname::c_acc, nc_acc)
+         ([],[]) modified
+       in
+       let conflicts = List.map fst (List.filter 
+         (fun (_,f) -> f = Some MatitaFilesystem.MConflict) files)
+       in
+       MatitaAuthentication.set_file_flag u
+         (List.map (fun x -> x, Some MatitaFilesystem.MSynchronized) (added@committed));
+       MatitaAuthentication.set_file_flag u files;
+       out ^ "\n\n" ^ (Printf.sprintf
+        ("COMMIT RESULTS for %s\n" ^^
+         "==============\n" ^^
+         "added and committed (%d of %d): %s\n" ^^
+         "modified and committed (%d of %d): %s\n" ^^
+         "not added: %s\n" ^^
+         "not committed: %s\n" ^^
+         "conflicts: %s\n")
+         u (List.length added) (List.length to_be_added) (String.concat ", " added)
+         (List.length committed) (List.length modified) (String.concat ", " committed)
+         (String.concat ", " not_added)
+         (String.concat ", " not_committed) (String.concat ", " conflicts)))
+
+  (* 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 ())
+;;
+
 (*** from matitaScript.ml ***)
 (* let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$" *)
 
@@ -89,19 +213,17 @@ let output_status s =
     let markup = 
       if is_loc then
         (match depth, pos with
-         | 0, 0 -> "<B>" ^ (render_switch sw) ^ "</B>"
+         | 0, 0 -> "<span class=\"activegoal\">" ^ (render_switch sw) ^ "</span>"
          | 0, _ -> 
-            Printf.sprintf "<B>|<SUB>%d</SUB>: %s</B>" pos (render_switch sw)
+            Printf.sprintf "<span class=\"activegoal\">|<SUB>%d</SUB>: %s</span>" pos (render_switch sw)
          | 1, pos when Stack.head_tag s#stack = `BranchTag ->
-             Printf.sprintf "|<SUB>%d</SUB> : %s" pos (render_switch sw)
+             Printf.sprintf "<span class=\"passivegoal\">|<SUB>%d</SUB> : %s</span>" pos (render_switch sw)
          | _ -> render_switch sw)
       else render_switch sw
     in
-    prerr_endline "pippo1";
     let markup = 
       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () markup in
     let markup = "<metaname>" ^ markup ^ "</metaname>" in
-    prerr_endline "pippo2";
     let sequent =
       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () (sequent sw)
     in      
@@ -109,43 +231,23 @@ let output_status s =
     "<meta number=\"" ^ (string_of_int metano) ^ "\">" ^ markup ^
     txt0 ^ "</meta>" ^ acc
   in
-  let res = "<metasenv>" ^
+  "<metasenv>" ^
     (Stack.fold 
       ~env:(render_sequent true) ~cont:(render_sequent false) 
       ~todo:(render_sequent false) "" s#stack) ^
     "</metasenv>"
-  in 
-  prerr_endline ("sending metasenv:\n" ^ res); res
+  (* prerr_endline ("sending metasenv:\n" ^ res); res *)
 ;;
 
-(* let html_of_status s =
-  let _,_,metasenv,subst,_ = s#obj in
-  let txt = List.fold_left 
-    (fun acc (nmeta,_ as meta) ->
-       let txt0 = snd (ApplyTransformation.ntxt_of_cic_sequent 
-         ~metasenv ~subst ~map_unicode_to_tex:false 80 s meta)
-       in
-       prerr_endline ("### txt0 = " ^ txt0);
-      ("<B>Goal ?" ^ (string_of_int nmeta) ^ "</B>\n" ^ txt0)::acc)
-    [] metasenv
-  in
-  String.concat "\n\n" txt
-;; *)
-
 let html_of_matita s =
-  prerr_endline ("input: " ^ 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
-  prerr_endline ("output: " ^ res);
   let res = Str.global_replace patt3 "&lt;" res in
-  prerr_endline ("output: " ^ res);
   let res = Str.global_replace patt2 ">" res in
-  prerr_endline ("output: " ^ res);
   let res = Str.global_replace patt1 "<" res in
-  prerr_endline ("output: " ^ res);
   res
 ;;
 
@@ -199,13 +301,13 @@ let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ();
     *)
     let filename = libdir uid ^ "/" ^ (cgi # argument_value "file") in
-    prerr_endline ("reading file " ^ filename);
+    (* prerr_endline ("reading file " ^ filename); *)
     let body = 
      Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false ()
         (html_of_matita (read_file filename)) in
      
      (*   html_of_matita (read_file filename) in *)
-    prerr_endline ("sending:\nBEGIN\n" ^ body ^ "\nEND");
+    (* prerr_endline ("sending:\nBEGIN\n" ^ body ^ "\nEND"); *)
     let body = "<response><file>" ^ body ^ "</file></response>" in
     let baseuri, incpaths = 
       try 
@@ -222,8 +324,10 @@ let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
        with 
          Librarian.NoRootFor _ | Librarian.FileNotFound _ -> "",[] in
     include_paths := incpaths;
-    let status = MatitaAuthentication.get_status sid in
-    MatitaAuthentication.set_status sid (status#set_baseuri baseuri);
+    let status = (MatitaAuthentication.get_status sid)#set_baseuri 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\""
@@ -243,17 +347,71 @@ let advance0 sid text =
   let status = MatitaAuthentication.get_status 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 (_,e) -> raise e
-        (*| End_of_file -> raise Margin *)
-     in
+    try
+    eval_statement !include_paths (*buffer*) status (`Raw text)
+    with
+    | HExtlib.Localized (floc,e) as exn ->
+      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 = "" 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) 
+    | GrafiteDisambiguate.Ambiguous_input (loc,choices) ->
+      let x,y = HExtlib.loc_of_floc loc in
+      let choice_of_alias = function
+       | GrafiteAst.Ident_alias (_,uri) -> uri, None, uri
+       | GrafiteAst.Number_alias (None,desc)
+       | GrafiteAst.Symbol_alias (_,None,desc) -> "cic:/fakeuri.def(1)", Some desc, desc
+       | GrafiteAst.Number_alias (Some uri,desc)
+       | GrafiteAst.Symbol_alias (_,Some uri,desc) -> uri, Some desc, desc
+      in
+      let tag_of_choice (uri,title,desc) =
+        match title with
+        | None -> Printf.sprintf "<choice href=\"%s\">%s</choice>"
+            uri 
+            (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
+        | Some t -> Printf.sprintf "<choice href=\"%s\" title=\"%s\">%s</choice>"
+            uri 
+            (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () t)
+            (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
+      in
+      let strchoices = 
+        String.concat "\n" 
+          (List.map (fun x -> tag_of_choice (choice_of_alias x)) choices)
+      in
+      prerr_endline (Printf.sprintf
+        "@@@ Ambiguous input at (%d,%d). Possible choices:\n\n%s\n\n@@@ End."
+          x y strchoices);
+      (*
+      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 = "Disambiguation Error" 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
+      *)
+      let strchoices = Printf.sprintf
+        "<ambiguity start=\"%d\" stop=\"%d\">%s</ambiguity>" x y strchoices
+      in raise (Ambiguous strchoices) 
+   (* | End_of_file -> ...          *)
+  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 ("parser output: " ^ !outstr);
+  prerr_endline ("baseuri after advance = " ^ st#baseuri);
+  (* prerr_endline ("parser output: " ^ !outstr); *)
   MatitaAuthentication.set_status sid st;
   parsed_len, 
     Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
@@ -261,7 +419,7 @@ let advance0 sid text =
 
 let register (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
   
   assert (cgi#arguments <> []);
   let uid = cgi#argument_value "userid" in
@@ -269,7 +427,7 @@ let register (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   (try 
     MatitaAuthentication.add_user uid userpw;
 (*    env#set_output_header_field "Location" "/index.html" *)
-    cgi#outchannel#output_string
+    cgi#out_channel#output_string
      ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/login.html\">"
      ^ "</head><body>Redirecting to login page...</body></html>")
    with
@@ -302,20 +460,20 @@ let login (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
 
   if pw = userpw then
    begin
-    let _ = MatitaFilesystem.html_of_library uid in
+   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#outchannel#output_string
+    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
-    prerr_endline ("ERROR: received " ^ userpw ^ "but the password is " ^ pw);
     cgi#set_header
       ~cache:`No_cache 
       ~content_type:"text/html; charset=\"utf-8\""
@@ -351,6 +509,8 @@ let logout (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   cgi#out_channel#commit_work()
 ;;
 
+exception File_already_exists;;
+
 let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
   let env = cgi#environment in
@@ -362,25 +522,75 @@ let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     assert (cgi#arguments <> []);
     let locked = cgi#argument_value "locked" in
     let unlocked = cgi#argument_value "unlocked" in
-    let filename = libdir uid ^ "/" ^ (cgi # argument_value "file") in
-    prerr_endline ("Matita will save the file for user " ^ uid);
-    let oc = open_out filename in
-    output_string oc (locked ^ unlocked);
-    close_out oc;
-    if MatitaEngine.eos status unlocked then
+    let dir = cgi#argument_value "dir" in
+    let rel_filename = cgi # argument_value "file" in
+    let filename = libdir uid ^ "/" ^ rel_filename in
+    let force = bool_of_string (cgi#argument_value "force") in
+    let already_exists = Sys.file_exists filename in
+
+    if ((not force) && already_exists) then 
+      raise File_already_exists;
+
+    if dir = "true" then
+       Unix.mkdir filename 0o744
+    else 
      begin
-      prerr_endline ("serializing proof objects...");
-      GrafiteTypes.Serializer.serialize 
-        ~baseuri:(NUri.uri_of_string status#baseuri) status;
-      prerr_endline ("adding to the commit queue...");
-      MatitaFilesystem.add_user uid;
-      prerr_endline ("done.");
+      let oc = open_out filename in
+      output_string oc (locked ^ unlocked);
+      close_out oc;
+      if MatitaEngine.eos status unlocked then
+       begin
+        (* prerr_endline ("serializing proof objects..."); *)
+        GrafiteTypes.Serializer.serialize 
+          ~baseuri:(NUri.uri_of_string status#baseuri) status;
+        (* prerr_endline ("done."); *)
+       end;
      end;
+    let old_flag =
+      try 
+        List.assoc rel_filename (MatitaAuthentication.read_ft uid)
+      with Not_found -> MatitaFilesystem.MUnversioned
+    in
+    (if old_flag <> MatitaFilesystem.MConflict &&
+       old_flag <> MatitaFilesystem.MAdd then
+      let newflag = 
+        if already_exists then MatitaFilesystem.MModified
+        else MatitaFilesystem.MAdd
+      in
+      MatitaAuthentication.set_file_flag uid [rel_filename, Some newflag]);
+    cgi # set_header 
+     ~cache:`No_cache 
+     ~content_type:"text/xml; charset=\"utf-8\""
+     ();
+    cgi#out_channel#output_string "<response>ok</response>"
+  with
+  | File_already_exists ->
+      cgi#out_channel#output_string "<response>cancelled</response>"
+  | Sys_error _ -> 
+    cgi # set_header
+      ~status:`Internal_server_error
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ()
+  | e ->
+      let estr = Printexc.to_string e in
+      cgi#out_channel#output_string ("<response>" ^ estr ^ "</response>"));
+  cgi#out_channel#commit_work()
+;;
+
+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
+  (try
+    let out = do_global_commit () in
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
-    cgi#out_channel#output_string "<response>ok</response>"
+    cgi#out_channel#output_string "<commit>";
+    cgi#out_channel#output_string "<response>ok</response>";
+    cgi#out_channel#output_string ("<details>" ^ out ^ "</details>");
+    cgi#out_channel#output_string "</commit>"
   with
   | Not_found _ -> 
     cgi # set_header
@@ -391,17 +601,38 @@ let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   cgi#out_channel#commit_work()
 ;;
 
-let initiate_commit (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
+let svn_update (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
   let env = cgi#environment in
+  let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
+  let sid = HExtlib.unopt sid in
+  let uid = MatitaAuthentication.user_of_session sid in
   (try
-    let errors = MatitaFilesystem.do_global_commit () in
-    prerr_endline ("commit errors: " ^ (String.concat " " errors));
+    let files,anomalies,(added,conflict,del,upd,merged) = 
+      MatitaFilesystem.update_user uid 
+    in
+    let anomalies = String.concat "\n" anomalies in
+    let details = Printf.sprintf 
+      ("%d new files\n"^^
+       "%d deleted files\n"^^
+       "%d updated files\n"^^
+       "%d merged files\n"^^
+       "%d conflicting files\n\n" ^^
+       "Anomalies:\n%s") added del upd merged conflict anomalies
+    in
+    prerr_endline ("update details:\n" ^ details);
+    let details = 
+      Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () details
+    in
+    MatitaAuthentication.set_file_flag uid files;
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
-    cgi#out_channel#output_string "<response>ok</response>"
+    cgi#out_channel#output_string "<update>";
+    cgi#out_channel#output_string "<response>ok</response>";
+    cgi#out_channel#output_string ("<details>" ^ details ^ "</details>");
+    cgi#out_channel#output_string "</update>";
   with
   | Not_found _ -> 
     cgi # set_header
@@ -427,7 +658,7 @@ let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ();
     *)
     let text = cgi#argument_value "body" in
-    prerr_endline ("body =\n" ^ text);
+    (* 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);
@@ -437,13 +668,28 @@ let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
        new_parsed ^ "</parsed>" ^ txt 
        ^ "</response>"
     in 
-    prerr_endline ("sending advance response:\n" ^ body);
+    (* prerr_endline ("sending advance response:\n" ^ body); *)
+    cgi # set_header 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ();
+    cgi#out_channel#output_string body
+   with
+  | Emphasized_error text ->
+(* | MultiPassDisambiguator.DisambiguationError (offset,errorll) -> *)
+    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
+  | Ambiguous 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
-  with
   | Not_found _ -> 
     cgi # set_header
       ~status:`Internal_server_error
@@ -483,7 +729,7 @@ let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ();
     *)
     let text = cgi#argument_value "body" in
-    prerr_endline ("body =\n" ^ text);
+    (* prerr_endline ("body =\n" ^ text); *)
     let parsed_len, new_parsed = aux 0 "" text in
     let status = MatitaAuthentication.get_status sid in
     let txt = output_status status in
@@ -496,7 +742,7 @@ let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
        "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\" />" ^ txt 
        ^ "</response>"
     in*) 
-    prerr_endline ("sending goto bottom response:\n" ^ body);
+    (* prerr_endline ("sending goto bottom response:\n" ^ body); *)
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/xml; charset=\"utf-8\""
@@ -508,10 +754,46 @@ let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
   cgi#out_channel#commit_work() 
 ;;
 
+let gotoTop (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
+  let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
+  let env = cgi#environment in
+  prerr_endline "executing goto Top";
+  (try 
+    let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
+    let sid = HExtlib.unopt sid in
+    (*
+    cgi # set_header 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ();
+    *)
+    let status = MatitaAuthentication.get_status sid in
+    let uid = MatitaAuthentication.user_of_session sid in
+    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;
+    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;
+    cgi # set_header 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\""
+      ();
+    cgi#out_channel#output_string "<response>ok</response>"
+   with _ -> 
+     (cgi#set_header ~status:`Internal_server_error 
+      ~cache:`No_cache 
+      ~content_type:"text/xml; charset=\"utf-8\"" ();
+      cgi#out_channel#output_string "<response>ok</response>"));
+  cgi#out_channel#commit_work() 
+;;
+
 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
-  prerr_endline "executing retract";
   (try 
     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
     let sid = HExtlib.unopt sid in
@@ -528,13 +810,12 @@ let retract (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
           history, status
       | [_] -> (prerr_endline "singleton";failwith "retract")
       | _ -> (prerr_endline "nil"; assert false) in
-    prerr_endline "before time_travel";
+    prerr_endline ("prima della time travel");
     NCicLibrary.time_travel new_status;
-    prerr_endline "after time travel";
+    prerr_endline ("dopo della time travel");
     MatitaAuthentication.set_history sid new_history;
     MatitaAuthentication.set_status sid new_status;
-    prerr_endline ("after retract history.length = " ^ 
-      string_of_int (List.length new_history));
+    prerr_endline ("baseuri after retract = " ^ new_status#baseuri);
     let body = output_status new_status in
     cgi # set_header 
       ~cache:`No_cache 
@@ -562,7 +843,8 @@ let viewLib (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
     *)
     let uid = MatitaAuthentication.user_of_session sid in
     
-    let html = MatitaFilesystem.html_of_library uid in
+    let ft = MatitaAuthentication.read_ft uid in
+    let html = MatitaFilesystem.html_of_library uid ft in
     cgi # set_header 
       ~cache:`No_cache 
       ~content_type:"text/html; charset=\"utf-8\""
@@ -575,6 +857,14 @@ let viewLib (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
        "<script src=\"treeview/xmlTree.js\" type=\"text/javascript\"></script>\n" ^
        "<body>\n" ^ *)
        html (* ^ "\n</body></html>" *) );
+    
+    let files,anomalies = MatitaFilesystem.stat_user uid in
+    let changed = HExtlib.filter_map 
+      (fun (n,f) -> if (f = Some MatitaFilesystem.MModified) then Some n else None) files
+    in
+    let changed = String.concat "\n" changed in
+    let anomalies = String.concat "\n" anomalies in
+    prerr_endline ("Changed:\n" ^ changed ^ "\n\nAnomalies:\n" ^ anomalies);
   cgi#out_channel#commit_work()
   
 ;;
@@ -649,6 +939,13 @@ let start() =
       dyn_translator = (fun _ -> ""); (* not needed *)
       dyn_accept_all_conditionals = false;
     } in
+  let goto_top =
+    { Nethttpd_services.dyn_handler = (fun _ -> gotoTop);
+      dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
+      dyn_uri = None;                 (* not needed *)
+      dyn_translator = (fun _ -> ""); (* not needed *)
+      dyn_accept_all_conditionals = false;
+    } in
   let retrieve =
     { Nethttpd_services.dyn_handler = (fun _ -> retrieve);
       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
@@ -705,12 +1002,21 @@ let start() =
       dyn_translator = (fun _ -> ""); (* not needed *)
       dyn_accept_all_conditionals = false;
     } in 
+  let do_update =
+    { Nethttpd_services.dyn_handler = (fun _ -> svn_update);
+      dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
+      dyn_uri = None;                 (* not needed *)
+      dyn_translator = (fun _ -> ""); (* not needed *)
+      dyn_accept_all_conditionals = false;
+    } in 
+  
   
   let nethttpd_factory = 
     Nethttpd_plex.nethttpd_factory
       ~handlers:[ "advance", do_advance
                 ; "retract", do_retract
                 ; "bottom", goto_bottom
+                ; "top", goto_top
                 ; "open", retrieve 
                 ; "register", do_register
                 ; "login", do_login 
@@ -718,7 +1024,8 @@ let start() =
                 ; "reset", do_resetlib
                 ; "viewlib", do_viewlib
                 ; "save", do_save
-                ; "commit", do_commit]
+                ; "commit", do_commit
+               ; "update", do_update]
       () in
   MatitaInit.initialize_all ();
   MatitaAuthentication.deserialize ();