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