]> matita.cs.unibo.it Git - helm.git/blob - matitaB/matita/matitadaemon.ml
Hyperlink support.
[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 = (MatitaAuthentication.get_status sid)#set_baseuri 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   | Not_found _ -> 
422     cgi # set_header
423       ~status:`Internal_server_error
424       ~cache:`No_cache 
425       ~content_type:"text/html; charset=\"utf-8\""
426       ());
427   cgi#out_channel#commit_work()
428 ;;
429
430 let xml_of_disamb_error l =
431   let mk_alias = function
432   | GrafiteAst.Ident_alias (_,uri) -> "href=\"" ^ uri ^ "\""
433   | GrafiteAst.Symbol_alias (_,uri,desc) 
434   | GrafiteAst.Number_alias (uri,desc) -> 
435       let uri = try HExtlib.unopt uri with _ -> "cic:/fakeuri.def(1)" in
436         "href=\"" ^ uri ^ "\" title=\"" ^ 
437         (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
438         ^ "\""
439   in
440
441   let mk_interpr (loc,a) =
442     let x,y = HExtlib.loc_of_floc loc in
443     Printf.sprintf "<interpretation start=\"%d\" stop=\"%d\" %s />"
444       x y (mk_alias a)
445   in
446
447   let mk_failure (il,loc,msg) =
448     let x,y = HExtlib.loc_of_floc loc in
449     Printf.sprintf "<failure start=\"%d\" stop=\"%d\" title=\"%s\">%s</failure>"
450       x y (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () msg)
451       (String.concat "" (List.map mk_interpr il))
452   in
453
454   let mk_choice (a,fl) = 
455     let fl' = String.concat "" (List.map mk_failure fl) in
456     match a with
457     | None -> "<choice>" ^ fl' ^ "</choice>"
458     | Some a -> Printf.sprintf "<choice %s>%s</choice>" (mk_alias a) fl'
459   in
460
461   let mk_located (loc,cl) =
462     let x,y = HExtlib.loc_of_floc loc in
463     Printf.sprintf "<choicepoint start=\"%d\" stop=\"%d\">%s</choicepoint>"
464       x y (String.concat "" (List.map mk_choice cl))
465   in
466   "<disamberror>" ^ (String.concat "" (List.map mk_located l)) ^ "</disamberror>"
467 ;;
468
469 let advance0 sid text =
470   let status = MatitaAuthentication.get_status sid in
471   let history = MatitaAuthentication.get_history sid in
472   let status = status#reset_disambiguate_db () in
473   let (st,new_statements,new_unparsed),parsed_len =
474     let rec do_exc = function
475     | HExtlib.Localized (floc,e) -> 
476       let x, y = HExtlib.loc_of_floc floc in
477       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
478       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
479       let post = Netconversion.ustring_sub `Enc_utf8 y 
480          (Netconversion.ustring_length `Enc_utf8 text - y) text in
481       let _,title = MatitaExcPp.to_string e in
482       (* let title = "" in *)
483       let marked = 
484         pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
485       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
486       () (html_of_matita marked) in
487       raise (Emphasized_error marked)
488     | Disambiguate.NoWellTypedInterpretation (floc,e) ->
489       let x, y = HExtlib.loc_of_floc floc in
490       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
491       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
492       let post = Netconversion.ustring_sub `Enc_utf8 y 
493          (Netconversion.ustring_length `Enc_utf8 text - y) text in
494       (*let _,title = MatitaExcPp.to_string e in*)
495       (* let title = "" in *)
496       let marked = 
497         pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
498       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
499       () (html_of_matita marked) in
500       raise (Emphasized_error marked)
501     | NCicRefiner.Uncertain m as exn ->
502       let floc, e = Lazy.force m in
503       let x, y = HExtlib.loc_of_floc floc in
504       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
505       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
506       let post = Netconversion.ustring_sub `Enc_utf8 y 
507          (Netconversion.ustring_length `Enc_utf8 text - y) text in
508       (* let _,title = MatitaExcPp.to_string e in *)
509       (* let title = "" in *)
510       let marked = 
511         pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
512       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
513       () (html_of_matita marked) in
514       raise (Emphasized_error marked)
515     | NTacStatus.Error (s,None) as e ->
516         prerr_endline 
517           ("NTacStatus.Error " ^ (Lazy.force s)); raise e
518     | NTacStatus.Error (s,Some exc) as e ->
519         prerr_endline 
520           ("NTacStatus.Error " ^ Lazy.force s ^ " -- " ^ (Printexc.to_string exc));
521         do_exc exc
522     | GrafiteDisambiguate.Ambiguous_input (loc,choices) ->
523       let x,y = HExtlib.loc_of_floc loc in
524       let choice_of_alias = function
525        | GrafiteAst.Ident_alias (_,uri) -> uri, None, uri
526        | GrafiteAst.Number_alias (None,desc)
527        | GrafiteAst.Symbol_alias (_,None,desc) -> "cic:/fakeuri.def(1)", Some desc, desc
528        | GrafiteAst.Number_alias (Some uri,desc)
529        | GrafiteAst.Symbol_alias (_,Some uri,desc) -> uri, Some desc, desc
530       in
531       let tag_of_choice (uri,title,desc) =
532         match title with
533         | None -> Printf.sprintf "<choice href=\"%s\">%s</choice>"
534             uri 
535             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
536         | Some t -> Printf.sprintf "<choice href=\"%s\" title=\"%s\">%s</choice>"
537             uri 
538             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () t)
539             (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
540       in
541       let strchoices = 
542         String.concat "\n" 
543           (List.map (fun x -> tag_of_choice (choice_of_alias x)) choices)
544       in
545       prerr_endline (Printf.sprintf
546         "@@@ Ambiguous input at (%d,%d). Possible choices:\n\n%s\n\n@@@ End."
547           x y strchoices);
548       (*
549       let pre = Netconversion.ustring_sub `Enc_utf8  0 x text in
550       let err = Netconversion.ustring_sub `Enc_utf8  x (y-x) text in
551       let post = Netconversion.ustring_sub `Enc_utf8 y 
552          (Netconversion.ustring_length `Enc_utf8 text - y) text in
553       let title = "Disambiguation Error" in
554       (* let title = "" in *)
555       let marked = 
556         pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
557       let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
558       () (html_of_matita marked) in
559       *)
560       let strchoices = Printf.sprintf
561         "<ambiguity start=\"%d\" stop=\"%d\">%s</ambiguity>" x y strchoices
562       in raise (Disamb_error strchoices)
563    | GrafiteDisambiguate.Error l -> raise (Disamb_error (xml_of_disamb_error l))
564    (* | End_of_file -> ...          *)
565    | e -> 
566       prerr_endline ("matitadaemon *** Unhandled exception " ^ Printexc.to_string e);
567       raise e
568    in
569
570     try
571       eval_statement !include_paths (*buffer*) status (`Raw text)
572     with e -> do_exc e
573   in
574         debug "BEGIN PRINTGRAMMAR";
575         (*prerr_endline (Print_grammar.ebnf_of_term status);*)
576         (*let kwds = String.concat ", " status#get_kwds in
577         debug ("keywords = " ^ kwds );*)
578         debug "END PRINTGRAMMAR";
579   MatitaAuthentication.set_status sid st;
580   MatitaAuthentication.set_history sid (st::history);
581 (*  prerr_endline "previous timestamp";
582   status#print_timestamp();
583   prerr_endline "current timestamp";
584   st#print_timestamp(); *)
585   parsed_len, 
586     Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false 
587       () (html_of_matita new_statements), new_unparsed, st
588
589 let register  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
590   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
591   let _env = cgi#environment in
592   
593   assert (cgi#arguments <> []);
594   let uid = cgi#argument_value "userid" in
595   let userpw = cgi#argument_value "password" in
596   (try
597     (* currently registering only unprivileged users *) 
598     MatitaAuthentication.add_user uid userpw false;
599 (*    env#set_output_header_field "Location" "/index.html" *)
600     cgi#out_channel#output_string
601      ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/login.html\">"
602      ^ "</head><body>Redirecting to login page...</body></html>")
603    with
604    | MatitaAuthentication.UsernameCollision _ ->
605       cgi#set_header
606        ~cache:`No_cache 
607        ~content_type:"text/html; charset=\"utf-8\""
608        ();
609      cgi#out_channel#output_string
610       "<html><head></head><body>Error: User id collision!</body></html>"
611    | MatitaFilesystem.SvnError msg ->
612       cgi#set_header
613        ~cache:`No_cache 
614        ~content_type:"text/html; charset=\"utf-8\""
615        ();
616      cgi#out_channel#output_string
617       ("<html><head></head><body><p>Error: Svn checkout failed!<p><p><textarea>"
618        ^ msg ^ "</textarea></p></body></html>"));
619   cgi#out_channel#commit_work()
620 ;;
621
622 let login  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
623   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
624   let env = cgi#environment in
625   
626   assert (cgi#arguments <> []);
627   let uid = cgi#argument_value "userid" in
628   let userpw = cgi#argument_value "password" in
629   (try 
630       MatitaAuthentication.check_pw uid userpw;
631       NCicLibrary.init (Some uid);
632       let ft = MatitaAuthentication.read_ft uid in
633       let _ = MatitaFilesystem.html_of_library uid ft in
634        let sid = MatitaAuthentication.create_session uid in
635        (* let cookie = Netcgi.Cookie.make "session" (Uuidm.to_string sid) in
636           cgi#set_header ~set_cookies:[cookie] (); *)
637        env#set_output_header_field 
638          "Set-Cookie" ("session=" ^ (Uuidm.to_string sid));
639    (*    env#set_output_header_field "Location" "/index.html" *)
640        cgi#out_channel#output_string
641         ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/index.html\">"
642         ^ "</head><body>Redirecting to Matita page...</body></html>")
643   with MatitaAuthentication.InvalidPassword ->
644     cgi#set_header
645       ~cache:`No_cache 
646       ~content_type:"text/html; charset=\"utf-8\""
647       ();
648     cgi#out_channel#output_string
649       "<html><head></head><body>Authentication error</body></html>");
650   cgi#out_channel#commit_work()
651 ;;
652
653 let logout  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
654   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
655   let env = cgi#environment in
656   (try 
657     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
658     let sid = HExtlib.unopt sid in
659     MatitaAuthentication.logout_user sid;
660     cgi # set_header 
661       ~cache:`No_cache 
662       ~content_type:"text/html; charset=\"utf-8\""
663       ();
664     let text = read_file (rt_path () ^ "/logout.html") in
665     cgi#out_channel#output_string text
666   with
667   | Not_found _ -> 
668     cgi # set_header
669       ~status:`Internal_server_error
670       ~cache:`No_cache 
671       ~content_type:"text/html; charset=\"utf-8\""
672       ());
673   cgi#out_channel#commit_work()
674 ;;
675
676 exception File_already_exists;;
677
678 let save  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
679   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
680   let env = cgi#environment in
681   (try 
682     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
683     let sid = HExtlib.unopt sid in
684     let status = MatitaAuthentication.get_status sid in
685     let uid = MatitaAuthentication.user_of_session sid in
686     assert (cgi#arguments <> []);
687     let locked = cgi#argument_value "locked" in
688     let unlocked = cgi#argument_value "unlocked" in
689     let dir = cgi#argument_value "dir" in
690     let rel_filename = cgi # argument_value "file" in
691     let filename = libdir uid ^ "/" ^ rel_filename in
692     let force = bool_of_string (cgi#argument_value "force") in
693     let already_exists = Sys.file_exists filename in
694
695     if ((not force) && already_exists) then 
696       raise File_already_exists;
697
698     if dir = "true" then
699        Unix.mkdir filename 0o744
700     else 
701      begin
702       let oc = open_out filename in
703       output_string oc (locked ^ unlocked);
704       close_out oc;
705       if MatitaEngine.eos status unlocked then
706        begin
707         (* prerr_endline ("serializing proof objects..."); *)
708         GrafiteTypes.Serializer.serialize 
709           ~baseuri:(NUri.uri_of_string status#baseuri) status;
710         (* prerr_endline ("done."); *)
711        end;
712      end;
713     let old_flag =
714       try 
715         List.assoc rel_filename (MatitaAuthentication.read_ft uid)
716       with Not_found -> MatitaFilesystem.MUnversioned
717     in
718     (if old_flag <> MatitaFilesystem.MConflict &&
719        old_flag <> MatitaFilesystem.MAdd then
720       let newflag = 
721         if already_exists then MatitaFilesystem.MModified
722         else MatitaFilesystem.MAdd
723       in
724       MatitaAuthentication.set_file_flag uid [rel_filename, Some newflag]);
725     cgi # set_header 
726      ~cache:`No_cache 
727      ~content_type:"text/xml; charset=\"utf-8\""
728      ();
729     cgi#out_channel#output_string "<response>ok</response>"
730   with
731   | File_already_exists ->
732       cgi#out_channel#output_string "<response>cancelled</response>"
733   | Sys_error _ -> 
734     cgi # set_header
735       ~status:`Internal_server_error
736       ~cache:`No_cache 
737       ~content_type:"text/xml; charset=\"utf-8\""
738       ()
739   | e ->
740       let estr = Printexc.to_string e in
741       cgi#out_channel#output_string ("<response>" ^ estr ^ "</response>"));
742   cgi#out_channel#commit_work()
743 ;;
744
745 let initiate_commit (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
746   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
747   let env = cgi#environment in
748   (try
749     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
750     let sid = HExtlib.unopt sid in
751     MatitaAuthentication.probe_commit_priv sid;
752     let out = do_global_commit () in
753     cgi # set_header 
754       ~cache:`No_cache 
755       ~content_type:"text/xml; charset=\"utf-8\""
756       ();
757     cgi#out_channel#output_string "<commit>";
758     cgi#out_channel#output_string "<response>ok</response>";
759     cgi#out_channel#output_string ("<details>" ^ out ^ "</details>");
760     cgi#out_channel#output_string "</commit>"
761   with
762   | Not_found _ -> 
763     cgi # set_header
764       ~status:`Internal_server_error
765       ~cache:`No_cache 
766       ~content_type:"text/xml; charset=\"utf-8\""
767       ());
768   cgi#out_channel#commit_work()
769 ;;
770
771 let svn_update  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
772   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
773   let env = cgi#environment in
774   let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
775   let sid = HExtlib.unopt sid in
776   let uid = MatitaAuthentication.user_of_session sid in
777   (try
778     MatitaAuthentication.probe_commit_priv sid;
779     let files,anomalies,(added,conflict,del,upd,merged) = 
780       MatitaFilesystem.update_user uid 
781     in
782     let anomalies = String.concat "\n" anomalies in
783     let details = Printf.sprintf 
784       ("%d new files\n"^^
785        "%d deleted files\n"^^
786        "%d updated files\n"^^
787        "%d merged files\n"^^
788        "%d conflicting files\n\n" ^^
789        "Anomalies:\n%s") added del upd merged conflict anomalies
790     in
791     prerr_endline ("update details:\n" ^ details);
792     let details = 
793       Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () details
794     in
795     MatitaAuthentication.set_file_flag uid files;
796     cgi # set_header 
797       ~cache:`No_cache 
798       ~content_type:"text/xml; charset=\"utf-8\""
799       ();
800     cgi#out_channel#output_string "<update>";
801     cgi#out_channel#output_string "<response>ok</response>";
802     cgi#out_channel#output_string ("<details>" ^ details ^ "</details>");
803     cgi#out_channel#output_string "</update>";
804   with
805   | Not_found _ -> 
806     cgi # set_header
807       ~status:`Internal_server_error
808       ~cache:`No_cache 
809       ~content_type:"text/xml; charset=\"utf-8\""
810       ());
811   cgi#out_channel#commit_work()
812 ;;
813
814 (* returns the length of the executed text and an html representation of the
815  * current metasenv*)
816 (*let advance  =*)
817 let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
818   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
819   let env = cgi#environment in
820   (try 
821     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
822     let sid = HExtlib.unopt sid in
823     (*
824     cgi # set_header 
825       ~cache:`No_cache 
826       ~content_type:"text/xml; charset=\"utf-8\""
827       ();
828     *)
829     let text = cgi#argument_value "body" in
830     (* prerr_endline ("body =\n" ^ text); *)
831     let parsed_len, new_parsed, new_unparsed, new_status = advance0 sid text in
832     let txt = output_status new_status in
833     let body = 
834        "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\">" ^
835        new_parsed ^ "</parsed>" ^ txt 
836        ^ "</response>"
837     in 
838     (* prerr_endline ("sending advance response:\n" ^ body); *)
839     cgi # set_header 
840       ~cache:`No_cache 
841       ~content_type:"text/xml; charset=\"utf-8\""
842       ();
843     cgi#out_channel#output_string body
844    with
845   | Emphasized_error text ->
846 (* | MultiPassDisambiguator.DisambiguationError (offset,errorll) -> *)
847     let body = "<response><error>" ^ text ^ "</error></response>" in 
848     cgi # set_header 
849       ~cache:`No_cache 
850       ~content_type:"text/xml; charset=\"utf-8\""
851       ();
852     cgi#out_channel#output_string body
853   | Disamb_error text -> 
854     let body = "<response>" ^ text ^ "</response>" in 
855     cgi # set_header 
856       ~cache:`No_cache 
857       ~content_type:"text/xml; charset=\"utf-8\""
858       ();
859     cgi#out_channel#output_string body
860   | Not_found _ -> 
861     cgi # set_header
862       ~status:`Internal_server_error
863       ~cache:`No_cache 
864       ~content_type:"text/xml; charset=\"utf-8\""
865       ()
866   );
867   cgi#out_channel#commit_work()
868 ;;
869
870 let gotoBottom  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
871   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
872   let env = cgi#environment in
873 (*  (try  *)
874     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
875     let sid = HExtlib.unopt sid in
876
877     let error_msg = function
878       | Emphasized_error text -> "<localized>" ^ text ^ "</localized>" 
879       | Disamb_error text -> text
880       | End_of_file _ -> (* not an error *) ""
881       | e -> (* unmanaged error *)
882           "<error>" ^ 
883           (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () 
884             (Printexc.to_string e)) ^ "</error>"
885     in
886
887     let rec aux acc text =
888       try
889         prerr_endline ("evaluating: " ^ first_line text);
890         let plen,new_parsed,new_unparsed,_new_status = advance0 sid text in
891         aux ((plen,new_parsed)::acc) new_unparsed
892       with e -> acc, error_msg e 
893         (* DON'T SERIALIZE NOW!!!
894           let status = MatitaAuthentication.get_status sid in
895           GrafiteTypes.Serializer.serialize 
896             ~baseuri:(NUri.uri_of_string status#baseuri) status;
897           acc, error_msg e *)
898     in
899     (* 
900     cgi # set_header 
901       ~cache:`No_cache 
902       ~content_type:"text/xml; charset=\"utf-8\""
903       ();
904     *)
905     let text = cgi#argument_value "body" in
906     (* prerr_endline ("body =\n" ^ text); *)
907     let len_parsedlist, err_msg = aux [] text in
908     let status = MatitaAuthentication.get_status sid in
909     let txt = output_status status in
910     let parsed_tag (len,txt) = 
911        "<parsed length=\"" ^ (string_of_int len) ^ "\">" ^ txt ^ "</parsed>"
912     in
913     (* List.rev: the list begins with the older parsed txt *)
914     let body = 
915        "<response>" ^
916        String.concat "" (List.rev (List.map parsed_tag len_parsedlist)) ^
917        txt ^ err_msg ^ "</response>"
918     in
919     (* prerr_endline ("sending goto bottom response:\n" ^ body); *)
920     cgi # set_header 
921       ~cache:`No_cache 
922       ~content_type:"text/xml; charset=\"utf-8\""
923       ();
924     cgi#out_channel#output_string body;
925 (*   with Not_found -> cgi#set_header ~status:`Internal_server_error 
926       ~cache:`No_cache 
927       ~content_type:"text/xml; charset=\"utf-8\"" ()); *)
928   cgi#out_channel#commit_work() 
929 ;;
930
931 let gotoTop  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
932   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
933   let env = cgi#environment in
934   prerr_endline "executing goto Top";
935   (try 
936     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
937     let sid = HExtlib.unopt sid in
938     (*
939     cgi # set_header 
940       ~cache:`No_cache 
941       ~content_type:"text/xml; charset=\"utf-8\""
942       ();
943     *)
944     let status = MatitaAuthentication.get_status sid in
945     let uid = MatitaAuthentication.user_of_session sid in
946     let baseuri = status#baseuri in
947     let new_status = new MatitaEngine.status (Some uid) baseuri in
948     prerr_endline "gototop prima della time travel";
949     (* NCicLibrary.time_travel new_status; *)
950     prerr_endline "gototop dopo della time travel";
951     let new_history = [new_status] in 
952     MatitaAuthentication.set_history sid new_history;
953     MatitaAuthentication.set_status sid new_status;
954     (* NCicLibrary.time_travel new_status; *)
955     cgi # set_header 
956       ~cache:`No_cache 
957       ~content_type:"text/xml; charset=\"utf-8\""
958       ();
959     cgi#out_channel#output_string "<response>ok</response>"
960    with _ -> 
961      (cgi#set_header ~status:`Internal_server_error 
962       ~cache:`No_cache 
963       ~content_type:"text/xml; charset=\"utf-8\"" ();
964       cgi#out_channel#output_string "<response>ok</response>"));
965   cgi#out_channel#commit_work() 
966 ;;
967
968 let retract  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
969   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
970   let env = cgi#environment in
971   (try  
972     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
973     let sid = HExtlib.unopt sid in
974     (*
975     cgi # set_header 
976       ~cache:`No_cache 
977       ~content_type:"text/xml; charset=\"utf-8\""
978       ();
979     *)
980     let history = MatitaAuthentication.get_history sid in
981     let old_status = MatitaAuthentication.get_status sid in
982     let new_history,new_status =
983        match history with
984          _::(status::_ as history) ->
985           history, status
986       | [_] -> (prerr_endline "singleton";failwith "retract")
987       | _ -> (prerr_endline "nil"; assert false) in
988 (*    prerr_endline "timestamp prima della retract";
989     old_status#print_timestamp ();
990     prerr_endline "timestamp della retract";
991     new_status#print_timestamp ();
992     prerr_endline ("prima della time travel"); *)
993     NCicLibrary.time_travel new_status;
994     prerr_endline ("dopo della time travel");
995     MatitaAuthentication.set_history sid new_history;
996     MatitaAuthentication.set_status sid new_status;
997     prerr_endline ("baseuri after retract = " ^ new_status#baseuri);
998     let body = output_status new_status in
999     cgi # set_header 
1000       ~cache:`No_cache 
1001       ~content_type:"text/xml; charset=\"utf-8\""
1002       ();
1003     cgi#out_channel#output_string body
1004    with e -> 
1005     prerr_endline ("error in retract: " ^ Printexc.to_string e);
1006     cgi#set_header ~status:`Internal_server_error 
1007       ~cache:`No_cache 
1008       ~content_type:"text/xml; charset=\"utf-8\"" ());
1009   cgi#out_channel#commit_work() 
1010 ;;
1011
1012
1013 let viewLib  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1014   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1015   let env = cgi#environment in
1016   
1017     let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
1018     let sid = HExtlib.unopt sid in
1019     (*
1020     cgi # set_header 
1021       ~cache:`No_cache 
1022       ~content_type:"text/html; charset=\"utf-8\""
1023       ();
1024     *)
1025     let uid = MatitaAuthentication.user_of_session sid in
1026     
1027     let ft = MatitaAuthentication.read_ft uid in
1028     let html = MatitaFilesystem.html_of_library uid ft in
1029     cgi # set_header 
1030       ~cache:`No_cache 
1031       ~content_type:"text/html; charset=\"utf-8\""
1032       ();
1033     cgi#out_channel#output_string
1034       ((*
1035        "<html><head>\n" ^
1036        "<title>XML Tree Control</title>\n" ^
1037        "<link href=\"treeview/xmlTree.css\" type=\"text/css\" rel=\"stylesheet\">\n" ^
1038        "<script src=\"treeview/xmlTree.js\" type=\"text/javascript\"></script>\n" ^
1039        "<body>\n" ^ *)
1040        html (* ^ "\n</body></html>" *) );
1041     
1042     let files,anomalies = MatitaFilesystem.stat_user uid in
1043     let changed = HExtlib.filter_map 
1044       (fun (n,f) -> if (f = Some MatitaFilesystem.MModified) then Some n else None) files
1045     in
1046     let changed = String.concat "\n" changed in
1047     let anomalies = String.concat "\n" anomalies in
1048     prerr_endline ("Changed:\n" ^ changed ^ "\n\nAnomalies:\n" ^ anomalies);
1049   cgi#out_channel#commit_work()
1050   
1051 ;;
1052
1053 let resetLib  (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1054   let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1055   MatitaAuthentication.reset ();
1056     cgi # set_header 
1057       ~cache:`No_cache 
1058       ~content_type:"text/html; charset=\"utf-8\""
1059       ();
1060     
1061     cgi#out_channel#output_string
1062       ("<html><head>\n" ^
1063        "<title>Matitaweb Reset</title>\n" ^
1064        "<body><H1>Reset completed</H1></body></html>");
1065     cgi#out_channel#commit_work()
1066
1067 open Netcgi1_compat.Netcgi_types;;
1068
1069 (**********************************************************************)
1070 (* Create the webserver                                               *)
1071 (**********************************************************************)
1072
1073
1074 let start() =
1075   let (opt_list, cmdline_cfg) = Netplex_main.args() in
1076
1077   let use_mt = ref true in
1078
1079   let opt_list' =
1080     [ "-mt", Arg.Set use_mt,
1081       "  Use multi-threading instead of multi-processing"
1082     ] @ opt_list in
1083
1084   Arg.parse 
1085     opt_list'
1086     (fun s -> raise (Arg.Bad ("Don't know what to do with: " ^ s)))
1087     "usage: netplex [options]";
1088   let parallelizer = 
1089     if !use_mt then
1090       Netplex_mt.mt()     (* multi-threading *)
1091     else
1092       Netplex_mp.mp() in  (* multi-processing *)
1093 (*
1094   let adder =
1095     { Nethttpd_services.dyn_handler = (fun _ -> process1);
1096       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1097       dyn_uri = None;                 (* not needed *)
1098       dyn_translator = (fun _ -> ""); (* not needed *)
1099       dyn_accept_all_conditionals = false;
1100     } in
1101 *)
1102   let do_advance =
1103     { Nethttpd_services.dyn_handler = (fun _ -> advance);
1104       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1105       dyn_uri = None;                 (* not needed *)
1106       dyn_translator = (fun _ -> ""); (* not needed *)
1107       dyn_accept_all_conditionals = false;
1108     } in
1109   let do_retract =
1110     { Nethttpd_services.dyn_handler = (fun _ -> retract);
1111       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1112       dyn_uri = None;                 (* not needed *)
1113       dyn_translator = (fun _ -> ""); (* not needed *)
1114       dyn_accept_all_conditionals = false;
1115     } in
1116   let goto_bottom =
1117     { Nethttpd_services.dyn_handler = (fun _ -> gotoBottom);
1118       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1119       dyn_uri = None;                 (* not needed *)
1120       dyn_translator = (fun _ -> ""); (* not needed *)
1121       dyn_accept_all_conditionals = false;
1122     } in
1123   let goto_top =
1124     { Nethttpd_services.dyn_handler = (fun _ -> gotoTop);
1125       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1126       dyn_uri = None;                 (* not needed *)
1127       dyn_translator = (fun _ -> ""); (* not needed *)
1128       dyn_accept_all_conditionals = false;
1129     } in
1130   let retrieve =
1131     { Nethttpd_services.dyn_handler = (fun _ -> retrieve);
1132       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1133       dyn_uri = None;                 (* not needed *)
1134       dyn_translator = (fun _ -> ""); (* not needed *)
1135       dyn_accept_all_conditionals = false;
1136     } in
1137   let do_register =
1138     { Nethttpd_services.dyn_handler = (fun _ -> register);
1139       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1140       dyn_uri = None;                 (* not needed *)
1141       dyn_translator = (fun _ -> ""); (* not needed *)
1142       dyn_accept_all_conditionals = false;
1143     } in
1144   let do_login =
1145     { Nethttpd_services.dyn_handler = (fun _ -> login);
1146       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1147       dyn_uri = None;                 (* not needed *)
1148       dyn_translator = (fun _ -> ""); (* not needed *)
1149       dyn_accept_all_conditionals = false;
1150     } in
1151   let do_logout =
1152     { Nethttpd_services.dyn_handler = (fun _ -> logout);
1153       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1154       dyn_uri = None;                 (* not needed *)
1155       dyn_translator = (fun _ -> ""); (* not needed *)
1156       dyn_accept_all_conditionals = false;
1157     } in 
1158   let do_viewlib =
1159     { Nethttpd_services.dyn_handler = (fun _ -> viewLib);
1160       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1161       dyn_uri = None;                 (* not needed *)
1162       dyn_translator = (fun _ -> ""); (* not needed *)
1163       dyn_accept_all_conditionals = false;
1164     } in 
1165   let do_resetlib =
1166     { Nethttpd_services.dyn_handler = (fun _ -> resetLib);
1167       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1168       dyn_uri = None;                 (* not needed *)
1169       dyn_translator = (fun _ -> ""); (* not needed *)
1170       dyn_accept_all_conditionals = false;
1171     } in 
1172   let do_save =
1173     { Nethttpd_services.dyn_handler = (fun _ -> save);
1174       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1175       dyn_uri = None;                 (* not needed *)
1176       dyn_translator = (fun _ -> ""); (* not needed *)
1177       dyn_accept_all_conditionals = false;
1178     } in 
1179   let do_commit =
1180     { Nethttpd_services.dyn_handler = (fun _ -> initiate_commit);
1181       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1182       dyn_uri = None;                 (* not needed *)
1183       dyn_translator = (fun _ -> ""); (* not needed *)
1184       dyn_accept_all_conditionals = false;
1185     } in 
1186   let do_update =
1187     { Nethttpd_services.dyn_handler = (fun _ -> svn_update);
1188       dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1189       dyn_uri = None;                 (* not needed *)
1190       dyn_translator = (fun _ -> ""); (* not needed *)
1191       dyn_accept_all_conditionals = false;
1192     } in 
1193   
1194   
1195   let nethttpd_factory = 
1196     Nethttpd_plex.nethttpd_factory
1197       ~handlers:[ "advance", do_advance
1198                 ; "retract", do_retract
1199                 ; "bottom", goto_bottom
1200                 ; "top", goto_top
1201                 ; "open", retrieve 
1202                 ; "register", do_register
1203                 ; "login", do_login 
1204                 ; "logout", do_logout 
1205                 ; "reset", do_resetlib
1206                 ; "viewlib", do_viewlib
1207                 ; "save", do_save
1208                 ; "commit", do_commit
1209                 ; "update", do_update]
1210       () in
1211   MatitaInit.initialize_all ();
1212   MatitaAuthentication.deserialize ();
1213   Netplex_main.startup
1214     parallelizer
1215     Netplex_log.logger_factories   (* allow all built-in logging styles *)
1216     Netplex_workload.workload_manager_factories (* ... all ways of workload management *)
1217     [ nethttpd_factory ]           (* make this nethttpd available *)
1218     cmdline_cfg
1219 ;;
1220
1221 Sys.set_signal Sys.sigpipe Sys.Signal_ignore;
1222 start();;