]> matita.cs.unibo.it Git - helm.git/blob - matitaB/matita/matitadaemon.ml
0c0f6cefda58da86b44c768b1d2d6c778d06004d
[helm.git] / matitaB / matita / matitadaemon.ml
1 open Printf;;
2 open Http_types;;
3
4 exception Emphasized_error of string
5 exception Disamb_error of string
6
7 module Stack = Continuationals.Stack
8
9 (* disable for debug *)
10 let prerr_endline _ = ()
11
12 let rt_path () = Helm_registry.get "matita.rt_base_dir" 
13
14 let libdir uid = (rt_path ()) ^ "/users/" ^ uid 
15
16 let utf8_length = Netconversion.ustring_length `Enc_utf8
17
18 let mutex = Mutex.create ();;
19
20 let to_be_committed = ref [];;
21
22 let html_of_matita s =
23   let patt1 = Str.regexp "\005" in
24   let patt2 = Str.regexp "\006" in
25   let patt3 = Str.regexp "<" in
26   let patt4 = Str.regexp ">" in
27   let res = Str.global_replace patt4 "&gt;" s in
28   let res = Str.global_replace patt3 "&lt;" res in
29   let res = Str.global_replace patt2 ">" res in
30   let res = Str.global_replace patt1 "<" res in
31   res
32 ;;
33
34 (* adds a user to the commit queue; concurrent instances possible, so we
35  * enclose the update in a CS
36  *)
37 let add_user_for_commit uid =
38   Mutex.lock mutex;
39   to_be_committed := uid::List.filter (fun x -> x <> uid) !to_be_committed;
40   Mutex.unlock mutex;
41 ;;
42
43 let do_global_commit () =
44   prerr_endline ("to be committed: " ^ String.concat " " !to_be_committed);
45   List.fold_left
46     (fun out u ->
47        let ft = MatitaAuthentication.read_ft u in
48
49        (* first we add new files/dirs to the repository *)
50        (* must take the reverse because svn requires the add to be performed in
51           the correct order
52           (otherwise run with --parents option) *)
53        let to_be_added = List.rev (List.map fst  
54          (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MAdd) ft))
55        in
56        prerr_endline ("@@@ ADDING files: " ^ String.concat ", " to_be_added);
57        let out = 
58          try
59            let newout = MatitaFilesystem.add_files u to_be_added in
60            out ^ "\n" ^ newout
61          with
62          | MatitaFilesystem.SvnError outstr -> 
63              prerr_endline ("ADD OF " ^ u ^ "FAILED:" ^ outstr);
64              out
65        in
66
67        (* now we update the local copy (to merge updates from other users) *)
68        let out = try
69          let files,anomalies,(added,conflict,del,upd,merged) = 
70            MatitaFilesystem.update_user u 
71          in
72          let anomalies = String.concat "\n" anomalies in
73          let details = Printf.sprintf 
74            ("%d new files\n"^^
75             "%d deleted files\n"^^
76             "%d updated files\n"^^
77             "%d merged files\n"^^
78             "%d conflicting files\n\n" ^^
79             "Anomalies:\n%s") added del upd merged conflict anomalies
80          in
81          prerr_endline ("update details:\n" ^ details);
82          MatitaAuthentication.set_file_flag u files;
83          out ^ "\n" ^ details 
84          with
85          | MatitaFilesystem.SvnError outstr -> 
86              prerr_endline ("UPDATE OF " ^ u ^ "FAILED:" ^ outstr);
87              out
88        in
89
90        (* we re-read the file table after updating *)
91        let ft = MatitaAuthentication.read_ft u in
92
93        (* finally we perform the real commit *)
94        let modified = (List.map fst
95          (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MModified) ft))
96        in
97        let to_be_committed = to_be_added @ modified
98        in
99        let out = try
100          let newout = MatitaFilesystem.commit u to_be_committed in
101          out ^ "\n" ^ newout
102          with
103          | MatitaFilesystem.SvnError outstr -> 
104              prerr_endline ("COMMIT OF " ^ u ^ "FAILED:" ^ outstr);
105              out
106        in
107
108        (* call stat to get the final status *)
109        let files, anomalies = MatitaFilesystem.stat_user u in
110        let added,not_added = List.fold_left 
111          (fun (a_acc, na_acc) fname ->
112             if List.mem fname (List.map fst files) then
113                a_acc, fname::na_acc
114             else
115                fname::a_acc, na_acc)
116          ([],[]) to_be_added
117        in
118        let committed,not_committed = List.fold_left 
119          (fun (c_acc, nc_acc) fname ->
120             if List.mem fname (List.map fst files) then
121                c_acc, fname::nc_acc
122             else
123                fname::c_acc, nc_acc)
124          ([],[]) modified
125        in
126        let conflicts = List.map fst (List.filter 
127          (fun (_,f) -> f = Some MatitaFilesystem.MConflict) files)
128        in
129        MatitaAuthentication.set_file_flag u
130          (List.map (fun x -> x, Some MatitaFilesystem.MSynchronized) (added@committed));
131        MatitaAuthentication.set_file_flag u files;
132        out ^ "\n\n" ^ (Printf.sprintf
133         ("COMMIT RESULTS for %s\n" ^^
134          "==============\n" ^^
135          "added and committed (%d of %d): %s\n" ^^
136          "modified and committed (%d of %d): %s\n" ^^
137          "not added: %s\n" ^^
138          "not committed: %s\n" ^^
139          "conflicts: %s\n")
140          u (List.length added) (List.length to_be_added) (String.concat ", " added)
141          (List.length committed) (List.length modified) (String.concat ", " committed)
142          (String.concat ", " not_added)
143          (String.concat ", " not_committed) (String.concat ", " conflicts)))
144
145   (* XXX: at the moment, we don't keep track of the order in which users have 
146      scheduled their commits, but we should, otherwise we will get a 
147      "first come, random served" policy *)
148   "" (* (List.rev !to_be_committed) *) (MatitaAuthentication.get_users ())
149 ;;
150
151 (*** from matitaScript.ml ***)
152 (* let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$" *)
153
154 let eval_statement include_paths (* (buffer : GText.buffer) *) status (* script *)
155  statement
156 =
157   let ast,unparsed_text =
158     match statement with
159     | `Raw text ->
160         (* if Pcre.pmatch ~rex:only_dust_RE text then raise Margin; *)
161         prerr_endline ("raw text = " ^ text);
162         let strm =
163          GrafiteParser.parsable_statement status
164           (Ulexing.from_utf8_string text) in
165         prerr_endline "before get_ast";
166         let ast = MatitaEngine.get_ast status include_paths strm in
167         prerr_endline "after get_ast";
168          ast, text
169     | `Ast (st, text) -> st, text
170   in
171
172   (* do we want to generate a trace? *)
173   let is_auto (l,a) = 
174     not (List.mem_assoc "demod" a || List.mem_assoc "paramod" a ||
175       List.mem_assoc "fast_paramod" a || List.assoc "depth" a = "1" ||
176       l <> None)
177   in
178
179   let get_param a param = 
180      try 
181        Some (param ^ "=" ^ List.assoc param a)
182      with Not_found -> None
183   in
184
185   let floc = match ast with
186   | GrafiteAst.Executable (loc, _)
187   | GrafiteAst.Comment (loc, _) -> loc in
188   
189   let lstart,lend = HExtlib.loc_of_floc floc in 
190   let parsed_text, _parsed_text_len = 
191     HExtlib.utf8_parsed_text unparsed_text (HExtlib.floc_of_loc (0,lend)) in
192   let parsed_text_len = utf8_length parsed_text in
193   let byte_parsed_text_len = String.length parsed_text in
194   let unparsed_txt' = 
195     String.sub unparsed_text byte_parsed_text_len 
196       (String.length unparsed_text - byte_parsed_text_len)
197   in
198   prerr_endline (Printf.sprintf "ustring_sub caso 1: lstart=%d, parsed=%s" lstart parsed_text);
199   let pre = Netconversion.ustring_sub `Enc_utf8  0 lstart parsed_text in
200
201   let mk_univ trace = 
202     let href r = 
203       Printf.sprintf "\005A href=\"%s\"\006%s\005/A\006"
204         (NReference.string_of_reference r) (NCicPp.r2s status true r)
205     in
206     (*if trace = [] then "{}"
207     else*) String.concat ", " 
208       (HExtlib.filter_map (function 
209         | NotationPt.NRef r -> Some (href r) 
210         | _ -> None)
211       trace)
212   in
213   
214   match ast with
215   | GrafiteAst.Executable (_,
216       GrafiteAst.NTactic (_,
217         [GrafiteAst.NAuto (_, (l,a as auto_params))])) when is_auto auto_params
218           ->
219           let l = match l with
220           | None -> None
221           | Some (_,l') -> Some (List.map (fun x -> "",0,x) l')
222           in
223           let trace_ref = ref [] in
224           let status = NnAuto.auto_tac ~params:(l,a) ~trace_ref status in
225           let new_parsed_text = pre ^ (Printf.sprintf 
226             "/\005span class='autotactic'\006%s\005span class='autotrace'\006 trace %s\005/span\006\005/span\006/"
227              (String.concat " " 
228                (List.assoc "depth" a::
229                 HExtlib.filter_map (get_param a) ["width";"size"]))
230              (mk_univ !trace_ref))
231           in
232           (status,new_parsed_text, unparsed_txt'),parsed_text_len
233   | _ ->
234       let status = 
235         MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
236       in
237       let new_parsed_text = Ulexing.from_utf8_string parsed_text in
238       let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
239       let outstr = ref "" in
240       ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
241       prerr_endline ("baseuri after advance = " ^ status#baseuri);
242       (* prerr_endline ("parser output: " ^ !outstr); *)
243       (status,!outstr, unparsed_txt'),parsed_text_len
244
245 (*let save_moo status = 
246   let script = MatitaScript.current () in
247   let baseuri = status#baseuri in
248   match script#bos, script#eos with
249   | true, _ -> ()
250   | _, true ->
251      GrafiteTypes.Serializer.serialize ~baseuri:(NUri.uri_of_string baseuri)
252       status
253   | _ -> clean_current_baseuri status 
254 ;;*)
255     
256 let sequent_size = ref 40;;
257
258 let include_paths = ref [];;
259
260 (* <metasenv>
261  *   <meta number="...">
262  *     <metaname>...</metaname>
263  *     <goal>...</goal>
264  *   </meta>
265  *
266  *   ...
267  * </metasenv> *)
268 let output_status s =
269   let _,_,metasenv,subst,_ = s#obj in
270   let render_switch = function 
271   | Stack.Open i -> "?" ^ (string_of_int i) 
272   | Stack.Closed i -> "<S>?" ^ (string_of_int i) ^ "</S>"
273   in
274   let int_of_switch = function
275   | Stack.Open i | Stack.Closed i -> i
276   in
277   let sequent = function
278   | Stack.Open i ->
279       let meta = List.assoc i metasenv in
280       snd (ApplyTransformation.ntxt_of_cic_sequent 
281         ~metasenv ~subst ~map_unicode_to_tex:false !sequent_size s (i,meta))
282   | Stack.Closed _ -> "This goal has already been closed."
283   in
284   let render_sequent is_loc acc depth tag (pos,sw) =
285     let metano = int_of_switch sw in
286     let markup = 
287       if is_loc then
288         (match depth, pos with
289          | 0, 0 -> "<span class=\"activegoal\">" ^ (render_switch sw) ^ "</span>"
290          | 0, _ -> 
291             Printf.sprintf "<span class=\"activegoal\">|<SUB>%d</SUB>: %s</span>" pos (render_switch sw)
292          | 1, pos when Stack.head_tag s#stack = `BranchTag ->
293              Printf.sprintf "<span class=\"passivegoal\">|<SUB>%d</SUB> : %s</span>" pos (render_switch sw)
294          | _ -> render_switch sw)
295       else render_switch sw
296     in
297     let markup = 
298       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () markup in
299     let markup = "<metaname>" ^ markup ^ "</metaname>" in
300     let sequent =
301       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () (sequent sw)
302     in      
303     let txt0 = "<goal>" ^ sequent ^ "</goal>" in
304     "<meta number=\"" ^ (string_of_int metano) ^ "\">" ^ markup ^
305     txt0 ^ "</meta>" ^ acc
306   in
307   "<metasenv>" ^
308     (Stack.fold 
309       ~env:(render_sequent true) ~cont:(render_sequent false) 
310       ~todo:(render_sequent false) "" s#stack) ^
311     "</metasenv>"
312   (* prerr_endline ("sending metasenv:\n" ^ res); res *)
313 ;;
314
315 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*";;
316
317 let first_line s =
318   let s = Pcre.replace ~rex:heading_nl_RE s in
319   try
320     let nl_pos = String.index s '\n' in
321     String.sub s 0 nl_pos
322   with Not_found -> s
323 ;;
324
325 let read_file fname =
326   let chan = open_in fname in
327   let lines = ref [] in
328   (try
329      while true do
330        lines := input_line chan :: !lines
331      done;
332    with End_of_file -> close_in chan);
333   String.concat "\n" (List.rev !lines)
334 ;;
335
336 let load_index outchan =
337   let s = read_file "index.html" in
338   Http_daemon.respond ~headers:["Content-Type", "text/html"] ~code:(`Code 200) ~body:s outchan
339 ;;
340
341 let load_doc filename outchan =
342   let s = read_file filename in
343   let is_png = 
344     try String.sub filename (String.length filename - 4) 4 = ".png"
345     with Invalid_argument _ -> false
346   in
347   let contenttype = if is_png then "image/png" else "text/html" in
348   Http_daemon.respond ~headers:["Content-Type", contenttype] ~code:(`Code 200) ~body:s outchan
349 ;;
350
351 let retrieve (cgi : Netcgi.cgi_activation) =
352   let env = cgi#environment in
353   (try 
354     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
355     let sid = HExtlib.unopt sid in
356     let uid = MatitaAuthentication.user_of_session sid in
357     (*
358     cgi # set_header 
359       ~cache:`No_cache 
360       ~content_type:"text/xml; charset=\"utf-8\""
361       ();
362     *)
363     let filename = libdir uid ^ "/" ^ (cgi # argument_value "file") in
364     (* prerr_endline ("reading file " ^ filename); *)
365     let body = 
366      Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false ()
367         (html_of_matita (read_file filename)) in
368      
369      (*   html_of_matita (read_file filename) in *)
370     (* prerr_endline ("sending:\nBEGIN\n" ^ body ^ "\nEND"); *)
371     let body = "<response><file>" ^ body ^ "</file></response>" in
372     let baseuri, incpaths = 
373       try 
374         let root, baseuri, _fname, _tgt = 
375           Librarian.baseuri_of_script ~include_paths:[] filename in 
376         let includes =
377          try
378           Str.split (Str.regexp " ") 
379            (List.assoc "include_paths" (Librarian.load_root_file (root^"/root")))
380          with Not_found -> []
381         in
382         let rc = root :: includes in
383          List.iter (HLog.debug) rc; baseuri, rc
384        with 
385          Librarian.NoRootFor _ | Librarian.FileNotFound _ -> "",[] in
386     include_paths := incpaths;
387     let status = (MatitaAuthentication.get_status sid)#set_baseuri baseuri in
388     let history = [status] in
389     MatitaAuthentication.set_status sid status;
390     MatitaAuthentication.set_history sid history;
391     cgi # set_header 
392       ~cache:`No_cache 
393       ~content_type:"text/xml; charset=\"utf-8\""
394       ();
395     cgi#out_channel#output_string body;
396   with
397   | Not_found _ -> 
398     cgi # set_header
399       ~status:`Internal_server_error
400       ~cache:`No_cache 
401       ~content_type:"text/html; charset=\"utf-8\""
402       ());
403   cgi#out_channel#commit_work()
404 ;;
405
406 let xml_of_disamb_error l =
407   let mk_alias = function
408   | GrafiteAst.Ident_alias (_,uri) -> "href=\"" ^ uri ^ "\""
409   | GrafiteAst.Symbol_alias (_,uri,desc) 
410   | GrafiteAst.Number_alias (uri,desc) -> 
411       let uri = try HExtlib.unopt uri with _ -> "cic:/fakeuri.def(1)" in
412         "href=\"" ^ uri ^ "\" title=\"" ^ 
413         (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
414         ^ "\""
415   in
416
417   let mk_interpr (loc,a) =
418     let x,y = HExtlib.loc_of_floc loc in
419     Printf.sprintf "<interpretation start=\"%d\" stop=\"%d\" %s />"
420       x y (mk_alias a)
421   in
422
423   let mk_failure (il,loc,msg) =
424     let x,y = HExtlib.loc_of_floc loc in
425     Printf.sprintf "<failure start=\"%d\" stop=\"%d\" title=\"%s\">%s</failure>"
426       x y (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () msg)
427       (String.concat "" (List.map mk_interpr il))
428   in
429
430   let mk_choice (a,fl) = 
431     let fl' = String.concat "" (List.map mk_failure fl) in
432     match a with
433     | None -> "<choice>" ^ fl' ^ "</choice>"
434     | Some a -> Printf.sprintf "<choice %s>%s</choice>" (mk_alias a) fl'
435   in
436
437   let mk_located (loc,cl) =
438     let x,y = HExtlib.loc_of_floc loc in
439     Printf.sprintf "<choicepoint start=\"%d\" stop=\"%d\">%s</choicepoint>"
440       x y (String.concat "" (List.map mk_choice cl))
441   in
442   "<disamberror>" ^ (String.concat "" (List.map mk_located l)) ^ "</disamberror>"
443 ;;
444
445 let advance0 sid text =
446   let status = MatitaAuthentication.get_status sid in
447   let history = MatitaAuthentication.get_history sid in
448   let status = status#reset_disambiguate_db () in
449   let (st,new_statements,new_unparsed),parsed_len =
450     let rec do_exc = function
451     | HExtlib.Localized (floc,e) -> 
452       let x, y = HExtlib.loc_of_floc floc in
453       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
454       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
455       let post = Netconversion.ustring_sub `Enc_utf8 y 
456          (Netconversion.ustring_length `Enc_utf8 text - y) text in
457       let _,title = MatitaExcPp.to_string e in
458       (* let title = "" in *)
459       let marked = 
460         pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
461       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
462       () (html_of_matita marked) in
463       raise (Emphasized_error marked)
464     | Disambiguate.NoWellTypedInterpretation (floc,e) ->
465       let x, y = HExtlib.loc_of_floc floc in
466       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
467       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
468       let post = Netconversion.ustring_sub `Enc_utf8 y 
469          (Netconversion.ustring_length `Enc_utf8 text - y) text in
470       (*let _,title = MatitaExcPp.to_string e in*)
471       (* let title = "" in *)
472       let marked = 
473         pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
474       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
475       () (html_of_matita marked) in
476       raise (Emphasized_error marked)
477     | NCicRefiner.Uncertain m as exn ->
478       let floc, e = Lazy.force m in
479       let x, y = HExtlib.loc_of_floc floc in
480       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
481       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
482       let post = Netconversion.ustring_sub `Enc_utf8 y 
483          (Netconversion.ustring_length `Enc_utf8 text - y) text in
484       (* let _,title = MatitaExcPp.to_string e in *)
485       (* let title = "" in *)
486       let marked = 
487         pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
488       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
489       () (html_of_matita marked) in
490       raise (Emphasized_error marked)
491     | NTacStatus.Error (s,None) as e ->
492         prerr_endline 
493           ("NTacStatus.Error " ^ (Lazy.force s)); raise e
494     | NTacStatus.Error (s,Some exc) as e ->
495         prerr_endline 
496           ("NTacStatus.Error " ^ Lazy.force s ^ " -- " ^ (Printexc.to_string exc));
497         do_exc exc
498     | GrafiteDisambiguate.Ambiguous_input (loc,choices) ->
499       let x,y = HExtlib.loc_of_floc loc in
500       let choice_of_alias = function
501        | GrafiteAst.Ident_alias (_,uri) -> uri, None, uri
502        | GrafiteAst.Number_alias (None,desc)
503        | GrafiteAst.Symbol_alias (_,None,desc) -> "cic:/fakeuri.def(1)", Some desc, desc
504        | GrafiteAst.Number_alias (Some uri,desc)
505        | GrafiteAst.Symbol_alias (_,Some uri,desc) -> uri, Some desc, desc
506       in
507       let tag_of_choice (uri,title,desc) =
508         match title with
509         | None -> Printf.sprintf "<choice href=\"%s\">%s</choice>"
510             uri 
511             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
512         | Some t -> Printf.sprintf "<choice href=\"%s\" title=\"%s\">%s</choice>"
513             uri 
514             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () t)
515             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
516       in
517       let strchoices = 
518         String.concat "\n" 
519           (List.map (fun x -> tag_of_choice (choice_of_alias x)) choices)
520       in
521       prerr_endline (Printf.sprintf
522         "@@@ Ambiguous input at (%d,%d). Possible choices:\n\n%s\n\n@@@ End."
523           x y strchoices);
524       (*
525       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
526       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
527       let post = Netconversion.ustring_sub `Enc_utf8 y 
528          (Netconversion.ustring_length `Enc_utf8 text - y) text in
529       let title = "Disambiguation Error" in
530       (* let title = "" in *)
531       let marked = 
532         pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
533       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
534       () (html_of_matita marked) in
535       *)
536       let strchoices = Printf.sprintf
537         "<ambiguity start=\"%d\" stop=\"%d\">%s</ambiguity>" x y strchoices
538       in raise (Disamb_error strchoices)
539    | GrafiteDisambiguate.Error l -> raise (Disamb_error (xml_of_disamb_error l))
540    (* | End_of_file -> ...          *)
541    | e -> raise e
542    in
543
544     try
545       eval_statement !include_paths (*buffer*) status (`Raw text)
546     with e -> do_exc e
547   in
548   MatitaAuthentication.set_status sid st;
549   MatitaAuthentication.set_history sid (st::history);
550 (*  prerr_endline "previous timestamp";
551   status#print_timestamp();
552   prerr_endline "current timestamp";
553   st#print_timestamp(); *)
554   parsed_len, 
555     Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
556       () (html_of_matita new_statements), new_unparsed, st
557
558 let register (cgi : Netcgi.cgi_activation) =
559   let _env = cgi#environment in
560   
561   assert (cgi#arguments <> []);
562   let uid = cgi#argument_value "userid" in
563   let userpw = cgi#argument_value "password" in
564   (try
565     (* currently registering only unprivileged users *) 
566     MatitaAuthentication.add_user uid userpw false;
567 (*    env#set_output_header_field "Location" "/index.html" *)
568     cgi#out_channel#output_string
569      ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/login.html\">"
570      ^ "</head><body>Redirecting to login page...</body></html>")
571    with
572    | MatitaAuthentication.UsernameCollision _ ->
573       cgi#set_header
574        ~cache:`No_cache 
575        ~content_type:"text/html; charset=\"utf-8\""
576        ();
577      cgi#out_channel#output_string
578       "<html><head></head><body>Error: User id collision!</body></html>"
579    | MatitaFilesystem.SvnError msg ->
580       cgi#set_header
581        ~cache:`No_cache 
582        ~content_type:"text/html; charset=\"utf-8\""
583        ();
584      cgi#out_channel#output_string
585       ("<html><head></head><body><p>Error: Svn checkout failed!<p><p><textarea>"
586        ^ msg ^ "</textarea></p></body></html>"));
587   cgi#out_channel#commit_work()
588 ;;
589
590 let login (cgi : Netcgi.cgi_activation) =
591   let env = cgi#environment in
592   
593   assert (cgi#arguments <> []);
594   let uid = cgi#argument_value "userid" in
595   let userpw = cgi#argument_value "password" in
596   (try 
597       MatitaAuthentication.check_pw uid userpw;
598       NCicLibrary.init (Some uid);
599       let ft = MatitaAuthentication.read_ft uid in
600       let _ = MatitaFilesystem.html_of_library uid ft in
601        let sid = MatitaAuthentication.create_session uid in
602        (* let cookie = Netcgi.Cookie.make "session" (Uuidm.to_string sid) in
603           cgi#set_header ~set_cookies:[cookie] (); *)
604        env#set_output_header_field 
605          "Set-Cookie" ("session=" ^ (Uuidm.to_string sid));
606    (*    env#set_output_header_field "Location" "/index.html" *)
607        cgi#out_channel#output_string
608         ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/index.html\">"
609         ^ "</head><body>Redirecting to Matita page...</body></html>")
610   with MatitaAuthentication.InvalidPassword ->
611     cgi#set_header
612       ~cache:`No_cache 
613       ~content_type:"text/html; charset=\"utf-8\""
614       ();
615     cgi#out_channel#output_string
616       "<html><head></head><body>Authentication error</body></html>");
617   cgi#out_channel#commit_work()
618 ;;
619
620 let logout (cgi : Netcgi.cgi_activation) =
621   let env = cgi#environment in
622   (try 
623     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
624     let sid = HExtlib.unopt sid in
625     MatitaAuthentication.logout_user sid;
626     cgi # set_header 
627       ~cache:`No_cache 
628       ~content_type:"text/html; charset=\"utf-8\""
629       ();
630     let text = read_file (rt_path () ^ "/logout.html") in
631     cgi#out_channel#output_string text
632   with
633   | Not_found _ -> 
634     cgi # set_header
635       ~status:`Internal_server_error
636       ~cache:`No_cache 
637       ~content_type:"text/html; charset=\"utf-8\""
638       ());
639   cgi#out_channel#commit_work()
640 ;;
641
642 exception File_already_exists;;
643
644 let save (cgi : Netcgi.cgi_activation) =
645   let env = cgi#environment in
646   (try 
647     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
648     let sid = HExtlib.unopt sid in
649     let status = MatitaAuthentication.get_status sid in
650     let uid = MatitaAuthentication.user_of_session sid in
651     assert (cgi#arguments <> []);
652     let locked = cgi#argument_value "locked" in
653     let unlocked = cgi#argument_value "unlocked" in
654     let dir = cgi#argument_value "dir" in
655     let rel_filename = cgi # argument_value "file" in
656     let filename = libdir uid ^ "/" ^ rel_filename in
657     let force = bool_of_string (cgi#argument_value "force") in
658     let already_exists = Sys.file_exists filename in
659
660     if ((not force) && already_exists) then 
661       raise File_already_exists;
662
663     if dir = "true" then
664        Unix.mkdir filename 0o744
665     else 
666      begin
667       let oc = open_out filename in
668       output_string oc (locked ^ unlocked);
669       close_out oc;
670       if MatitaEngine.eos status unlocked then
671        begin
672         (* prerr_endline ("serializing proof objects..."); *)
673         GrafiteTypes.Serializer.serialize 
674           ~baseuri:(NUri.uri_of_string status#baseuri) status;
675         (* prerr_endline ("done."); *)
676        end;
677      end;
678     let old_flag =
679       try 
680         List.assoc rel_filename (MatitaAuthentication.read_ft uid)
681       with Not_found -> MatitaFilesystem.MUnversioned
682     in
683     (if old_flag <> MatitaFilesystem.MConflict &&
684        old_flag <> MatitaFilesystem.MAdd then
685       let newflag = 
686         if already_exists then MatitaFilesystem.MModified
687         else MatitaFilesystem.MAdd
688       in
689       MatitaAuthentication.set_file_flag uid [rel_filename, Some newflag]);
690     cgi # set_header 
691      ~cache:`No_cache 
692      ~content_type:"text/xml; charset=\"utf-8\""
693      ();
694     cgi#out_channel#output_string "<response>ok</response>"
695   with
696   | File_already_exists ->
697       cgi#out_channel#output_string "<response>cancelled</response>"
698   | Sys_error _ -> 
699     cgi # set_header
700       ~status:`Internal_server_error
701       ~cache:`No_cache 
702       ~content_type:"text/xml; charset=\"utf-8\""
703       ()
704   | e ->
705       let estr = Printexc.to_string e in
706       cgi#out_channel#output_string ("<response>" ^ estr ^ "</response>"));
707   cgi#out_channel#commit_work()
708 ;;
709
710 let initiate_commit (cgi : Netcgi.cgi_activation) =
711   let env = cgi#environment in
712   (try
713     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
714     let sid = HExtlib.unopt sid in
715     MatitaAuthentication.probe_commit_priv sid;
716     let out = do_global_commit () in
717     cgi # set_header 
718       ~cache:`No_cache 
719       ~content_type:"text/xml; charset=\"utf-8\""
720       ();
721     cgi#out_channel#output_string "<commit>";
722     cgi#out_channel#output_string "<response>ok</response>";
723     cgi#out_channel#output_string ("<details>" ^ out ^ "</details>");
724     cgi#out_channel#output_string "</commit>"
725   with
726   | Not_found _ -> 
727     cgi # set_header
728       ~status:`Internal_server_error
729       ~cache:`No_cache 
730       ~content_type:"text/xml; charset=\"utf-8\""
731       ());
732   cgi#out_channel#commit_work()
733 ;;
734
735 let svn_update (cgi : Netcgi.cgi_activation) =
736   let env = cgi#environment in
737   let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
738   let sid = HExtlib.unopt sid in
739   let uid = MatitaAuthentication.user_of_session sid in
740   (try
741     MatitaAuthentication.probe_commit_priv sid;
742     let files,anomalies,(added,conflict,del,upd,merged) = 
743       MatitaFilesystem.update_user uid 
744     in
745     let anomalies = String.concat "\n" anomalies in
746     let details = Printf.sprintf 
747       ("%d new files\n"^^
748        "%d deleted files\n"^^
749        "%d updated files\n"^^
750        "%d merged files\n"^^
751        "%d conflicting files\n\n" ^^
752        "Anomalies:\n%s") added del upd merged conflict anomalies
753     in
754     prerr_endline ("update details:\n" ^ details);
755     let details = 
756       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () details
757     in
758     MatitaAuthentication.set_file_flag uid files;
759     cgi # set_header 
760       ~cache:`No_cache 
761       ~content_type:"text/xml; charset=\"utf-8\""
762       ();
763     cgi#out_channel#output_string "<update>";
764     cgi#out_channel#output_string "<response>ok</response>";
765     cgi#out_channel#output_string ("<details>" ^ details ^ "</details>");
766     cgi#out_channel#output_string "</update>";
767   with
768   | Not_found _ -> 
769     cgi # set_header
770       ~status:`Internal_server_error
771       ~cache:`No_cache 
772       ~content_type:"text/xml; charset=\"utf-8\""
773       ());
774   cgi#out_channel#commit_work()
775 ;;
776
777 (* returns the length of the executed text and an html representation of the
778  * current metasenv*)
779 (*let advance  =*)
780 let advance (cgi : Netcgi.cgi_activation) =
781   (* let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in *)
782   let env = cgi#environment in
783   (try 
784     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
785     let sid = HExtlib.unopt sid in
786     (*
787     cgi # set_header 
788       ~cache:`No_cache 
789       ~content_type:"text/xml; charset=\"utf-8\""
790       ();
791     *)
792     let text = cgi#argument_value "body" in
793     (* prerr_endline ("body =\n" ^ text); *)
794     let parsed_len, new_parsed, new_unparsed, new_status = advance0 sid text in
795     let txt = output_status new_status in
796     let body = 
797        "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\">" ^
798        new_parsed ^ "</parsed>" ^ txt 
799        ^ "</response>"
800     in 
801     (* prerr_endline ("sending advance response:\n" ^ body); *)
802     cgi # set_header 
803       ~cache:`No_cache 
804       ~content_type:"text/xml; charset=\"utf-8\""
805       ();
806     cgi#out_channel#output_string body
807    with
808   | Emphasized_error text ->
809 (* | MultiPassDisambiguator.DisambiguationError (offset,errorll) -> *)
810     let body = "<response><error>" ^ text ^ "</error></response>" in 
811     cgi # set_header 
812       ~cache:`No_cache 
813       ~content_type:"text/xml; charset=\"utf-8\""
814       ();
815     cgi#out_channel#output_string body
816   | Disamb_error text -> 
817     let body = "<response>" ^ text ^ "</response>" in 
818     cgi # set_header 
819       ~cache:`No_cache 
820       ~content_type:"text/xml; charset=\"utf-8\""
821       ();
822     cgi#out_channel#output_string body
823   | Not_found _ -> 
824     cgi # set_header
825       ~status:`Internal_server_error
826       ~cache:`No_cache 
827       ~content_type:"text/xml; charset=\"utf-8\""
828       ()
829   );
830   cgi#out_channel#commit_work()
831 ;;
832
833 let gotoBottom (cgi : Netcgi.cgi_activation) =
834   let env = cgi#environment in
835 (*  (try  *)
836     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
837     let sid = HExtlib.unopt sid in
838
839     let error_msg = function
840       | Emphasized_error text -> "<localized>" ^ text ^ "</localized>" 
841       | Disamb_error text -> text
842       | End_of_file _ -> (* not an error *) ""
843       | e -> (* unmanaged error *)
844           "<error>" ^ 
845           (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () 
846             (Printexc.to_string e)) ^ "</error>"
847     in
848
849     let rec aux acc text =
850       try
851         prerr_endline ("evaluating: " ^ first_line text);
852         let plen,new_parsed,new_unparsed,_new_status = advance0 sid text in
853         aux ((plen,new_parsed)::acc) new_unparsed
854       with e -> acc, error_msg e 
855         (* DON'T SERIALIZE NOW!!!
856           let status = MatitaAuthentication.get_status sid in
857           GrafiteTypes.Serializer.serialize 
858             ~baseuri:(NUri.uri_of_string status#baseuri) status;
859           acc, error_msg e *)
860     in
861     (* 
862     cgi # set_header 
863       ~cache:`No_cache 
864       ~content_type:"text/xml; charset=\"utf-8\""
865       ();
866     *)
867     let text = cgi#argument_value "body" in
868     (* prerr_endline ("body =\n" ^ text); *)
869     let len_parsedlist, err_msg = aux [] text in
870     let status = MatitaAuthentication.get_status sid in
871     let txt = output_status status in
872     let parsed_tag (len,txt) = 
873        "<parsed length=\"" ^ (string_of_int len) ^ "\">" ^ txt ^ "</parsed>"
874     in
875     (* List.rev: the list begins with the older parsed txt *)
876     let body = 
877        "<response>" ^
878        String.concat "" (List.rev (List.map parsed_tag len_parsedlist)) ^
879        txt ^ err_msg ^ "</response>"
880     in
881     (* prerr_endline ("sending goto bottom response:\n" ^ body); *)
882     cgi # set_header 
883       ~cache:`No_cache 
884       ~content_type:"text/xml; charset=\"utf-8\""
885       ();
886     cgi#out_channel#output_string body;
887 (*   with Not_found -> cgi#set_header ~status:`Internal_server_error 
888       ~cache:`No_cache 
889       ~content_type:"text/xml; charset=\"utf-8\"" ()); *)
890   cgi#out_channel#commit_work() 
891 ;;
892
893 let gotoTop (cgi : Netcgi.cgi_activation) =
894   let env = cgi#environment in
895   prerr_endline "executing goto Top";
896   (try 
897     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
898     let sid = HExtlib.unopt sid in
899     (*
900     cgi # set_header 
901       ~cache:`No_cache 
902       ~content_type:"text/xml; charset=\"utf-8\""
903       ();
904     *)
905     let status = MatitaAuthentication.get_status sid in
906     let uid = MatitaAuthentication.user_of_session sid in
907     let baseuri = status#baseuri in
908     let new_status = new MatitaEngine.status (Some uid) baseuri in
909     prerr_endline "gototop prima della time travel";
910     (* NCicLibrary.time_travel new_status; *)
911     prerr_endline "gototop dopo della time travel";
912     let new_history = [new_status] in 
913     MatitaAuthentication.set_history sid new_history;
914     MatitaAuthentication.set_status sid new_status;
915     (* NCicLibrary.time_travel new_status; *)
916     cgi # set_header 
917       ~cache:`No_cache 
918       ~content_type:"text/xml; charset=\"utf-8\""
919       ();
920     cgi#out_channel#output_string "<response>ok</response>"
921    with _ -> 
922      (cgi#set_header ~status:`Internal_server_error 
923       ~cache:`No_cache 
924       ~content_type:"text/xml; charset=\"utf-8\"" ();
925       cgi#out_channel#output_string "<response>ok</response>"));
926   cgi#out_channel#commit_work() 
927 ;;
928
929 let retract (cgi : Netcgi.cgi_activation) =
930   let env = cgi#environment in
931   (try  
932     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
933     let sid = HExtlib.unopt sid in
934     (*
935     cgi # set_header 
936       ~cache:`No_cache 
937       ~content_type:"text/xml; charset=\"utf-8\""
938       ();
939     *)
940     let history = MatitaAuthentication.get_history sid in
941     let old_status = MatitaAuthentication.get_status sid in
942     let new_history,new_status =
943        match history with
944          _::(status::_ as history) ->
945           history, status
946       | [_] -> (prerr_endline "singleton";failwith "retract")
947       | _ -> (prerr_endline "nil"; assert false) in
948 (*    prerr_endline "timestamp prima della retract";
949     old_status#print_timestamp ();
950     prerr_endline "timestamp della retract";
951     new_status#print_timestamp ();
952     prerr_endline ("prima della time travel"); *)
953     NCicLibrary.time_travel new_status;
954     prerr_endline ("dopo della time travel");
955     MatitaAuthentication.set_history sid new_history;
956     MatitaAuthentication.set_status sid new_status;
957     prerr_endline ("baseuri after retract = " ^ new_status#baseuri);
958     let body = output_status new_status in
959     cgi # set_header 
960       ~cache:`No_cache 
961       ~content_type:"text/xml; charset=\"utf-8\""
962       ();
963     cgi#out_channel#output_string body
964    with e -> 
965     prerr_endline ("error in retract: " ^ Printexc.to_string e);
966     cgi#set_header ~status:`Internal_server_error 
967       ~cache:`No_cache 
968       ~content_type:"text/xml; charset=\"utf-8\"" ());
969   cgi#out_channel#commit_work() 
970 ;;
971
972
973 let viewLib (cgi : Netcgi.cgi_activation) =
974   let env = cgi#environment in
975   
976     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
977     let sid = HExtlib.unopt sid in
978     (*
979     cgi # set_header 
980       ~cache:`No_cache 
981       ~content_type:"text/html; charset=\"utf-8\""
982       ();
983     *)
984     let uid = MatitaAuthentication.user_of_session sid in
985     
986     let ft = MatitaAuthentication.read_ft uid in
987     let html = MatitaFilesystem.html_of_library uid ft in
988     cgi # set_header 
989       ~cache:`No_cache 
990       ~content_type:"text/html; charset=\"utf-8\""
991       ();
992     cgi#out_channel#output_string
993       ((*
994        "<html><head>\n" ^
995        "<title>XML Tree Control</title>\n" ^
996        "<link href=\"treeview/xmlTree.css\" type=\"text/css\" rel=\"stylesheet\">\n" ^
997        "<script src=\"treeview/xmlTree.js\" type=\"text/javascript\"></script>\n" ^
998        "<body>\n" ^ *)
999        html (* ^ "\n</body></html>" *) );
1000     
1001     let files,anomalies = MatitaFilesystem.stat_user uid in
1002     let changed = HExtlib.filter_map 
1003       (fun (n,f) -> if (f = Some MatitaFilesystem.MModified) then Some n else None) files
1004     in
1005     let changed = String.concat "\n" changed in
1006     let anomalies = String.concat "\n" anomalies in
1007     prerr_endline ("Changed:\n" ^ changed ^ "\n\nAnomalies:\n" ^ anomalies);
1008   cgi#out_channel#commit_work()
1009   
1010 ;;
1011
1012 let resetLib (cgi : Netcgi.cgi_activation) =
1013   MatitaAuthentication.reset ();
1014     cgi # set_header 
1015       ~cache:`No_cache 
1016       ~content_type:"text/html; charset=\"utf-8\""
1017       ();
1018     
1019     cgi#out_channel#output_string
1020       ("<html><head>\n" ^
1021        "<title>Matitaweb Reset</title>\n" ^
1022        "<body><H1>Reset completed</H1></body></html>");
1023     cgi#out_channel#commit_work()
1024
1025 open Netcgi1_compat.Netcgi_types;;
1026
1027 (**********************************************************************)
1028 (* Create the webserver                                               *)
1029 (**********************************************************************)
1030
1031
1032 let start() =
1033   let (opt_list, cmdline_cfg) = Netplex_main.args() in
1034
1035   let use_mt = ref true in
1036
1037   let opt_list' =
1038     [ "-mt", Arg.Set use_mt,
1039       "  Use multi-threading instead of multi-processing"
1040     ] @ opt_list in
1041
1042   Arg.parse 
1043     opt_list'
1044     (fun s -> raise (Arg.Bad ("Don't know what to do with: " ^ s)))
1045     "usage: netplex [options]";
1046   let parallelizer = 
1047     if !use_mt then
1048       Netplex_mt.mt()     (* multi-threading *)
1049     else
1050       Netplex_mp.mp() in  (* multi-processing *)
1051 (*
1052   let adder =
1053     { Nethttpd_services.dyn_handler = (fun _ -> process1);
1054       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1055       dyn_uri = None;                 (* not needed *)
1056       dyn_translator = (fun _ -> ""); (* not needed *)
1057       dyn_accept_all_conditionals = false;
1058     } in
1059 *)
1060   let do_advance =
1061     { Nethttpd_services.dyn_handler = (fun _ -> advance);
1062       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1063       dyn_uri = None;                 (* not needed *)
1064       dyn_translator = (fun _ -> ""); (* not needed *)
1065       dyn_accept_all_conditionals = false;
1066     } in
1067   let do_retract =
1068     { Nethttpd_services.dyn_handler = (fun _ -> retract);
1069       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1070       dyn_uri = None;                 (* not needed *)
1071       dyn_translator = (fun _ -> ""); (* not needed *)
1072       dyn_accept_all_conditionals = false;
1073     } in
1074   let goto_bottom =
1075     { Nethttpd_services.dyn_handler = (fun _ -> gotoBottom);
1076       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1077       dyn_uri = None;                 (* not needed *)
1078       dyn_translator = (fun _ -> ""); (* not needed *)
1079       dyn_accept_all_conditionals = false;
1080     } in
1081   let goto_top =
1082     { Nethttpd_services.dyn_handler = (fun _ -> gotoTop);
1083       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1084       dyn_uri = None;                 (* not needed *)
1085       dyn_translator = (fun _ -> ""); (* not needed *)
1086       dyn_accept_all_conditionals = false;
1087     } in
1088   let retrieve =
1089     { Nethttpd_services.dyn_handler = (fun _ -> retrieve);
1090       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1091       dyn_uri = None;                 (* not needed *)
1092       dyn_translator = (fun _ -> ""); (* not needed *)
1093       dyn_accept_all_conditionals = false;
1094     } in
1095   let do_register =
1096     { Nethttpd_services.dyn_handler = (fun _ -> register);
1097       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1098       dyn_uri = None;                 (* not needed *)
1099       dyn_translator = (fun _ -> ""); (* not needed *)
1100       dyn_accept_all_conditionals = false;
1101     } in
1102   let do_login =
1103     { Nethttpd_services.dyn_handler = (fun _ -> login);
1104       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1105       dyn_uri = None;                 (* not needed *)
1106       dyn_translator = (fun _ -> ""); (* not needed *)
1107       dyn_accept_all_conditionals = false;
1108     } in
1109   let do_logout =
1110     { Nethttpd_services.dyn_handler = (fun _ -> logout);
1111       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1112       dyn_uri = None;                 (* not needed *)
1113       dyn_translator = (fun _ -> ""); (* not needed *)
1114       dyn_accept_all_conditionals = false;
1115     } in 
1116   let do_viewlib =
1117     { Nethttpd_services.dyn_handler = (fun _ -> viewLib);
1118       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1119       dyn_uri = None;                 (* not needed *)
1120       dyn_translator = (fun _ -> ""); (* not needed *)
1121       dyn_accept_all_conditionals = false;
1122     } in 
1123   let do_resetlib =
1124     { Nethttpd_services.dyn_handler = (fun _ -> resetLib);
1125       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1126       dyn_uri = None;                 (* not needed *)
1127       dyn_translator = (fun _ -> ""); (* not needed *)
1128       dyn_accept_all_conditionals = false;
1129     } in 
1130   let do_save =
1131     { Nethttpd_services.dyn_handler = (fun _ -> save);
1132       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1133       dyn_uri = None;                 (* not needed *)
1134       dyn_translator = (fun _ -> ""); (* not needed *)
1135       dyn_accept_all_conditionals = false;
1136     } in 
1137   let do_commit =
1138     { Nethttpd_services.dyn_handler = (fun _ -> initiate_commit);
1139       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1140       dyn_uri = None;                 (* not needed *)
1141       dyn_translator = (fun _ -> ""); (* not needed *)
1142       dyn_accept_all_conditionals = false;
1143     } in 
1144   let do_update =
1145     { Nethttpd_services.dyn_handler = (fun _ -> svn_update);
1146       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1147       dyn_uri = None;                 (* not needed *)
1148       dyn_translator = (fun _ -> ""); (* not needed *)
1149       dyn_accept_all_conditionals = false;
1150     } in 
1151   
1152   
1153   let nethttpd_factory = 
1154     Nethttpd_plex.nethttpd_factory
1155       ~handlers:[ "advance", do_advance
1156                 ; "retract", do_retract
1157                 ; "bottom", goto_bottom
1158                 ; "top", goto_top
1159                 ; "open", retrieve 
1160                 ; "register", do_register
1161                 ; "login", do_login 
1162                 ; "logout", do_logout 
1163                 ; "reset", do_resetlib
1164                 ; "viewlib", do_viewlib
1165                 ; "save", do_save
1166                 ; "commit", do_commit
1167                 ; "update", do_update]
1168       () in
1169   MatitaInit.initialize_all ();
1170   MatitaAuthentication.deserialize ();
1171   Netplex_main.startup
1172     parallelizer
1173     Netplex_log.logger_factories   (* allow all built-in logging styles *)
1174     Netplex_workload.workload_manager_factories (* ... all ways of workload management *)
1175     [ nethttpd_factory ]           (* make this nethttpd available *)
1176     cmdline_cfg
1177 ;;
1178
1179 Sys.set_signal Sys.sigpipe Sys.Signal_ignore;
1180 start();;