]> matita.cs.unibo.it Git - helm.git/blob - matitaB/matita/matitadaemon.ml
261811815d3c1705d41de529c789ac19cb9ad4a9
[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.NCommand (_,
218         GrafiteAst.NObj (loc, astobj,_))) ->
219           let objname = NotationPt.name_of_obj astobj in
220           let status = 
221             MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
222           in
223           let new_parsed_text = Ulexing.from_utf8_string parsed_text in
224           let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
225           let outstr = ref "" in
226           ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
227           let x, y = HExtlib.loc_of_floc floc in
228           let pre = Netconversion.ustring_sub `Enc_utf8  0 x !outstr in
229           let post = Netconversion.ustring_sub `Enc_utf8 x
230            (Netconversion.ustring_length `Enc_utf8 !outstr - x) !outstr in
231           outstr := Printf.sprintf 
232             "%s\005input type=\"radio\" class=\"anchor\" id=\"%s\" /\006%s" pre objname post;
233           prerr_endline ("baseuri after advance = " ^ status#baseuri);
234           (* prerr_endline ("parser output: " ^ !outstr); *)
235           (status,!outstr, unparsed_txt'),parsed_text_len
236   | GrafiteAst.Executable (_,
237       GrafiteAst.NTactic (_,
238         [GrafiteAst.NAuto (_, (l,a as auto_params))])) when is_auto auto_params
239           ->
240           let l = match l with
241           | None -> None
242           | Some (_,l') -> Some (List.map (fun x -> "",0,x) l')
243           in
244           let trace_ref = ref [] in
245           let status = NnAuto.auto_tac ~params:(l,a) ~trace_ref status in
246           let new_parsed_text = pre ^ (Printf.sprintf 
247             "/\005span class='autotactic'\006%s\005span class='autotrace'\006 trace %s\005/span\006\005/span\006/"
248              (String.concat " " 
249                (List.assoc "depth" a::
250                 HExtlib.filter_map (get_param a) ["width";"size"]))
251              (mk_univ !trace_ref))
252           in
253           (status,new_parsed_text, unparsed_txt'),parsed_text_len
254   | _ ->
255       let status = 
256         MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
257       in
258       let new_parsed_text = Ulexing.from_utf8_string parsed_text in
259       let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
260       let outstr = ref "" in
261       ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
262       prerr_endline ("baseuri after advance = " ^ status#baseuri);
263       (* prerr_endline ("parser output: " ^ !outstr); *)
264       (status,!outstr, unparsed_txt'),parsed_text_len
265
266 (*let save_moo status = 
267   let script = MatitaScript.current () in
268   let baseuri = status#baseuri in
269   match script#bos, script#eos with
270   | true, _ -> ()
271   | _, true ->
272      GrafiteTypes.Serializer.serialize ~baseuri:(NUri.uri_of_string baseuri)
273       status
274   | _ -> clean_current_baseuri status 
275 ;;*)
276     
277 let sequent_size = ref 40;;
278
279 let include_paths = ref [];;
280
281 (* <metasenv>
282  *   <meta number="...">
283  *     <metaname>...</metaname>
284  *     <goal>...</goal>
285  *   </meta>
286  *
287  *   ...
288  * </metasenv> *)
289 let output_status s =
290   let _,_,metasenv,subst,_ = s#obj in
291   let render_switch = function 
292   | Stack.Open i -> "?" ^ (string_of_int i) 
293   | Stack.Closed i -> "<S>?" ^ (string_of_int i) ^ "</S>"
294   in
295   let int_of_switch = function
296   | Stack.Open i | Stack.Closed i -> i
297   in
298   let sequent = function
299   | Stack.Open i ->
300       let meta = List.assoc i metasenv in
301       snd (ApplyTransformation.ntxt_of_cic_sequent 
302         ~metasenv ~subst ~map_unicode_to_tex:false !sequent_size s (i,meta))
303   | Stack.Closed _ -> "This goal has already been closed."
304   in
305   let render_sequent is_loc acc depth tag (pos,sw) =
306     let metano = int_of_switch sw in
307     let markup = 
308       if is_loc then
309         (match depth, pos with
310          | 0, 0 -> "<span class=\"activegoal\">" ^ (render_switch sw) ^ "</span>"
311          | 0, _ -> 
312             Printf.sprintf "<span class=\"activegoal\">|<SUB>%d</SUB>: %s</span>" pos (render_switch sw)
313          | 1, pos when Stack.head_tag s#stack = `BranchTag ->
314              Printf.sprintf "<span class=\"passivegoal\">|<SUB>%d</SUB> : %s</span>" pos (render_switch sw)
315          | _ -> render_switch sw)
316       else render_switch sw
317     in
318     let markup = 
319       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () markup in
320     let markup = "<metaname>" ^ markup ^ "</metaname>" in
321     let sequent =
322       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () (sequent sw)
323     in      
324     let txt0 = "<goal>" ^ sequent ^ "</goal>" in
325     "<meta number=\"" ^ (string_of_int metano) ^ "\">" ^ markup ^
326     txt0 ^ "</meta>" ^ acc
327   in
328   "<metasenv>" ^
329     (Stack.fold 
330       ~env:(render_sequent true) ~cont:(render_sequent false) 
331       ~todo:(render_sequent false) "" s#stack) ^
332     "</metasenv>"
333   (* prerr_endline ("sending metasenv:\n" ^ res); res *)
334 ;;
335
336 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*";;
337
338 let first_line s =
339   let s = Pcre.replace ~rex:heading_nl_RE s in
340   try
341     let nl_pos = String.index s '\n' in
342     String.sub s 0 nl_pos
343   with Not_found -> s
344 ;;
345
346 let read_file fname =
347   let chan = open_in fname in
348   let lines = ref [] in
349   (try
350      while true do
351        lines := input_line chan :: !lines
352      done;
353    with End_of_file -> close_in chan);
354   String.concat "\n" (List.rev !lines)
355 ;;
356
357 let load_index outchan =
358   let s = read_file "index.html" in
359   Http_daemon.respond ~headers:["Content-Type", "text/html"] ~code:(`Code 200) ~body:s outchan
360 ;;
361
362 let load_doc filename outchan =
363   let s = read_file filename in
364   let is_png = 
365     try String.sub filename (String.length filename - 4) 4 = ".png"
366     with Invalid_argument _ -> false
367   in
368   let contenttype = if is_png then "image/png" else "text/html" in
369   Http_daemon.respond ~headers:["Content-Type", contenttype] ~code:(`Code 200) ~body:s outchan
370 ;;
371
372 let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
373   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
374   let env = cgi#environment in
375   (try 
376     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
377     let sid = HExtlib.unopt sid in
378     let uid = MatitaAuthentication.user_of_session sid in
379     (*
380     cgi # set_header 
381       ~cache:`No_cache 
382       ~content_type:"text/xml; charset=\"utf-8\""
383       ();
384     *)
385     let readonly = cgi # argument_value "readonly" in
386     let filename = libdir uid ^ "/" ^ (cgi # argument_value "file") in
387     (* prerr_endline ("reading file " ^ filename); *)
388     let body = 
389      Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false ()
390         (html_of_matita (read_file filename)) in
391      
392      (*   html_of_matita (read_file filename) in *)
393     (* prerr_endline ("sending:\nBEGIN\n" ^ body ^ "\nEND"); *)
394     let body = "<response><file>" ^ body ^ "</file></response>" in
395     let baseuri, incpaths = 
396       try 
397         let root, baseuri, _fname, _tgt = 
398           Librarian.baseuri_of_script ~include_paths:[] filename in 
399         let includes =
400          try
401           Str.split (Str.regexp " ") 
402            (List.assoc "include_paths" (Librarian.load_root_file (root^"/root")))
403          with Not_found -> []
404         in
405         let rc = root :: includes in
406          List.iter (HLog.debug) rc; baseuri, rc
407        with 
408          Librarian.NoRootFor _ | Librarian.FileNotFound _ -> "",[] in
409     include_paths := incpaths;
410     if readonly <> "true" then
411        (let status = new MatitaEngine.status (Some uid) baseuri in
412         let history = [status] in
413         MatitaAuthentication.set_status sid status;
414         MatitaAuthentication.set_history sid history);
415     cgi # set_header 
416       ~cache:`No_cache 
417       ~content_type:"text/xml; charset=\"utf-8\""
418       ();
419     cgi#out_channel#output_string body;
420   with
421   | Sys_error _ -> 
422     cgi # set_header 
423       ~cache:`No_cache 
424       ~content_type:"text/xml; charset=\"utf-8\""
425       ();
426     cgi#out_channel#output_string "<error />"
427   | Not_found _ -> 
428     cgi # set_header
429       ~status:`Internal_server_error
430       ~cache:`No_cache 
431       ~content_type:"text/html; charset=\"utf-8\""
432       ());
433   cgi#out_channel#commit_work()
434 ;;
435
436 let xml_of_disamb_error l =
437   let mk_alias = function
438   | GrafiteAst.Ident_alias (_,uri) -> "href=\"" ^ uri ^ "\""
439   | GrafiteAst.Symbol_alias (_,uri,desc) 
440   | GrafiteAst.Number_alias (uri,desc) -> 
441       let uri = try HExtlib.unopt uri with _ -> "cic:/fakeuri.def(1)" in
442         "href=\"" ^ uri ^ "\" title=\"" ^ 
443         (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
444         ^ "\""
445   in
446
447   let mk_interpr (loc,a) =
448     let x,y = HExtlib.loc_of_floc loc in
449     Printf.sprintf "<interpretation start=\"%d\" stop=\"%d\" %s />"
450       x y (mk_alias a)
451   in
452
453   let mk_failure (il,loc,msg) =
454     let x,y = HExtlib.loc_of_floc loc in
455     Printf.sprintf "<failure start=\"%d\" stop=\"%d\" title=\"%s\">%s</failure>"
456       x y (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () msg)
457       (String.concat "" (List.map mk_interpr il))
458   in
459
460   let mk_choice (a,fl) = 
461     let fl' = String.concat "" (List.map mk_failure fl) in
462     match a with
463     | None -> "<choice>" ^ fl' ^ "</choice>"
464     | Some a -> Printf.sprintf "<choice %s>%s</choice>" (mk_alias a) fl'
465   in
466
467   let mk_located (loc,cl) =
468     let x,y = HExtlib.loc_of_floc loc in
469     Printf.sprintf "<choicepoint start=\"%d\" stop=\"%d\">%s</choicepoint>"
470       x y (String.concat "" (List.map mk_choice cl))
471   in
472   "<disamberror>" ^ (String.concat "" (List.map mk_located l)) ^ "</disamberror>"
473 ;;
474
475 let advance0 sid text =
476   let status = MatitaAuthentication.get_status sid in
477   let history = MatitaAuthentication.get_history sid in
478   let status = status#reset_disambiguate_db () in
479   let (st,new_statements,new_unparsed),parsed_len =
480     let rec do_exc = function
481     | HExtlib.Localized (floc,e) -> 
482       let x, y = HExtlib.loc_of_floc floc in
483       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
484       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
485       let post = Netconversion.ustring_sub `Enc_utf8 y 
486          (Netconversion.ustring_length `Enc_utf8 text - y) text in
487       let _,title = MatitaExcPp.to_string e in
488       (* let title = "" in *)
489       let marked = 
490         pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
491       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
492       () (html_of_matita marked) in
493       raise (Emphasized_error marked)
494     | Disambiguate.NoWellTypedInterpretation (floc,e) ->
495       let x, y = HExtlib.loc_of_floc floc in
496       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
497       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
498       let post = Netconversion.ustring_sub `Enc_utf8 y 
499          (Netconversion.ustring_length `Enc_utf8 text - y) text in
500       (*let _,title = MatitaExcPp.to_string e in*)
501       (* let title = "" in *)
502       let marked = 
503         pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
504       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
505       () (html_of_matita marked) in
506       raise (Emphasized_error marked)
507     | NCicRefiner.Uncertain m as exn ->
508       let floc, e = Lazy.force m in
509       let x, y = HExtlib.loc_of_floc floc in
510       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
511       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
512       let post = Netconversion.ustring_sub `Enc_utf8 y 
513          (Netconversion.ustring_length `Enc_utf8 text - y) text in
514       (* let _,title = MatitaExcPp.to_string e in *)
515       (* let title = "" in *)
516       let marked = 
517         pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
518       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
519       () (html_of_matita marked) in
520       raise (Emphasized_error marked)
521     | NTacStatus.Error (s,None) as e ->
522         prerr_endline 
523           ("NTacStatus.Error " ^ (Lazy.force s)); raise e
524     | NTacStatus.Error (s,Some exc) as e ->
525         prerr_endline 
526           ("NTacStatus.Error " ^ Lazy.force s ^ " -- " ^ (Printexc.to_string exc));
527         do_exc exc
528     | GrafiteDisambiguate.Ambiguous_input (loc,choices) ->
529       let x,y = HExtlib.loc_of_floc loc in
530       let choice_of_alias = function
531        | GrafiteAst.Ident_alias (_,uri) -> uri, None, uri
532        | GrafiteAst.Number_alias (None,desc)
533        | GrafiteAst.Symbol_alias (_,None,desc) -> "cic:/fakeuri.def(1)", Some desc, desc
534        | GrafiteAst.Number_alias (Some uri,desc)
535        | GrafiteAst.Symbol_alias (_,Some uri,desc) -> uri, Some desc, desc
536       in
537       let tag_of_choice (uri,title,desc) =
538         match title with
539         | None -> Printf.sprintf "<choice href=\"%s\">%s</choice>"
540             uri 
541             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
542         | Some t -> Printf.sprintf "<choice href=\"%s\" title=\"%s\">%s</choice>"
543             uri 
544             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () t)
545             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
546       in
547       let strchoices = 
548         String.concat "\n" 
549           (List.map (fun x -> tag_of_choice (choice_of_alias x)) choices)
550       in
551       prerr_endline (Printf.sprintf
552         "@@@ Ambiguous input at (%d,%d). Possible choices:\n\n%s\n\n@@@ End."
553           x y strchoices);
554       (*
555       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
556       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
557       let post = Netconversion.ustring_sub `Enc_utf8 y 
558          (Netconversion.ustring_length `Enc_utf8 text - y) text in
559       let title = "Disambiguation Error" in
560       (* let title = "" in *)
561       let marked = 
562         pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
563       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
564       () (html_of_matita marked) in
565       *)
566       let strchoices = Printf.sprintf
567         "<ambiguity start=\"%d\" stop=\"%d\">%s</ambiguity>" x y strchoices
568       in raise (Disamb_error strchoices)
569    | GrafiteDisambiguate.Error l -> raise (Disamb_error (xml_of_disamb_error l))
570    (* | End_of_file -> ...          *)
571    | e -> 
572       prerr_endline ("matitadaemon *** Unhandled exception " ^ Printexc.to_string e);
573       raise e
574    in
575
576     try
577       eval_statement !include_paths (*buffer*) status (`Raw text)
578     with e -> do_exc e
579   in
580         debug "BEGIN PRINTGRAMMAR";
581         (*prerr_endline (Print_grammar.ebnf_of_term status);*)
582         (*let kwds = String.concat ", " status#get_kwds in
583         debug ("keywords = " ^ kwds );*)
584         debug "END PRINTGRAMMAR";
585   MatitaAuthentication.set_status sid st;
586   MatitaAuthentication.set_history sid (st::history);
587 (*  prerr_endline "previous timestamp";
588   status#print_timestamp();
589   prerr_endline "current timestamp";
590   st#print_timestamp(); *)
591   parsed_len, 
592     Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
593       () (html_of_matita new_statements), new_unparsed, st
594
595 let register  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
596   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
597   let _env = cgi#environment in
598   
599   assert (cgi#arguments <> []);
600   let uid = cgi#argument_value "userid" in
601   let userpw = cgi#argument_value "password" in
602   (try
603     (* currently registering only unprivileged users *) 
604     MatitaAuthentication.add_user uid userpw false;
605 (*    env#set_output_header_field "Location" "/index.html" *)
606     cgi#out_channel#output_string
607      ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/login.html\">"
608      ^ "</head><body>Redirecting to login page...</body></html>")
609    with
610    | MatitaAuthentication.UsernameCollision _ ->
611       cgi#set_header
612        ~cache:`No_cache 
613        ~content_type:"text/html; charset=\"utf-8\""
614        ();
615      cgi#out_channel#output_string
616       "<html><head></head><body>Error: User id collision!</body></html>"
617    | MatitaFilesystem.SvnError msg ->
618       cgi#set_header
619        ~cache:`No_cache 
620        ~content_type:"text/html; charset=\"utf-8\""
621        ();
622      cgi#out_channel#output_string
623       ("<html><head></head><body><p>Error: Svn checkout failed!<p><p><textarea>"
624        ^ msg ^ "</textarea></p></body></html>"));
625   cgi#out_channel#commit_work()
626 ;;
627
628 let login  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
629   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
630   let env = cgi#environment in
631   
632   assert (cgi#arguments <> []);
633   let uid = cgi#argument_value "userid" in
634   let userpw = cgi#argument_value "password" in
635   (try 
636       MatitaAuthentication.check_pw uid userpw;
637       NCicLibrary.init (Some uid);
638       let ft = MatitaAuthentication.read_ft uid in
639       let _ = MatitaFilesystem.html_of_library uid ft in
640        let sid = MatitaAuthentication.create_session uid in
641        (* let cookie = Netcgi.Cookie.make "session" (Uuidm.to_string sid) in
642           cgi#set_header ~set_cookies:[cookie] (); *)
643        env#set_output_header_field 
644          "Set-Cookie" ("session=" ^ (Uuidm.to_string sid));
645    (*    env#set_output_header_field "Location" "/index.html" *)
646        cgi#out_channel#output_string
647         ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/index.html\">"
648         ^ "</head><body>Redirecting to Matita page...</body></html>")
649   with MatitaAuthentication.InvalidPassword ->
650     cgi#set_header
651       ~cache:`No_cache 
652       ~content_type:"text/html; charset=\"utf-8\""
653       ();
654     cgi#out_channel#output_string
655       "<html><head></head><body>Authentication error</body></html>");
656   cgi#out_channel#commit_work()
657 ;;
658
659 let logout  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
660   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
661   let env = cgi#environment in
662   (try 
663     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
664     let sid = HExtlib.unopt sid in
665     MatitaAuthentication.logout_user sid;
666     cgi # set_header 
667       ~cache:`No_cache 
668       ~content_type:"text/html; charset=\"utf-8\""
669       ();
670     let text = read_file (rt_path () ^ "/logout.html") in
671     cgi#out_channel#output_string text
672   with
673   | Not_found _ -> 
674     cgi # set_header
675       ~status:`Internal_server_error
676       ~cache:`No_cache 
677       ~content_type:"text/html; charset=\"utf-8\""
678       ());
679   cgi#out_channel#commit_work()
680 ;;
681
682 exception File_already_exists;;
683
684 let save  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
685   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
686   let env = cgi#environment in
687   (try 
688     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
689     let sid = HExtlib.unopt sid in
690     let status = MatitaAuthentication.get_status sid in
691     let uid = MatitaAuthentication.user_of_session sid in
692     assert (cgi#arguments <> []);
693     let locked = cgi#argument_value "locked" in
694     let unlocked = cgi#argument_value "unlocked" in
695     let dir = cgi#argument_value "dir" in
696     let rel_filename = cgi # argument_value "file" in
697     let filename = libdir uid ^ "/" ^ rel_filename in
698     let force = bool_of_string (cgi#argument_value "force") in
699     let already_exists = Sys.file_exists filename in
700
701     if ((not force) && already_exists) then 
702       raise File_already_exists;
703
704     if dir = "true" then
705        Unix.mkdir filename 0o744
706     else 
707      begin
708       let oc = open_out filename in
709       output_string oc (locked ^ unlocked);
710       close_out oc;
711       if MatitaEngine.eos status unlocked then
712        begin
713         (* prerr_endline ("serializing proof objects..."); *)
714         GrafiteTypes.Serializer.serialize 
715           ~baseuri:(NUri.uri_of_string status#baseuri) status;
716         (* prerr_endline ("done."); *)
717        end;
718      end;
719     let old_flag =
720       try 
721         List.assoc rel_filename (MatitaAuthentication.read_ft uid)
722       with Not_found -> MatitaFilesystem.MUnversioned
723     in
724     (if old_flag <> MatitaFilesystem.MConflict &&
725        old_flag <> MatitaFilesystem.MAdd then
726       let newflag = 
727         if already_exists then MatitaFilesystem.MModified
728         else MatitaFilesystem.MAdd
729       in
730       MatitaAuthentication.set_file_flag uid [rel_filename, Some newflag]);
731     cgi # set_header 
732      ~cache:`No_cache 
733      ~content_type:"text/xml; charset=\"utf-8\""
734      ();
735     cgi#out_channel#output_string "<response>ok</response>"
736   with
737   | File_already_exists ->
738       cgi#out_channel#output_string "<response>cancelled</response>"
739   | Sys_error _ -> 
740     cgi # set_header
741       ~status:`Internal_server_error
742       ~cache:`No_cache 
743       ~content_type:"text/xml; charset=\"utf-8\""
744       ()
745   | e ->
746       let estr = Printexc.to_string e in
747       cgi#out_channel#output_string ("<response>" ^ estr ^ "</response>"));
748   cgi#out_channel#commit_work()
749 ;;
750
751 let initiate_commit (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
752   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
753   let env = cgi#environment in
754   (try
755     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
756     let sid = HExtlib.unopt sid in
757     MatitaAuthentication.probe_commit_priv sid;
758     let out = do_global_commit () in
759     cgi # set_header 
760       ~cache:`No_cache 
761       ~content_type:"text/xml; charset=\"utf-8\""
762       ();
763     cgi#out_channel#output_string "<commit>";
764     cgi#out_channel#output_string "<response>ok</response>";
765     cgi#out_channel#output_string ("<details>" ^ out ^ "</details>");
766     cgi#out_channel#output_string "</commit>"
767   with
768   | Not_found _ -> 
769     cgi # set_header
770       ~status:`Internal_server_error
771       ~cache:`No_cache 
772       ~content_type:"text/xml; charset=\"utf-8\""
773       ());
774   cgi#out_channel#commit_work()
775 ;;
776
777 let svn_update  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
778   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
779   let env = cgi#environment in
780   let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
781   let sid = HExtlib.unopt sid in
782   let uid = MatitaAuthentication.user_of_session sid in
783   (try
784     MatitaAuthentication.probe_commit_priv sid;
785     let files,anomalies,(added,conflict,del,upd,merged) = 
786       MatitaFilesystem.update_user uid 
787     in
788     let anomalies = String.concat "\n" anomalies in
789     let details = Printf.sprintf 
790       ("%d new files\n"^^
791        "%d deleted files\n"^^
792        "%d updated files\n"^^
793        "%d merged files\n"^^
794        "%d conflicting files\n\n" ^^
795        "Anomalies:\n%s") added del upd merged conflict anomalies
796     in
797     prerr_endline ("update details:\n" ^ details);
798     let details = 
799       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () details
800     in
801     MatitaAuthentication.set_file_flag uid files;
802     cgi # set_header 
803       ~cache:`No_cache 
804       ~content_type:"text/xml; charset=\"utf-8\""
805       ();
806     cgi#out_channel#output_string "<update>";
807     cgi#out_channel#output_string "<response>ok</response>";
808     cgi#out_channel#output_string ("<details>" ^ details ^ "</details>");
809     cgi#out_channel#output_string "</update>";
810   with
811   | Not_found _ -> 
812     cgi # set_header
813       ~status:`Internal_server_error
814       ~cache:`No_cache 
815       ~content_type:"text/xml; charset=\"utf-8\""
816       ());
817   cgi#out_channel#commit_work()
818 ;;
819
820 (* returns the length of the executed text and an html representation of the
821  * current metasenv*)
822 (*let advance  =*)
823 let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
824   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
825   let env = cgi#environment in
826   (try 
827     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
828     let sid = HExtlib.unopt sid in
829     (*
830     cgi # set_header 
831       ~cache:`No_cache 
832       ~content_type:"text/xml; charset=\"utf-8\""
833       ();
834     *)
835     let text = cgi#argument_value "body" in
836     (* prerr_endline ("body =\n" ^ text); *)
837     let parsed_len, new_parsed, new_unparsed, new_status = advance0 sid text in
838     let txt = output_status new_status in
839     let body = 
840        "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\">" ^
841        new_parsed ^ "</parsed>" ^ txt 
842        ^ "</response>"
843     in 
844     (* prerr_endline ("sending advance response:\n" ^ body); *)
845     cgi # set_header 
846       ~cache:`No_cache 
847       ~content_type:"text/xml; charset=\"utf-8\""
848       ();
849     cgi#out_channel#output_string body
850    with
851   | Emphasized_error text ->
852 (* | MultiPassDisambiguator.DisambiguationError (offset,errorll) -> *)
853     let body = "<response><error>" ^ text ^ "</error></response>" in 
854     cgi # set_header 
855       ~cache:`No_cache 
856       ~content_type:"text/xml; charset=\"utf-8\""
857       ();
858     cgi#out_channel#output_string body
859   | Disamb_error text -> 
860     let body = "<response>" ^ text ^ "</response>" in 
861     cgi # set_header 
862       ~cache:`No_cache 
863       ~content_type:"text/xml; charset=\"utf-8\""
864       ();
865     cgi#out_channel#output_string body
866   | Not_found _ -> 
867     cgi # set_header
868       ~status:`Internal_server_error
869       ~cache:`No_cache 
870       ~content_type:"text/xml; charset=\"utf-8\""
871       ()
872   );
873   cgi#out_channel#commit_work()
874 ;;
875
876 let gotoBottom  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
877   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
878   let env = cgi#environment in
879 (*  (try  *)
880     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
881     let sid = HExtlib.unopt sid in
882
883     let error_msg = function
884       | Emphasized_error text -> "<localized>" ^ text ^ "</localized>" 
885       | Disamb_error text -> text
886       | End_of_file _ -> (* not an error *) ""
887       | e -> (* unmanaged error *)
888           "<error>" ^ 
889           (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () 
890             (Printexc.to_string e)) ^ "</error>"
891     in
892
893     let rec aux acc text =
894       try
895         prerr_endline ("evaluating: " ^ first_line text);
896         let plen,new_parsed,new_unparsed,_new_status = advance0 sid text in
897         aux ((plen,new_parsed)::acc) new_unparsed
898       with e -> acc, error_msg e 
899         (* DON'T SERIALIZE NOW!!!
900           let status = MatitaAuthentication.get_status sid in
901           GrafiteTypes.Serializer.serialize 
902             ~baseuri:(NUri.uri_of_string status#baseuri) status;
903           acc, error_msg e *)
904     in
905     (* 
906     cgi # set_header 
907       ~cache:`No_cache 
908       ~content_type:"text/xml; charset=\"utf-8\""
909       ();
910     *)
911     let text = cgi#argument_value "body" in
912     (* prerr_endline ("body =\n" ^ text); *)
913     let len_parsedlist, err_msg = aux [] text in
914     let status = MatitaAuthentication.get_status sid in
915     let txt = output_status status in
916     let parsed_tag (len,txt) = 
917        "<parsed length=\"" ^ (string_of_int len) ^ "\">" ^ txt ^ "</parsed>"
918     in
919     (* List.rev: the list begins with the older parsed txt *)
920     let body = 
921        "<response>" ^
922        String.concat "" (List.rev (List.map parsed_tag len_parsedlist)) ^
923        txt ^ err_msg ^ "</response>"
924     in
925     (* prerr_endline ("sending goto bottom response:\n" ^ body); *)
926     cgi # set_header 
927       ~cache:`No_cache 
928       ~content_type:"text/xml; charset=\"utf-8\""
929       ();
930     cgi#out_channel#output_string body;
931 (*   with Not_found -> cgi#set_header ~status:`Internal_server_error 
932       ~cache:`No_cache 
933       ~content_type:"text/xml; charset=\"utf-8\"" ()); *)
934   cgi#out_channel#commit_work() 
935 ;;
936
937 let gotoTop  (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   prerr_endline "executing goto Top";
941   (try 
942     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
943     let sid = HExtlib.unopt sid in
944     (*
945     cgi # set_header 
946       ~cache:`No_cache 
947       ~content_type:"text/xml; charset=\"utf-8\""
948       ();
949     *)
950     let status = MatitaAuthentication.get_status sid in
951     let uid = MatitaAuthentication.user_of_session sid in
952     let baseuri = status#baseuri in
953     let new_status = new MatitaEngine.status (Some uid) baseuri in
954     prerr_endline "gototop prima della time travel";
955     (* NCicLibrary.time_travel new_status; *)
956     prerr_endline "gototop dopo della time travel";
957     let new_history = [new_status] in 
958     MatitaAuthentication.set_history sid new_history;
959     MatitaAuthentication.set_status sid new_status;
960     (* NCicLibrary.time_travel new_status; *)
961     cgi # set_header 
962       ~cache:`No_cache 
963       ~content_type:"text/xml; charset=\"utf-8\""
964       ();
965     cgi#out_channel#output_string "<response>ok</response>"
966    with _ -> 
967      (cgi#set_header ~status:`Internal_server_error 
968       ~cache:`No_cache 
969       ~content_type:"text/xml; charset=\"utf-8\"" ();
970       cgi#out_channel#output_string "<response>ok</response>"));
971   cgi#out_channel#commit_work() 
972 ;;
973
974 let retract  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
975   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
976   let env = cgi#environment in
977   (try  
978     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
979     let sid = HExtlib.unopt sid in
980     (*
981     cgi # set_header 
982       ~cache:`No_cache 
983       ~content_type:"text/xml; charset=\"utf-8\""
984       ();
985     *)
986     let history = MatitaAuthentication.get_history sid in
987     let old_status = MatitaAuthentication.get_status sid in
988     let new_history,new_status =
989        match history with
990          _::(status::_ as history) ->
991           history, status
992       | [_] -> (prerr_endline "singleton";failwith "retract")
993       | _ -> (prerr_endline "nil"; assert false) in
994 (*    prerr_endline "timestamp prima della retract";
995     old_status#print_timestamp ();
996     prerr_endline "timestamp della retract";
997     new_status#print_timestamp ();
998     prerr_endline ("prima della time travel"); *)
999     NCicLibrary.time_travel new_status;
1000     prerr_endline ("dopo della time travel");
1001     MatitaAuthentication.set_history sid new_history;
1002     MatitaAuthentication.set_status sid new_status;
1003     prerr_endline ("baseuri after retract = " ^ new_status#baseuri);
1004     let body = output_status new_status in
1005     cgi # set_header 
1006       ~cache:`No_cache 
1007       ~content_type:"text/xml; charset=\"utf-8\""
1008       ();
1009     cgi#out_channel#output_string body
1010    with e -> 
1011     prerr_endline ("error in retract: " ^ Printexc.to_string e);
1012     cgi#set_header ~status:`Internal_server_error 
1013       ~cache:`No_cache 
1014       ~content_type:"text/xml; charset=\"utf-8\"" ());
1015   cgi#out_channel#commit_work() 
1016 ;;
1017
1018
1019 let viewLib  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1020   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1021   let env = cgi#environment in
1022   
1023     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
1024     let sid = HExtlib.unopt sid in
1025     (*
1026     cgi # set_header 
1027       ~cache:`No_cache 
1028       ~content_type:"text/html; charset=\"utf-8\""
1029       ();
1030     *)
1031     let uid = MatitaAuthentication.user_of_session sid in
1032     
1033     let ft = MatitaAuthentication.read_ft uid in
1034     let html = MatitaFilesystem.html_of_library uid ft in
1035     cgi # set_header 
1036       ~cache:`No_cache 
1037       ~content_type:"text/html; charset=\"utf-8\""
1038       ();
1039     cgi#out_channel#output_string
1040       ((*
1041        "<html><head>\n" ^
1042        "<title>XML Tree Control</title>\n" ^
1043        "<link href=\"treeview/xmlTree.css\" type=\"text/css\" rel=\"stylesheet\">\n" ^
1044        "<script src=\"treeview/xmlTree.js\" type=\"text/javascript\"></script>\n" ^
1045        "<body>\n" ^ *)
1046        html (* ^ "\n</body></html>" *) );
1047     
1048     let files,anomalies = MatitaFilesystem.stat_user uid in
1049     let changed = HExtlib.filter_map 
1050       (fun (n,f) -> if (f = Some MatitaFilesystem.MModified) then Some n else None) files
1051     in
1052     let changed = String.concat "\n" changed in
1053     let anomalies = String.concat "\n" anomalies in
1054     prerr_endline ("Changed:\n" ^ changed ^ "\n\nAnomalies:\n" ^ anomalies);
1055   cgi#out_channel#commit_work()
1056   
1057 ;;
1058
1059 let resetLib  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1060   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1061   MatitaAuthentication.reset ();
1062     cgi # set_header 
1063       ~cache:`No_cache 
1064       ~content_type:"text/html; charset=\"utf-8\""
1065       ();
1066     
1067     cgi#out_channel#output_string
1068       ("<html><head>\n" ^
1069        "<title>Matitaweb Reset</title>\n" ^
1070        "<body><H1>Reset completed</H1></body></html>");
1071     cgi#out_channel#commit_work()
1072
1073 open Netcgi1_compat.Netcgi_types;;
1074
1075 (**********************************************************************)
1076 (* Create the webserver                                               *)
1077 (**********************************************************************)
1078
1079
1080 let start() =
1081   let (opt_list, cmdline_cfg) = Netplex_main.args() in
1082
1083   let use_mt = ref true in
1084
1085   let opt_list' =
1086     [ "-mt", Arg.Set use_mt,
1087       "  Use multi-threading instead of multi-processing"
1088     ] @ opt_list in
1089
1090   Arg.parse 
1091     opt_list'
1092     (fun s -> raise (Arg.Bad ("Don't know what to do with: " ^ s)))
1093     "usage: netplex [options]";
1094   let parallelizer = 
1095     if !use_mt then
1096       Netplex_mt.mt()     (* multi-threading *)
1097     else
1098       Netplex_mp.mp() in  (* multi-processing *)
1099 (*
1100   let adder =
1101     { Nethttpd_services.dyn_handler = (fun _ -> process1);
1102       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1103       dyn_uri = None;                 (* not needed *)
1104       dyn_translator = (fun _ -> ""); (* not needed *)
1105       dyn_accept_all_conditionals = false;
1106     } in
1107 *)
1108   let do_advance =
1109     { Nethttpd_services.dyn_handler = (fun _ -> advance);
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_retract =
1116     { Nethttpd_services.dyn_handler = (fun _ -> retract);
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 goto_bottom =
1123     { Nethttpd_services.dyn_handler = (fun _ -> gotoBottom);
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 goto_top =
1130     { Nethttpd_services.dyn_handler = (fun _ -> gotoTop);
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 retrieve =
1137     { Nethttpd_services.dyn_handler = (fun _ -> retrieve);
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_register =
1144     { Nethttpd_services.dyn_handler = (fun _ -> register);
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_login =
1151     { Nethttpd_services.dyn_handler = (fun _ -> login);
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_logout =
1158     { Nethttpd_services.dyn_handler = (fun _ -> logout);
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_viewlib =
1165     { Nethttpd_services.dyn_handler = (fun _ -> viewLib);
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   let do_resetlib =
1172     { Nethttpd_services.dyn_handler = (fun _ -> resetLib);
1173       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1174       dyn_uri = None;                 (* not needed *)
1175       dyn_translator = (fun _ -> ""); (* not needed *)
1176       dyn_accept_all_conditionals = false;
1177     } in 
1178   let do_save =
1179     { Nethttpd_services.dyn_handler = (fun _ -> save);
1180       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1181       dyn_uri = None;                 (* not needed *)
1182       dyn_translator = (fun _ -> ""); (* not needed *)
1183       dyn_accept_all_conditionals = false;
1184     } in 
1185   let do_commit =
1186     { Nethttpd_services.dyn_handler = (fun _ -> initiate_commit);
1187       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1188       dyn_uri = None;                 (* not needed *)
1189       dyn_translator = (fun _ -> ""); (* not needed *)
1190       dyn_accept_all_conditionals = false;
1191     } in 
1192   let do_update =
1193     { Nethttpd_services.dyn_handler = (fun _ -> svn_update);
1194       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1195       dyn_uri = None;                 (* not needed *)
1196       dyn_translator = (fun _ -> ""); (* not needed *)
1197       dyn_accept_all_conditionals = false;
1198     } in 
1199   
1200   
1201   let nethttpd_factory = 
1202     Nethttpd_plex.nethttpd_factory
1203       ~handlers:[ "advance", do_advance
1204                 ; "retract", do_retract
1205                 ; "bottom", goto_bottom
1206                 ; "top", goto_top
1207                 ; "open", retrieve 
1208                 ; "register", do_register
1209                 ; "login", do_login 
1210                 ; "logout", do_logout 
1211                 ; "reset", do_resetlib
1212                 ; "viewlib", do_viewlib
1213                 ; "save", do_save
1214                 ; "commit", do_commit
1215                 ; "update", do_update]
1216       () in
1217   MatitaInit.initialize_all ();
1218   MatitaAuthentication.deserialize ();
1219   Netplex_main.startup
1220     parallelizer
1221     Netplex_log.logger_factories   (* allow all built-in logging styles *)
1222     Netplex_workload.workload_manager_factories (* ... all ways of workload management *)
1223     [ nethttpd_factory ]           (* make this nethttpd available *)
1224     cmdline_cfg
1225 ;;
1226
1227 Sys.set_signal Sys.sigpipe Sys.Signal_ignore;
1228 start();;