4 exception Emphasized_error of string
5 exception Disamb_error of string
6 exception Generic_error of string
8 module Stack = Continuationals.Stack
10 let debug = prerr_endline
11 (* disable for debug *)
12 let prerr_endline _ = ()
14 let rt_path () = Helm_registry.get "matita.rt_base_dir"
16 let libdir uid = (rt_path ()) ^ "/users/" ^ uid
18 let utf8_length = Netconversion.ustring_length `Enc_utf8
20 let mutex = Mutex.create ();;
22 let to_be_committed = ref [];;
24 let html_of_matita s =
25 let patt1 = Str.regexp "\005" in
26 let patt2 = Str.regexp "\006" in
27 let patt3 = Str.regexp "<" in
28 let patt4 = Str.regexp ">" in
29 let res = Str.global_replace patt4 ">" s in
30 let res = Str.global_replace patt3 "<" res in
31 let res = Str.global_replace patt2 ">" res in
32 let res = Str.global_replace patt1 "<" res in
36 (* adds a user to the commit queue; concurrent instances possible, so we
37 * enclose the update in a CS
39 let add_user_for_commit uid =
41 to_be_committed := uid::List.filter (fun x -> x <> uid) !to_be_committed;
45 let do_global_commit (* () *) uid =
46 prerr_endline ("to be committed: " ^ String.concat " " !to_be_committed);
49 let ft = MatitaAuthentication.read_ft u in
51 (* first we add new files/dirs to the repository *)
52 (* must take the reverse because svn requires the add to be performed in
54 (otherwise run with --parents option) *)
55 let to_be_added = List.rev (List.map fst
56 (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MAdd) ft))
58 prerr_endline ("@@@ ADDING files: " ^ String.concat ", " to_be_added);
61 let newout = MatitaFilesystem.add_files u to_be_added in
64 | MatitaFilesystem.SvnError outstr ->
65 prerr_endline ("ADD OF " ^ u ^ "FAILED:" ^ outstr);
69 (* now we update the local copy (to merge updates from other users) *)
71 let files,anomalies,(added,conflict,del,upd,merged) =
72 MatitaFilesystem.update_user u
74 let anomalies = String.concat "\n" anomalies in
75 let details = Printf.sprintf
77 "%d deleted files\n"^^
78 "%d updated files\n"^^
80 "%d conflicting files\n\n" ^^
81 "Anomalies:\n%s") added del upd merged conflict anomalies
83 prerr_endline ("update details:\n" ^ details);
84 MatitaAuthentication.set_file_flag u files;
87 | MatitaFilesystem.SvnError outstr ->
88 prerr_endline ("UPDATE OF " ^ u ^ "FAILED:" ^ outstr);
92 (* we re-read the file table after updating *)
93 let ft = MatitaAuthentication.read_ft u in
95 (* finally we perform the real commit *)
96 let modified = (List.map fst
97 (List.filter (fun (_,flag) -> flag = MatitaFilesystem.MModified) ft))
99 let to_be_committed = to_be_added @ modified
102 let newout = MatitaFilesystem.commit u to_be_committed in
105 | MatitaFilesystem.SvnError outstr ->
106 prerr_endline ("COMMIT OF " ^ u ^ "FAILED:" ^ outstr);
110 (* call stat to get the final status *)
111 let files, anomalies = MatitaFilesystem.stat_user u in
112 let added,not_added = List.fold_left
113 (fun (a_acc, na_acc) fname ->
114 if List.mem fname (List.map fst files) then
117 fname::a_acc, na_acc)
120 let committed,not_committed = List.fold_left
121 (fun (c_acc, nc_acc) fname ->
122 if List.mem fname (List.map fst files) then
125 fname::c_acc, nc_acc)
128 let conflicts = List.map fst (List.filter
129 (fun (_,f) -> f = Some MatitaFilesystem.MConflict) files)
131 MatitaAuthentication.set_file_flag u
132 (List.map (fun x -> x, Some MatitaFilesystem.MSynchronized) (added@committed));
133 MatitaAuthentication.set_file_flag u files;
134 out ^ "\n\n" ^ (Printf.sprintf
135 ("COMMIT RESULTS for %s\n" ^^
136 "==============\n" ^^
137 "added and committed (%d of %d): %s\n" ^^
138 "modified and committed (%d of %d): %s\n" ^^
140 "not committed: %s\n" ^^
142 u (List.length added) (List.length to_be_added) (String.concat ", " added)
143 (List.length committed) (List.length modified) (String.concat ", " committed)
144 (String.concat ", " not_added)
145 (String.concat ", " not_committed) (String.concat ", " conflicts)))
147 (* XXX: at the moment, we don't keep track of the order in which users have
148 scheduled their commits, but we should, otherwise we will get a
149 "first come, random served" policy *)
150 "" (* (List.rev !to_be_committed) *)
151 (* replace [uid] to commit all users:
152 (MatitaAuthentication.get_users ())
157 (*** from matitaScript.ml ***)
158 (* let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$" *)
160 let eval_statement include_paths (* (buffer : GText.buffer) *) status (* script *)
163 let ast,unparsed_text =
166 (* if Pcre.pmatch ~rex:only_dust_RE text then raise Margin; *)
167 prerr_endline ("raw text = " ^ text);
169 GrafiteParser.parsable_statement status
170 (Ulexing.from_utf8_string text) in
171 prerr_endline "before get_ast";
172 let ast = MatitaEngine.get_ast status include_paths strm in
173 prerr_endline "after get_ast";
175 | `Ast (st, text) -> st, text
178 (* do we want to generate a trace? *)
180 not (List.mem_assoc "demod" a || List.mem_assoc "paramod" a ||
181 List.mem_assoc "fast_paramod" a || List.assoc "depth" a = "1" ||
185 let get_param a param =
187 Some (param ^ "=" ^ List.assoc param a)
188 with Not_found -> None
191 let floc = match ast with
192 | GrafiteAst.Executable (loc, _)
193 | GrafiteAst.Comment (loc, _) -> loc in
195 let lstart,lend = HExtlib.loc_of_floc floc in
196 let parsed_text, _parsed_text_len =
197 HExtlib.utf8_parsed_text unparsed_text (HExtlib.floc_of_loc (0,lend)) in
198 let parsed_text_len = utf8_length parsed_text in
199 let byte_parsed_text_len = String.length parsed_text in
201 String.sub unparsed_text byte_parsed_text_len
202 (String.length unparsed_text - byte_parsed_text_len)
204 prerr_endline (Printf.sprintf "ustring_sub caso 1: lstart=%d, parsed=%s" lstart parsed_text);
205 let pre = Netconversion.ustring_sub `Enc_utf8 0 lstart parsed_text in
209 Printf.sprintf "\005A href=\"%s\"\006%s\005/A\006"
210 (NReference.string_of_reference r) (NCicPp.r2s status true r)
212 (*if trace = [] then "{}"
213 else*) String.concat ", "
214 (HExtlib.filter_map (function
215 | NotationPt.NRef r -> Some (href r)
221 | GrafiteAst.Executable (_,
222 GrafiteAst.NCommand (_,
223 GrafiteAst.NObj (loc, astobj,_))) ->
224 let objname = NotationPt.name_of_obj astobj in
226 MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
228 let new_parsed_text = Ulexing.from_utf8_string parsed_text in
229 let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
230 let outstr = ref "" in
231 ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
232 let x, y = HExtlib.loc_of_floc floc in
233 let pre = Netconversion.ustring_sub `Enc_utf8 0 x !outstr in
234 let post = Netconversion.ustring_sub `Enc_utf8 x
235 (Netconversion.ustring_length `Enc_utf8 !outstr - x) !outstr in
236 outstr := Printf.sprintf
237 "%s\005img class=\"anchor\" src=\"icons/tick.png\" id=\"%s\" /\006%s" pre objname post;
238 prerr_endline ("baseuri after advance = " ^ status#baseuri);
239 (* prerr_endline ("parser output: " ^ !outstr); *)
240 (status,!outstr, unparsed_txt'),parsed_text_len
241 | GrafiteAst.Executable (_,
242 GrafiteAst.NTactic (_,
243 [GrafiteAst.NAuto (_, (l,a as auto_params))])) when is_auto auto_params
247 | Some (_,l') -> Some (List.map (fun x -> "",0,x) l')
249 let trace_ref = ref [] in
250 let status = NnAuto.auto_tac ~params:(l,a) ~trace_ref status in
251 let new_parsed_text = pre ^ (Printf.sprintf
252 "/\005span class='autotactic'\006%s\005span class='autotrace'\006 trace %s\005/span\006\005/span\006/"
254 (List.assoc "depth" a::
255 HExtlib.filter_map (get_param a) ["width";"size"]))
256 (mk_univ !trace_ref))
258 (status,new_parsed_text, unparsed_txt'),parsed_text_len
261 MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:false status ("",0,ast)
263 let new_parsed_text = Ulexing.from_utf8_string parsed_text in
264 let interpr = GrafiteDisambiguate.get_interpr status#disambiguate_db in
265 let outstr = ref "" in
266 ignore (SmallLexer.mk_small_printer interpr outstr new_parsed_text);
267 prerr_endline ("baseuri after advance = " ^ status#baseuri);
268 (* prerr_endline ("parser output: " ^ !outstr); *)
269 (status,!outstr, unparsed_txt'),parsed_text_len
271 (*let save_moo status =
272 let script = MatitaScript.current () in
273 let baseuri = status#baseuri in
274 match script#bos, script#eos with
277 GrafiteTypes.Serializer.serialize ~baseuri:(NUri.uri_of_string baseuri)
279 | _ -> clean_current_baseuri status
282 let sequent_size = ref 40;;
284 let include_paths = ref [];;
287 * <meta number="...">
288 * <metaname>...</metaname>
294 let output_status s =
295 let _,_,metasenv,subst,_ = s#obj in
296 let render_switch = function
297 | Stack.Open i -> "?" ^ (string_of_int i)
298 | Stack.Closed i -> "<S>?" ^ (string_of_int i) ^ "</S>"
300 let int_of_switch = function
301 | Stack.Open i | Stack.Closed i -> i
303 let sequent = function
305 let meta = List.assoc i metasenv in
306 snd (ApplyTransformation.ntxt_of_cic_sequent
307 ~metasenv ~subst ~map_unicode_to_tex:false !sequent_size s (i,meta))
308 | Stack.Closed _ -> "This goal has already been closed."
310 let render_sequent is_loc acc depth tag (pos,sw) =
311 let metano = int_of_switch sw in
314 (match depth, pos with
315 | 0, 0 -> "<span class=\"activegoal\">" ^ (render_switch sw) ^ "</span>"
317 Printf.sprintf "<span class=\"activegoal\">|<SUB>%d</SUB>: %s</span>" pos (render_switch sw)
318 | 1, pos when Stack.head_tag s#stack = `BranchTag ->
319 Printf.sprintf "<span class=\"passivegoal\">|<SUB>%d</SUB> : %s</span>" pos (render_switch sw)
320 | _ -> render_switch sw)
321 else render_switch sw
324 Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () markup in
325 let markup = "<metaname>" ^ markup ^ "</metaname>" in
327 Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () (sequent sw)
329 let txt0 = "<goal>" ^ sequent ^ "</goal>" in
330 "<meta number=\"" ^ (string_of_int metano) ^ "\">" ^ markup ^
331 txt0 ^ "</meta>" ^ acc
335 ~env:(render_sequent true) ~cont:(render_sequent false)
336 ~todo:(render_sequent false) "" s#stack) ^
338 (* prerr_endline ("sending metasenv:\n" ^ res); res *)
341 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*";;
344 let s = Pcre.replace ~rex:heading_nl_RE s in
346 let nl_pos = String.index s '\n' in
347 String.sub s 0 nl_pos
351 let read_file fname =
352 let chan = open_in fname in
353 let lines = ref [] in
356 lines := input_line chan :: !lines
358 with End_of_file -> close_in chan);
359 String.concat "\n" (List.rev !lines)
362 let load_index outchan =
363 let s = read_file "index.html" in
364 Http_daemon.respond ~headers:["Content-Type", "text/html"] ~code:(`Code 200) ~body:s outchan
367 let load_doc filename outchan =
368 let s = read_file filename in
370 try String.sub filename (String.length filename - 4) 4 = ".png"
371 with Invalid_argument _ -> false
373 let contenttype = if is_png then "image/png" else "text/html" in
374 Http_daemon.respond ~headers:["Content-Type", contenttype] ~code:(`Code 200) ~body:s outchan
377 let retrieve (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
378 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
379 let env = cgi#environment in
381 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
382 let sid = HExtlib.unopt sid in
383 let uid = MatitaAuthentication.user_of_session sid in
387 ~content_type:"text/xml; charset=\"utf-8\""
390 let readonly = cgi # argument_value "readonly" in
391 let filename = libdir uid ^ "/" ^ (cgi # argument_value "file") in
392 (* prerr_endline ("reading file " ^ filename); *)
394 Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false ()
395 (html_of_matita (read_file filename)) in
397 (* html_of_matita (read_file filename) in *)
398 (* prerr_endline ("sending:\nBEGIN\n" ^ body ^ "\nEND"); *)
399 let body = "<response><file>" ^ body ^ "</file></response>" in
400 let baseuri, incpaths =
402 let root, baseuri, _fname, _tgt =
403 Librarian.baseuri_of_script ~include_paths:[] filename in
406 Str.split (Str.regexp " ")
407 (List.assoc "include_paths" (Librarian.load_root_file (root^"/root")))
410 let rc = root :: includes in
411 List.iter (HLog.debug) rc; baseuri, rc
413 Librarian.NoRootFor _ | Librarian.FileNotFound _ -> "",[] in
414 include_paths := incpaths;
415 if readonly <> "true" then
416 (let status = new MatitaEngine.status (Some uid) baseuri in
417 let history = [status] in
418 MatitaAuthentication.set_status sid status;
419 MatitaAuthentication.set_history sid history);
422 ~content_type:"text/xml; charset=\"utf-8\""
424 cgi#out_channel#output_string body;
429 ~content_type:"text/xml; charset=\"utf-8\""
431 cgi#out_channel#output_string "<error />"
434 ~status:`Internal_server_error
436 ~content_type:"text/html; charset=\"utf-8\""
438 cgi#out_channel#commit_work()
441 let xml_of_disamb_error l =
442 let mk_alias = function
443 | GrafiteAst.Ident_alias (_,uri) -> "href=\"" ^ uri ^ "\""
444 | GrafiteAst.Symbol_alias (_,uri,desc)
445 | GrafiteAst.Number_alias (uri,desc) ->
446 let uri = try HExtlib.unopt uri with _ -> "cic:/fakeuri.def(1)" in
447 "href=\"" ^ uri ^ "\" title=\"" ^
448 (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
452 let mk_interpr (loc,a) =
453 let x,y = HExtlib.loc_of_floc loc in
454 Printf.sprintf "<interpretation start=\"%d\" stop=\"%d\" %s />"
458 let mk_failure (il,loc,msg) =
459 let x,y = HExtlib.loc_of_floc loc in
460 Printf.sprintf "<failure start=\"%d\" stop=\"%d\" title=\"%s\">%s</failure>"
461 x y (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () msg)
462 (String.concat "" (List.map mk_interpr il))
465 let mk_choice (a,fl) =
466 let fl' = String.concat "" (List.map mk_failure fl) in
468 | None -> "<choice>" ^ fl' ^ "</choice>"
469 | Some a -> Printf.sprintf "<choice %s>%s</choice>" (mk_alias a) fl'
472 let mk_located (loc,cl) =
473 let x,y = HExtlib.loc_of_floc loc in
474 Printf.sprintf "<choicepoint start=\"%d\" stop=\"%d\">%s</choicepoint>"
475 x y (String.concat "" (List.map mk_choice cl))
477 "<disamberror>" ^ (String.concat "" (List.map mk_located l)) ^ "</disamberror>"
480 let advance0 sid text =
481 let status = MatitaAuthentication.get_status sid in
482 let history = MatitaAuthentication.get_history sid in
483 let status = status#reset_disambiguate_db () in
484 let (st,new_statements,new_unparsed),parsed_len =
485 let rec do_exc = function
486 | MatitaEngine.EnrichedWithStatus (e,_) -> do_exc e
487 | NCicTypeChecker.TypeCheckerFailure s -> raise (Generic_error (Lazy.force s))
488 | HExtlib.Localized (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 *)
497 pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\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 | Disambiguate.NoWellTypedInterpretation (floc,e) ->
502 let x, y = HExtlib.loc_of_floc floc in
503 let pre = Netconversion.ustring_sub `Enc_utf8 0 x text in
504 let err = Netconversion.ustring_sub `Enc_utf8 x (y-x) text in
505 let post = Netconversion.ustring_sub `Enc_utf8 y
506 (Netconversion.ustring_length `Enc_utf8 text - y) text in
507 (*let _,title = MatitaExcPp.to_string e in*)
508 (* let title = "" in *)
510 pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
511 let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false
512 () (html_of_matita marked) in
513 raise (Emphasized_error marked)
514 | NCicRefiner.Uncertain m as exn ->
515 let floc, e = Lazy.force m in
516 let x, y = HExtlib.loc_of_floc floc in
517 let pre = Netconversion.ustring_sub `Enc_utf8 0 x text in
518 let err = Netconversion.ustring_sub `Enc_utf8 x (y-x) text in
519 let post = Netconversion.ustring_sub `Enc_utf8 y
520 (Netconversion.ustring_length `Enc_utf8 text - y) text in
521 (* let _,title = MatitaExcPp.to_string e in *)
522 (* let title = "" in *)
524 pre ^ "\005span class=\"error\" title=\"" ^ e ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
525 let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false
526 () (html_of_matita marked) in
527 raise (Emphasized_error marked)
528 | NTacStatus.Error (s,None) as e ->
530 ("NTacStatus.Error " ^ (Lazy.force s)); raise e
531 | NTacStatus.Error (s,Some exc) as e ->
533 ("NTacStatus.Error " ^ Lazy.force s ^ " -- " ^ (Printexc.to_string exc));
535 | GrafiteDisambiguate.Ambiguous_input (loc,choices) ->
536 let x,y = HExtlib.loc_of_floc loc in
537 let choice_of_alias = function
538 | GrafiteAst.Ident_alias (_,uri) -> uri, None, uri
539 | GrafiteAst.Number_alias (None,desc)
540 | GrafiteAst.Symbol_alias (_,None,desc) -> "cic:/fakeuri.def(1)", Some desc, desc
541 | GrafiteAst.Number_alias (Some uri,desc)
542 | GrafiteAst.Symbol_alias (_,Some uri,desc) -> uri, Some desc, desc
544 let tag_of_choice (uri,title,desc) =
546 | None -> Printf.sprintf "<choice href=\"%s\">%s</choice>"
548 (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
549 | Some t -> Printf.sprintf "<choice href=\"%s\" title=\"%s\">%s</choice>"
551 (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () t)
552 (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () desc)
556 (List.map (fun x -> tag_of_choice (choice_of_alias x)) choices)
558 prerr_endline (Printf.sprintf
559 "@@@ Ambiguous input at (%d,%d). Possible choices:\n\n%s\n\n@@@ End."
562 let pre = Netconversion.ustring_sub `Enc_utf8 0 x text in
563 let err = Netconversion.ustring_sub `Enc_utf8 x (y-x) text in
564 let post = Netconversion.ustring_sub `Enc_utf8 y
565 (Netconversion.ustring_length `Enc_utf8 text - y) text in
566 let title = "Disambiguation Error" in
567 (* let title = "" in *)
569 pre ^ "\005span class=\"error\" title=\"" ^ title ^ "\"\006" ^ err ^ "\005/span\006" ^ post in
570 let marked = Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false
571 () (html_of_matita marked) in
573 let strchoices = Printf.sprintf
574 "<ambiguity start=\"%d\" stop=\"%d\">%s</ambiguity>" x y strchoices
575 in raise (Disamb_error strchoices)
576 | GrafiteDisambiguate.Error l -> raise (Disamb_error (xml_of_disamb_error l))
577 (* | End_of_file -> ... *)
579 (* prerr_endline ("matitadaemon *** Unhandled exception " ^ Printexc.to_string e); *)
580 prerr_endline ("matitadaemon *** Unhandled exception " ^ snd (MatitaExcPp.to_string e));
585 eval_statement !include_paths (*buffer*) status (`Raw text)
588 debug "BEGIN PRINTGRAMMAR";
589 (*prerr_endline (Print_grammar.ebnf_of_term status);*)
590 (*let kwds = String.concat ", " status#get_kwds in
591 debug ("keywords = " ^ kwds );*)
592 debug "END PRINTGRAMMAR";
593 MatitaAuthentication.set_status sid st;
594 MatitaAuthentication.set_history sid (st::history);
595 (* prerr_endline "previous timestamp";
596 status#print_timestamp();
597 prerr_endline "current timestamp";
598 st#print_timestamp(); *)
600 Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false
601 () (html_of_matita new_statements), new_unparsed, st
603 let register (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
604 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
605 let _env = cgi#environment in
607 assert (cgi#arguments <> []);
608 let uid = cgi#argument_value "userid" in
609 let userpw = cgi#argument_value "password" in
611 (* currently registering only unprivileged users *)
612 MatitaAuthentication.add_user uid userpw false;
613 (* env#set_output_header_field "Location" "/index.html" *)
614 cgi#out_channel#output_string
615 ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/login.html\">"
616 ^ "</head><body>Redirecting to login page...</body></html>")
618 | MatitaAuthentication.UsernameCollision _ ->
621 ~content_type:"text/html; charset=\"utf-8\""
623 cgi#out_channel#output_string
624 "<html><head></head><body>Error: User id collision!</body></html>"
625 | MatitaFilesystem.SvnError msg ->
628 ~content_type:"text/html; charset=\"utf-8\""
630 cgi#out_channel#output_string
631 ("<html><head></head><body><p>Error: Svn checkout failed!<p><p><textarea>"
632 ^ msg ^ "</textarea></p></body></html>"));
633 cgi#out_channel#commit_work()
636 let login (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
637 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
638 let env = cgi#environment in
640 assert (cgi#arguments <> []);
641 let uid = cgi#argument_value "userid" in
642 let userpw = cgi#argument_value "password" in
644 MatitaAuthentication.check_pw uid userpw;
645 NCicLibrary.init (Some uid);
646 let ft = MatitaAuthentication.read_ft uid in
647 let _ = MatitaFilesystem.html_of_library uid ft in
648 let sid = MatitaAuthentication.create_session uid in
649 (* let cookie = Netcgi.Cookie.make "session" (Uuidm.to_string sid) in
650 cgi#set_header ~set_cookies:[cookie] (); *)
651 env#set_output_header_field
652 "Set-Cookie" ("session=" ^ (Uuidm.to_string sid));
653 (* env#set_output_header_field "Location" "/index.html" *)
654 cgi#out_channel#output_string
655 ("<html><head><meta http-equiv=\"refresh\" content=\"2;url=/index.html\">"
656 ^ "</head><body>Redirecting to Matita page...</body></html>")
657 with MatitaAuthentication.InvalidPassword ->
660 ~content_type:"text/html; charset=\"utf-8\""
662 cgi#out_channel#output_string
663 "<html><head></head><body>Authentication error</body></html>");
664 cgi#out_channel#commit_work()
667 let logout (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
668 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
669 let env = cgi#environment in
671 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
672 let sid = HExtlib.unopt sid in
673 MatitaAuthentication.logout_user sid;
676 ~content_type:"text/html; charset=\"utf-8\""
678 let text = read_file (rt_path () ^ "/logout.html") in
679 cgi#out_channel#output_string text
683 ~status:`Internal_server_error
685 ~content_type:"text/html; charset=\"utf-8\""
687 cgi#out_channel#commit_work()
690 exception File_already_exists;;
692 let save (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
693 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
694 let env = cgi#environment in
696 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
697 let sid = HExtlib.unopt sid in
698 let status = MatitaAuthentication.get_status sid in
699 let uid = MatitaAuthentication.user_of_session sid in
700 assert (cgi#arguments <> []);
701 let locked = cgi#argument_value "locked" in
702 let unlocked = cgi#argument_value "unlocked" in
703 let dir = cgi#argument_value "dir" in
704 let rel_filename = cgi # argument_value "file" in
705 let filename = libdir uid ^ "/" ^ rel_filename in
706 let force = bool_of_string (cgi#argument_value "force") in
707 let already_exists = Sys.file_exists filename in
709 if ((not force) && already_exists) then
710 raise File_already_exists;
713 Unix.mkdir filename 0o744
716 let oc = open_out filename in
717 output_string oc (locked ^ unlocked);
719 if MatitaEngine.eos status unlocked then
721 (* prerr_endline ("serializing proof objects..."); *)
722 GrafiteTypes.Serializer.serialize
723 ~baseuri:(NUri.uri_of_string status#baseuri) status;
724 (* prerr_endline ("done."); *)
729 List.assoc rel_filename (MatitaAuthentication.read_ft uid)
730 with Not_found -> MatitaFilesystem.MUnversioned
732 (if old_flag <> MatitaFilesystem.MConflict &&
733 old_flag <> MatitaFilesystem.MAdd then
735 if already_exists then MatitaFilesystem.MModified
736 else MatitaFilesystem.MAdd
738 MatitaAuthentication.set_file_flag uid [rel_filename, Some newflag]);
741 ~content_type:"text/xml; charset=\"utf-8\""
743 cgi#out_channel#output_string "<response>ok</response>"
745 | File_already_exists ->
748 ~content_type:"text/xml; charset=\"utf-8\""
750 cgi#out_channel#output_string "<response>cancelled</response>"
753 ~status:`Internal_server_error
755 ~content_type:"text/xml; charset=\"utf-8\""
760 ~content_type:"text/xml; charset=\"utf-8\""
762 let estr = Printexc.to_string e in
763 cgi#out_channel#output_string ("<response>" ^ estr ^ "</response>"));
764 cgi#out_channel#commit_work()
767 let initiate_commit (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
768 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
769 let env = cgi#environment in
771 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
772 let sid = HExtlib.unopt sid in
773 MatitaAuthentication.probe_commit_priv sid;
774 let uid = MatitaAuthentication.user_of_session sid in
775 let out = do_global_commit (* () *) uid in
778 ~content_type:"text/xml; charset=\"utf-8\""
780 cgi#out_channel#output_string "<commit>";
781 cgi#out_channel#output_string "<response>ok</response>";
782 cgi#out_channel#output_string ("<details>" ^ out ^ "</details>");
783 cgi#out_channel#output_string "</commit>"
788 ~content_type:"text/xml; charset=\"utf-8\""
790 cgi#out_channel#output_string
791 "<commit><error>no commit privileges</error></commit>"
794 ~status:`Internal_server_error
796 ~content_type:"text/xml; charset=\"utf-8\""
798 cgi#out_channel#commit_work()
801 let svn_update (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
802 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
803 let env = cgi#environment in
804 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
805 let sid = HExtlib.unopt sid in
806 let uid = MatitaAuthentication.user_of_session sid in
808 MatitaAuthentication.probe_commit_priv sid;
809 let files,anomalies,(added,conflict,del,upd,merged) =
810 MatitaFilesystem.update_user uid
812 let anomalies = String.concat "\n" anomalies in
813 let details = Printf.sprintf
815 "%d deleted files\n"^^
816 "%d updated files\n"^^
817 "%d merged files\n"^^
818 "%d conflicting files\n\n" ^^
819 "Anomalies:\n%s") added del upd merged conflict anomalies
821 prerr_endline ("update details:\n" ^ details);
823 Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false () details
825 MatitaAuthentication.set_file_flag uid files;
828 ~content_type:"text/xml; charset=\"utf-8\""
830 cgi#out_channel#output_string "<update>";
831 cgi#out_channel#output_string "<response>ok</response>";
832 cgi#out_channel#output_string ("<details>" ^ details ^ "</details>");
833 cgi#out_channel#output_string "</update>";
838 ~content_type:"text/xml; charset=\"utf-8\""
840 cgi#out_channel#output_string
841 "<commit><error>no commit privileges</error></commit>"
844 ~status:`Internal_server_error
846 ~content_type:"text/xml; charset=\"utf-8\""
848 cgi#out_channel#commit_work()
851 (* returns the length of the executed text and an html representation of the
854 let advance (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
855 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
856 let env = cgi#environment in
858 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
859 let sid = HExtlib.unopt sid in
863 ~content_type:"text/xml; charset=\"utf-8\""
866 let text = cgi#argument_value "body" in
867 (* prerr_endline ("body =\n" ^ text); *)
868 let parsed_len, new_parsed, new_unparsed, new_status = advance0 sid text in
869 let txt = output_status new_status in
871 "<response><parsed length=\"" ^ (string_of_int parsed_len) ^ "\">" ^
872 new_parsed ^ "</parsed>" ^ txt
875 (* prerr_endline ("sending advance response:\n" ^ body); *)
878 ~content_type:"text/xml; charset=\"utf-8\""
880 cgi#out_channel#output_string body
882 | Generic_error text ->
883 let body = "<response><error>" ^ text ^ "</error></response>" in
886 ~content_type:"text/xml; charset=\"utf-8\""
888 cgi#out_channel#output_string body
889 | Emphasized_error text ->
890 (* | MultiPassDisambiguator.DisambiguationError (offset,errorll) -> *)
891 let body = "<response><localized>" ^ text ^ "</localized></response>" in
894 ~content_type:"text/xml; charset=\"utf-8\""
896 cgi#out_channel#output_string body
897 | Disamb_error text ->
898 let body = "<response>" ^ text ^ "</response>" in
901 ~content_type:"text/xml; charset=\"utf-8\""
903 cgi#out_channel#output_string body
905 let body = "<response><parsed length=\"0\"></parsed></response>" in
908 ~content_type:"text/xml; charset=\"utf-8\""
910 cgi#out_channel#output_string body
913 ~status:`Internal_server_error
915 ~content_type:"text/xml; charset=\"utf-8\""
918 cgi#out_channel#commit_work()
921 let gotoBottom (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
922 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
923 let env = cgi#environment in
925 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
926 let sid = HExtlib.unopt sid in
928 let error_msg = function
929 | Emphasized_error text -> "<localized>" ^ text ^ "</localized>"
930 | Disamb_error text -> text
931 | End_of_file _ -> (* not an error *) ""
932 | e -> (* unmanaged error *)
934 (Netencoding.Html.encode ~in_enc:`Enc_utf8 ~prefer_name:false ()
935 (Printexc.to_string e)) ^ "</error>"
938 let rec aux acc text =
940 prerr_endline ("evaluating: " ^ first_line text);
941 let plen,new_parsed,new_unparsed,_new_status = advance0 sid text in
942 aux ((plen,new_parsed)::acc) new_unparsed
943 with e -> acc, error_msg e
944 (* DON'T SERIALIZE NOW!!!
945 let status = MatitaAuthentication.get_status sid in
946 GrafiteTypes.Serializer.serialize
947 ~baseuri:(NUri.uri_of_string status#baseuri) status;
953 ~content_type:"text/xml; charset=\"utf-8\""
956 let text = cgi#argument_value "body" in
957 (* prerr_endline ("body =\n" ^ text); *)
958 let len_parsedlist, err_msg = aux [] text in
959 let status = MatitaAuthentication.get_status sid in
960 let txt = output_status status in
961 let parsed_tag (len,txt) =
962 "<parsed length=\"" ^ (string_of_int len) ^ "\">" ^ txt ^ "</parsed>"
964 (* List.rev: the list begins with the older parsed txt *)
967 String.concat "" (List.rev (List.map parsed_tag len_parsedlist)) ^
968 txt ^ err_msg ^ "</response>"
970 (* prerr_endline ("sending goto bottom response:\n" ^ body); *)
973 ~content_type:"text/xml; charset=\"utf-8\""
975 cgi#out_channel#output_string body;
976 (* with Not_found -> cgi#set_header ~status:`Internal_server_error
978 ~content_type:"text/xml; charset=\"utf-8\"" ()); *)
979 cgi#out_channel#commit_work()
982 let gotoTop (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
983 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
984 let env = cgi#environment in
985 prerr_endline "executing goto Top";
987 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
988 let sid = HExtlib.unopt sid in
992 ~content_type:"text/xml; charset=\"utf-8\""
995 let status = MatitaAuthentication.get_status sid in
996 let uid = MatitaAuthentication.user_of_session sid in
997 let baseuri = status#baseuri in
998 let new_status = new MatitaEngine.status (Some uid) baseuri in
999 prerr_endline "gototop prima della time travel";
1000 (* NCicLibrary.time_travel new_status; *)
1001 prerr_endline "gototop dopo della time travel";
1002 let new_history = [new_status] in
1003 MatitaAuthentication.set_history sid new_history;
1004 MatitaAuthentication.set_status sid new_status;
1005 (* NCicLibrary.time_travel new_status; *)
1008 ~content_type:"text/xml; charset=\"utf-8\""
1010 cgi#out_channel#output_string "<response>ok</response>"
1012 (cgi#set_header ~status:`Internal_server_error
1014 ~content_type:"text/xml; charset=\"utf-8\"" ();
1015 cgi#out_channel#output_string "<response>ok</response>"));
1016 cgi#out_channel#commit_work()
1019 let retract (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1020 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1021 let env = cgi#environment in
1023 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
1024 let sid = HExtlib.unopt sid in
1028 ~content_type:"text/xml; charset=\"utf-8\""
1031 let history = MatitaAuthentication.get_history sid in
1032 let old_status = MatitaAuthentication.get_status sid in
1033 let new_history,new_status =
1035 _::(status::_ as history) ->
1037 | [_] -> (prerr_endline "singleton";failwith "retract")
1038 | _ -> (prerr_endline "nil"; assert false) in
1039 (* prerr_endline "timestamp prima della retract";
1040 old_status#print_timestamp ();
1041 prerr_endline "timestamp della retract";
1042 new_status#print_timestamp ();
1043 prerr_endline ("prima della time travel"); *)
1044 NCicLibrary.time_travel new_status;
1045 prerr_endline ("dopo della time travel");
1046 MatitaAuthentication.set_history sid new_history;
1047 MatitaAuthentication.set_status sid new_status;
1048 prerr_endline ("baseuri after retract = " ^ new_status#baseuri);
1049 let body = output_status new_status in
1052 ~content_type:"text/xml; charset=\"utf-8\""
1054 cgi#out_channel#output_string body
1056 prerr_endline ("error in retract: " ^ Printexc.to_string e);
1057 cgi#set_header ~status:`Internal_server_error
1059 ~content_type:"text/xml; charset=\"utf-8\"" ());
1060 cgi#out_channel#commit_work()
1064 let viewLib (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1065 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1066 let env = cgi#environment in
1068 let sid = Uuidm.of_string (Netcgi.Cookie.value (env#cookie "session")) in
1069 let sid = HExtlib.unopt sid in
1073 ~content_type:"text/html; charset=\"utf-8\""
1076 let uid = MatitaAuthentication.user_of_session sid in
1078 let ft = MatitaAuthentication.read_ft uid in
1079 let html = MatitaFilesystem.html_of_library uid ft in
1082 ~content_type:"text/html; charset=\"utf-8\""
1084 cgi#out_channel#output_string
1087 "<title>XML Tree Control</title>\n" ^
1088 "<link href=\"treeview/xmlTree.css\" type=\"text/css\" rel=\"stylesheet\">\n" ^
1089 "<script src=\"treeview/xmlTree.js\" type=\"text/javascript\"></script>\n" ^
1091 html (* ^ "\n</body></html>" *) );
1093 let files,anomalies = MatitaFilesystem.stat_user uid in
1094 let changed = HExtlib.filter_map
1095 (fun (n,f) -> if (f = Some MatitaFilesystem.MModified) then Some n else None) files
1097 let changed = String.concat "\n" changed in
1098 let anomalies = String.concat "\n" anomalies in
1099 prerr_endline ("Changed:\n" ^ changed ^ "\n\nAnomalies:\n" ^ anomalies);
1100 cgi#out_channel#commit_work()
1104 let resetLib (cgi : Netcgi1_compat.Netcgi_types.cgi_activation) =
1105 let cgi = Netcgi1_compat.Netcgi_types.of_compat_activation cgi in
1106 MatitaAuthentication.reset ();
1109 ~content_type:"text/html; charset=\"utf-8\""
1112 cgi#out_channel#output_string
1114 "<title>Matitaweb Reset</title>\n" ^
1115 "<body><H1>Reset completed</H1></body></html>");
1116 cgi#out_channel#commit_work()
1118 open Netcgi1_compat.Netcgi_types;;
1120 (**********************************************************************)
1121 (* Create the webserver *)
1122 (**********************************************************************)
1126 let (opt_list, cmdline_cfg) = Netplex_main.args() in
1128 let use_mt = ref true in
1131 [ "-mt", Arg.Set use_mt,
1132 " Use multi-threading instead of multi-processing"
1137 (fun s -> raise (Arg.Bad ("Don't know what to do with: " ^ s)))
1138 "usage: netplex [options]";
1141 Netplex_mt.mt() (* multi-threading *)
1143 Netplex_mp.mp() in (* multi-processing *)
1146 { Nethttpd_services.dyn_handler = (fun _ -> process1);
1147 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1148 dyn_uri = None; (* not needed *)
1149 dyn_translator = (fun _ -> ""); (* not needed *)
1150 dyn_accept_all_conditionals = false;
1154 { Nethttpd_services.dyn_handler = (fun _ -> advance);
1155 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1156 dyn_uri = None; (* not needed *)
1157 dyn_translator = (fun _ -> ""); (* not needed *)
1158 dyn_accept_all_conditionals = false;
1161 { Nethttpd_services.dyn_handler = (fun _ -> retract);
1162 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1163 dyn_uri = None; (* not needed *)
1164 dyn_translator = (fun _ -> ""); (* not needed *)
1165 dyn_accept_all_conditionals = false;
1168 { Nethttpd_services.dyn_handler = (fun _ -> gotoBottom);
1169 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1170 dyn_uri = None; (* not needed *)
1171 dyn_translator = (fun _ -> ""); (* not needed *)
1172 dyn_accept_all_conditionals = false;
1175 { Nethttpd_services.dyn_handler = (fun _ -> gotoTop);
1176 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1177 dyn_uri = None; (* not needed *)
1178 dyn_translator = (fun _ -> ""); (* not needed *)
1179 dyn_accept_all_conditionals = false;
1182 { Nethttpd_services.dyn_handler = (fun _ -> retrieve);
1183 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1184 dyn_uri = None; (* not needed *)
1185 dyn_translator = (fun _ -> ""); (* not needed *)
1186 dyn_accept_all_conditionals = false;
1189 { Nethttpd_services.dyn_handler = (fun _ -> register);
1190 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1191 dyn_uri = None; (* not needed *)
1192 dyn_translator = (fun _ -> ""); (* not needed *)
1193 dyn_accept_all_conditionals = false;
1196 { Nethttpd_services.dyn_handler = (fun _ -> login);
1197 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1198 dyn_uri = None; (* not needed *)
1199 dyn_translator = (fun _ -> ""); (* not needed *)
1200 dyn_accept_all_conditionals = false;
1203 { Nethttpd_services.dyn_handler = (fun _ -> logout);
1204 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1205 dyn_uri = None; (* not needed *)
1206 dyn_translator = (fun _ -> ""); (* not needed *)
1207 dyn_accept_all_conditionals = false;
1210 { Nethttpd_services.dyn_handler = (fun _ -> viewLib);
1211 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1212 dyn_uri = None; (* not needed *)
1213 dyn_translator = (fun _ -> ""); (* not needed *)
1214 dyn_accept_all_conditionals = false;
1217 { Nethttpd_services.dyn_handler = (fun _ -> resetLib);
1218 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1219 dyn_uri = None; (* not needed *)
1220 dyn_translator = (fun _ -> ""); (* not needed *)
1221 dyn_accept_all_conditionals = false;
1224 { Nethttpd_services.dyn_handler = (fun _ -> save);
1225 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1226 dyn_uri = None; (* not needed *)
1227 dyn_translator = (fun _ -> ""); (* not needed *)
1228 dyn_accept_all_conditionals = false;
1231 { Nethttpd_services.dyn_handler = (fun _ -> initiate_commit);
1232 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1233 dyn_uri = None; (* not needed *)
1234 dyn_translator = (fun _ -> ""); (* not needed *)
1235 dyn_accept_all_conditionals = false;
1238 { Nethttpd_services.dyn_handler = (fun _ -> svn_update);
1239 dyn_activation = Nethttpd_services.std_activation `Std_activation_buffered;
1240 dyn_uri = None; (* not needed *)
1241 dyn_translator = (fun _ -> ""); (* not needed *)
1242 dyn_accept_all_conditionals = false;
1246 let nethttpd_factory =
1247 Nethttpd_plex.nethttpd_factory
1248 ~handlers:[ "advance", do_advance
1249 ; "retract", do_retract
1250 ; "bottom", goto_bottom
1253 ; "register", do_register
1255 ; "logout", do_logout
1256 ; "reset", do_resetlib
1257 ; "viewlib", do_viewlib
1259 ; "commit", do_commit
1260 ; "update", do_update]
1262 MatitaInit.initialize_all ();
1263 MatitaAuthentication.deserialize ();
1264 Netplex_main.startup
1266 Netplex_log.logger_factories (* allow all built-in logging styles *)
1267 Netplex_workload.workload_manager_factories (* ... all ways of workload management *)
1268 [ nethttpd_factory ] (* make this nethttpd available *)
1272 Sys.set_signal Sys.sigpipe Sys.Signal_ignore;