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