]> matita.cs.unibo.it Git - helm.git/blobdiff - matitaB/matita/matitadaemon.ml
Multi-user matita: changed the status object to include a ``user'' method
[helm.git] / matitaB / matita / matitadaemon.ml
index d1a7e207226d759d1992adee1ec80c0fe21a752f..8dbfa45112cc9be7074e37969fe5bdd7f4d83dc8 100644 (file)
@@ -1,6 +1,16 @@
 open Printf;;
 open Http_types;;
 
+module Stack = Continuationals.Stack
+
+let utf8_length = Netconversion.ustring_length `Enc_utf8
+
+let utf8_parsed_text s floc =
+  let start, stop = HExtlib.loc_of_floc floc in
+  let len = stop - start in
+  let res = Netconversion.ustring_sub `Enc_utf8 start len s in
+  res, String.length res
+
 (*** from matitaScript.ml ***)
 (* let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$" *)
 
@@ -23,65 +33,107 @@ let eval_statement include_paths (* (buffer : GText.buffer) *) status (* script
   | GrafiteAst.Comment (loc, _) -> loc in
   
   let _,lend = HExtlib.loc_of_floc floc in 
-  let parsed_text, parsed_text_len = 
-    MatitaGtkMisc.utf8_parsed_text unparsed_text (HExtlib.floc_of_loc (0,lend)) in
+  let parsed_text, _parsed_text_len = 
+    utf8_parsed_text unparsed_text (HExtlib.floc_of_loc (0,lend)) 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 status = 
     MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
   in 
-  (status, parsed_text),"",(*parsed_text_len*) Glib.Utf8.length parsed_text
+  (status, parsed_text, unparsed_txt'),"",(*parsed_text_len*)
+    utf8_length parsed_text
 
+(* FIXME: currently hard coded to single user mode *)
+let status = ref (new MatitaEngine.status (Some "ricciott") "cic:/matita");;
+let history = ref [!status];;
+let sequent_size = ref 40;;
 
-let status = ref (new MatitaEngine.status "cic:/matita");;
+let include_paths = ref [];;
 
-let include_paths = ["/home/barolo/matitaB/matita/lib"];;
+(* <metasenv>
+ *   <meta number="...">
+ *     <metaname>...</metaname>
+ *     <goal>...</goal>
+ *   </meta>
+ *
+ *   ...
+ * </metasenv> *)
+let output_status s =
+  let _,_,metasenv,subst,_ = s#obj in
+  let render_switch = function 
+  | Stack.Open i -> "?" ^ (string_of_int i) 
+  | Stack.Closed i -> "<S>?" ^ (string_of_int i) ^ "</S>"
+  in
+  let int_of_switch = function
+  | Stack.Open i | Stack.Closed i -> i
+  in
+  let sequent = function
+  | Stack.Open i ->
+      let meta = List.assoc i metasenv in
+      snd (ApplyTransformation.ntxt_of_cic_sequent 
+        ~metasenv ~subst ~map_unicode_to_tex:false !sequent_size s (i,meta))
+  | Stack.Closed _ -> "This goal has already been closed."
+  in
+  let render_sequent is_loc acc depth tag (pos,sw) =
+    let metano = int_of_switch sw in
+    let markup = 
+      if is_loc then
+        (match depth, pos with
+         | 0, 0 -> "<B>" ^ (render_switch sw) ^ "</B>"
+         | 0, _ -> 
+            Printf.sprintf "<B>|<SUB>%d</SUB>: %s</B>" pos (render_switch sw)
+         | 1, pos when Stack.head_tag s#stack = `BranchTag ->
+             Printf.sprintf "|<SUB>%d</SUB> : %s" 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      
+    let txt0 = "<goal>" ^ sequent ^ "</goal>" in
+    "<meta number=\"" ^ (string_of_int metano) ^ "\">" ^ markup ^
+    txt0 ^ "</meta>" ^ acc
+  in
+  let res = "<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
+;;
 
-let advance text (* (?bos=false) *) =
-   (* if bos then LibraryClean.clean_baseuris [self#buri_of_current_file];
-   (* HLog.debug ("evaluating: " ^ first_line s ^ " ...");*)
-   let time1 = Unix.gettimeofday () in
-   let entries, newtext, parsed_len = *)
-     let (st,_),_,parsed_len =
-       (* try *)
-         eval_statement include_paths (*buffer*) !status (`Raw text)
-       (* with End_of_file -> raise Margin *)
-     in
-     status := st; 
-     let _,_,metasenv,subst,_ = !status#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 !status
-           meta) in
-          prerr_endline ("### txt0 = " ^ txt0);
-         ("<B>Goal ?" ^ (string_of_int nmeta) ^ "</B>\n" ^ txt0)::acc)
-       [] metasenv
-     in
-     let txt = String.concat "\n\n" txt in
-     parsed_len, txt
-   (*in
-   let time2 = Unix.gettimeofday () in
-   HLog.debug ("... done in " ^ string_of_float (time2 -. time1) ^ "s");
-   let new_statuses, new_statements =
-     let statuses, texts = List.split entries in
-     statuses, texts
-   in
-   history <- new_statuses @ history;
-   statements <- new_statements @ statements;
-   let start = buffer#get_iter_at_mark (`MARK locked_mark) in
-   let new_text = String.concat "" (List.rev new_statements) in
-   if statement <> None then
-     buffer#insert ~iter:start new_text
-   else begin
-     let parsed_text = String.sub s 0 parsed_len in
-     if new_text <> parsed_text then begin
-       let stop = start#copy#forward_chars (Glib.Utf8.length parsed_text) in
-       buffer#delete ~start ~stop;
-       buffer#insert ~iter:start new_text;
-     end;
-   end;
-   self#moveMark (Glib.Utf8.length new_text);
-   buffer#insert ~iter:(buffer#get_iter_at_mark (`MARK locked_mark)) newtext*)
+(* 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 heading_nl_RE = Pcre.regexp "^\\s*\n\\s*";;
+
+let first_line s =
+  let s = Pcre.replace ~rex:heading_nl_RE s in
+  try
+    let nl_pos = String.index s '\n' in
+    String.sub s 0 nl_pos
+  with Not_found -> s
 ;;
 
 let read_file fname =
@@ -92,7 +144,7 @@ let read_file fname =
        lines := input_line chan :: !lines
      done;
    with End_of_file -> close_in chan);
-  String.concat "\r\n" (List.rev !lines)
+  String.concat "\n" (List.rev !lines)
 ;;
 
 let load_index outchan =
@@ -100,106 +152,214 @@ let load_index outchan =
   Http_daemon.respond ~headers:["Content-Type", "text/html"] ~code:(`Code 200) ~body:s outchan
 ;;
 
-let call_service outchan =
-  try 
-   (ignore(MatitaEngine.assert_ng 
-     ~include_paths:["/home/barolo/matitaB/matita/lib"] (* ~outch:outchan *)
-    "/home/barolo/matitaB/matita/lib/basics/pts.ma");
-    prerr_endline "fatto";
-    let s = read_file "/home/barolo/matitaB/matita/lib/basics/pts.ma.mad"
-    in
-    Http_daemon.respond ~headers:["Content-Type", "text/html"] ~code:(`Code 200) ~body:s outchan
-   )
-  with
-  e -> Http_daemon.respond ~code:(`Code 500) outchan
+let load_doc filename outchan =
+  let s = read_file filename in
+  let is_png = 
+    try String.sub filename (String.length filename - 4) 4 = ".png"
+    with Invalid_argument _ -> false
+  in
+  let contenttype = if is_png then "image/png" else "text/html" in
+  Http_daemon.respond ~headers:["Content-Type", contenttype] ~code:(`Code 200) ~body:s outchan
 ;;
 
-let callback req outchan =
-  let str = 
-    (sprintf "request path = %s\n"  req#path) ^
-    (sprintf "request GET params = %s\n"
-      (String.concat ";"
-        (List.map (fun (h,v) -> String.concat "=" [h;v]) req#params_GET))) ^
-    (sprintf "request POST params = %s\n"
-      (String.concat ";"
-        (List.map (fun (h,v) -> String.concat "=" [h;v]) req#params_POST))) ^
-    (sprintf "request ALL params = %s\n"
-      (String.concat ";"
-        (List.map (fun (h,v) -> String.concat "=" [h;v]) req#params))) ^
-    (sprintf "cookies = %s\n"
-      (match req#cookies with
-      | None ->
-          "NO COOKIES "
-          ^ (if req#hasHeader ~name:"cookie"
-             then "('Cookie:' header was '" ^ req#header ~name:"cookie" ^ "')"
-             else "(No 'Cookie:' header received)")
-      | Some cookies ->
-          (String.concat ";"
-            (List.map (fun (n,v) -> String.concat "=" [n;v]) cookies)))) ^
-    (sprintf "request BODY = '%s'\n\n" req#body)
-  in
-  (* Http_daemon.respond ~code:(`Code 200) ~body: str outchan *)
-
-  prerr_endline str;
-
-  match req#path with
-  | "/" -> load_index outchan
-  | "/matita" -> call_service outchan
-  | "/open" ->
-      prerr_endline "getting 'file' argument";
-      let filename = List.assoc "file" req#params_GET in
-      prerr_endline ("reading file " ^ filename);
-      let body = read_file filename in
-      let _,baseuri,_,_ = 
-        Librarian.baseuri_of_script ~include_paths:[] filename
+let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
+  let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
+  cgi # set_header 
+    ~cache:`No_cache 
+    ~content_type:"text/xml; charset=\"utf-8\""
+    ();
+  let filename = cgi # argument_value "file" in
+  prerr_endline ("reading file " ^ filename);
+  let body = 
+    Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () 
+      (read_file filename) in
+  prerr_endline ("sending:\nBEGIN\n" ^ body ^ "\nEND");
+  let body = "<file>" ^ body ^ "</file>" in
+  let baseuri, incpaths = 
+    try 
+      let root, baseuri, _fname, _tgt = 
+        Librarian.baseuri_of_script ~include_paths:[] filename in 
+      let includes =
+       try
+        Str.split (Str.regexp " ") 
+         (List.assoc "include_paths" (Librarian.load_root_file (root^"/root")))
+       with Not_found -> []
       in
-      status := (!status)#set_baseuri baseuri;
-      Http_daemon.respond ~code:(`Code 200) ~body outchan
-  | "/advance" ->
-      let script = req#body in
-      prerr_endline ("body length = " ^ (string_of_int (String.length script)));
-      let (parsed_len,txt), res, code =
-        try advance script, "OK", `Code 200
-        with 
-        | HExtlib.Localized(_,e) 
-        | e -> 
-                (prerr_endline ("exception: " ^ Printexc.to_string e);
-                (try 
-                  NTacStatus.pp_tac_status !status
-                with e -> prerr_endline ("inner exception: " ^
-                  Printexc.to_string e));
-                prerr_endline "end status";
-                let _,_,metasenv,subst,_ = !status#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 !status
-                      meta) in
-                     prerr_endline ("### txt0 = " ^ txt0);
-                    ("<B>Goal ?" ^ (string_of_int nmeta) ^ "</B>\n" ^ txt0)::acc)
-                  [] metasenv
-                in
-                let txt = String.concat "\n\n" txt in
-                (0,txt), Printexc.to_string e, `Code 500)
-      in
-      let txt = Netencoding.Url.encode ~plus:false txt in
-      let body = (string_of_int parsed_len) ^ "#" ^ txt in
-      Http_daemon.respond ~code ~body outchan
-  | url -> Http_daemon.respond_not_found ~url outchan  
-
+      let rc = root :: includes in
+       List.iter (HLog.debug) rc; baseuri, rc
+     with 
+       Librarian.NoRootFor _ | Librarian.FileNotFound _ -> "",[] in
+  include_paths := incpaths;
+  status := (!status)#set_baseuri baseuri;
+  cgi#out_channel#output_string body;
+  cgi#out_channel#commit_work()
 ;;
 
+let advance0 text =
+  let (st,new_statements,new_unparsed),(* newtext TODO *) _,parsed_len =
+       (* try *)
+         eval_statement !include_paths (*buffer*) !status (`Raw text)
+       (* with End_of_file -> raise Margin *)
+     in
+  status := st;
+  history := st :: !history;
+  prerr_endline ("after advance0 history.length = " ^ string_of_int (List.length !history));
+  parsed_len, new_unparsed
 
 
-let spec =
-  { Http_daemon.default_spec with
-      callback = callback;
-      port = 9999;
-      mode = `Single;
-  }
+(* returns the length of the executed text and an html representation of the
+ * current metasenv*)
+let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
+  let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
+  cgi # set_header 
+    ~cache:`No_cache 
+    ~content_type:"text/xml; charset=\"utf-8\""
+    ();
+  let text = cgi#argument_value "body" in
+  prerr_endline ("body =\n" ^ text);
+  let parsed_len, new_unparsed = advance0 text in
+  let txt = output_status !status in
+  let body = 
+     "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\" />" ^ txt 
+     ^ "</response>"
+  in 
+  prerr_endline ("sending advance response:\n" ^ body);
+  cgi#out_channel#output_string body;
+  cgi#out_channel#commit_work()
 ;;
 
-let _ =
+let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
+  let rec aux parsed_len text =
+    try
+      prerr_endline ("evaluating: " ^ first_line text);
+      let plen,new_unparsed = advance0 text in
+      aux (parsed_len+plen) new_unparsed
+    with 
+    | _ -> parsed_len
+  in 
+  let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
+  cgi # set_header 
+    ~cache:`No_cache 
+    ~content_type:"text/xml; charset=\"utf-8\""
+    ();
+  let text = cgi#argument_value "body" in
+  prerr_endline ("body =\n" ^ text);
+  let parsed_len = aux 0 text in
+  let txt = output_status !status in
+  let body = 
+     "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\" />" ^ txt 
+     ^ "</response>"
+  in 
+  prerr_endline ("sending goto bottom response:\n" ^ body);
+  cgi#out_channel#output_string body;
+  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
+  cgi # set_header 
+    ~cache:`No_cache 
+    ~content_type:"text/xml; charset=\"utf-8\""
+    ();
+  let new_history,new_status =
+     match !history with
+       _::(status::_ as history) ->
+        history, status
+    | [_] -> (prerr_endline "singleton";failwith "retract")
+    | _ -> (prerr_endline "nil"; assert false) in
+  NCicLibrary.time_travel new_status;
+  history := new_history;
+  status := new_status;
+  prerr_endline ("after retract history.length = " ^ string_of_int (List.length !history));
+  let body = output_status !status in
+  cgi#out_channel#output_string body;
+  cgi#out_channel#commit_work() 
+;;
+
+
+open Netcgi1_compat.Netcgi_types;;
+
+(**********************************************************************)
+(* Create the webserver                                               *)
+(**********************************************************************)
+
+
+let start() =
+  let (opt_list, cmdline_cfg) = Netplex_main.args() in
+
+  let use_mt = ref true in
+
+  let opt_list' =
+    [ "-mt", Arg.Set use_mt,
+      "  Use multi-threading instead of multi-processing"
+    ] @ opt_list in
+
+  Arg.parse 
+    opt_list'
+    (fun s -> raise (Arg.Bad ("Don't know what to do with: " ^ s)))
+    "usage: netplex [options]";
+  let parallelizer = 
+    if !use_mt then
+      Netplex_mt.mt()     (* multi-threading *)
+    else
+      Netplex_mp.mp() in  (* multi-processing *)
+(*
+  let adder =
+    { Nethttpd_services.dyn_handler = (fun _ -> process1);
+      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 do_advance =
+    { Nethttpd_services.dyn_handler = (fun _ -> advance);
+      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 do_retract =
+    { Nethttpd_services.dyn_handler = (fun _ -> retract);
+      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 goto_bottom =
+    { Nethttpd_services.dyn_handler = (fun _ -> gotoBottom);
+      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;
+      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
+                ; "open", retrieve ]
+      () in
   MatitaInit.initialize_all ();
-  Http_daemon.main spec
+  (* test begin *)
+  MatitaAuthentication.add_user "ricciott" "pippo123";
+  MatitaAuthentication.add_user "asperti" "pluto456";
+  (* test end *)
+  Netplex_main.startup
+    parallelizer
+    Netplex_log.logger_factories   (* allow all built-in logging styles *)
+    Netplex_workload.workload_manager_factories (* ... all ways of workload management *)
+    [ nethttpd_factory ]           (* make this nethttpd available *)
+    cmdline_cfg
 ;;
+
+Sys.set_signal Sys.sigpipe Sys.Signal_ignore;
+start();;