]> matita.cs.unibo.it Git - helm.git/blobdiff - matitaB/matita/matitadaemon.ml
Matitaweb: fixes compilation errors and minor graphical problems.
[helm.git] / matitaB / matita / matitadaemon.ml
index 606ccea4a755878eced8b61addcab5a02a5c7668..81fa956e1161b87855080b26a7882bb647c57b40 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" 
@@ -13,6 +16,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
  *)
@@ -29,9 +44,13 @@ let do_global_commit () =
        let ft = MatitaAuthentication.read_ft u in
 
        (* first we add new files/dirs to the repository *)
-       let to_be_added = List.map fst  
-         (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MAdd) ft)
+       (* 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
@@ -120,7 +139,10 @@ let do_global_commit () =
          (String.concat ", " not_added)
          (String.concat ", " not_committed) (String.concat ", " conflicts)))
 
-  "" (List.rev !to_be_committed)
+  (* 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 ***)
@@ -133,31 +155,88 @@ 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
+  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.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
@@ -229,18 +308,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 =
@@ -336,23 +403,78 @@ let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
 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
-  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); *)
+  let (st,new_statements,new_unparsed),parsed_len =
+    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) 
+    | NTacStatus.Error (s,None) as e ->
+        prerr_endline 
+          ("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
+    | 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
   MatitaAuthentication.set_status sid st;
   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
@@ -480,8 +602,6 @@ let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
         (* prerr_endline ("serializing proof objects..."); *)
         GrafiteTypes.Serializer.serialize 
           ~baseuri:(NUri.uri_of_string status#baseuri) status;
-        (* prerr_endline ("adding to the commit queue..."); *)
-        add_user_for_commit uid;
         (* prerr_endline ("done."); *)
        end;
      end;
@@ -613,7 +733,22 @@ let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
       ~content_type:"text/xml; charset=\"utf-8\""
       ();
     cgi#out_channel#output_string body
-  with
+   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
   | Not_found _ -> 
     cgi # set_header
       ~status:`Internal_server_error
@@ -637,14 +772,14 @@ let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
         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 -> 
+      | (* End_of_file *) _ -> 
           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
+      (*| _ -> parsed_len, parsed_txt*)
     in
     (* 
     cgi # set_header