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