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