]> matita.cs.unibo.it Git - helm.git/blob - helm/http_getter/http_getter.ml
- added "/add_server" and "/remove_server" to dynamically adjust servers
[helm.git] / helm / http_getter / http_getter.ml
1 (*
2  * Copyright (C) 2003:
3  *    Stefano Zacchiroli <zack@cs.unibo.it>
4  *    for the HELM Team http://helm.cs.unibo.it/
5  *
6  *  This file is part of HELM, an Hypertextual, Electronic
7  *  Library of Mathematics, developed at the Computer Science
8  *  Department, University of Bologna, Italy.
9  *
10  *  HELM is free software; you can redistribute it and/or
11  *  modify it under the terms of the GNU General Public License
12  *  as published by the Free Software Foundation; either version 2
13  *  of the License, or (at your option) any later version.
14  *
15  *  HELM is distributed in the hope that it will be useful,
16  *  but WITHOUT ANY WARRANTY; without even the implied warranty of
17  *  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  *  GNU General Public License for more details.
19  *
20  *  You should have received a copy of the GNU General Public License
21  *  along with HELM; if not, write to the Free Software
22  *  Foundation, Inc., 59 Temple Place - Suite 330, Boston,
23  *  MA  02111-1307, USA.
24  *
25  *  For details, see the HELM World-Wide-Web page,
26  *  http://helm.cs.unibo.it/
27  *)
28
29 open Http_getter_common;;
30 open Http_getter_misc;;
31 open Http_getter_types;;
32 open Http_getter_debugger;;
33 open Printf;;
34
35   (* constants *)
36
37 let common_headers = [
38   "Cache-Control", "no-cache";
39   "Pragma", "no-cache";
40   "Expires", "0"
41 ]
42
43   (* HTTP queries argument parsing *)
44
45   (* parse encoding ("format" parameter), default is Enc_normal *)
46 let parse_enc (req: Http_types.request) =
47   try
48     (match req#param "format" with
49     | "normal" -> Enc_normal
50     | "gz" -> Enc_gzipped
51     | s -> raise (Http_getter_bad_request ("Invalid format: " ^ s)))
52   with Http_types.Param_not_found _ -> Enc_normal
53 ;;
54   (* parse "patch_dtd" parameter, default is true *)
55 let parse_patch (req: Http_types.request) =
56   try
57     (match req#param "patch_dtd" with
58     | s when String.lowercase s = "yes" -> true
59     | s when String.lowercase s = "no" -> false
60     | s -> raise (Http_getter_bad_request ("Invalid patch_dtd value: " ^ s)))
61   with Http_types.Param_not_found _ -> true
62 ;;
63   (* parse output format ("format" parameter), no default value *)
64 let parse_output_format (req: Http_types.request) =
65   match req#param "format" with
66   | s when String.lowercase s = "txt" -> Fmt_text
67   | s when String.lowercase s = "xml" -> Fmt_xml
68   | s -> raise (Http_getter_bad_request ("Invalid /ls format: " ^ s))
69 ;;
70   (* parse "baseuri" format for /ls method, no default value *)
71 let parse_ls_uri =
72   let parse_ls_RE = Pcre.regexp "^(\\w+):(.*)$" in
73   let trailing_slash_RE = Pcre.regexp "/+$" in
74   fun (req: Http_types.request) ->
75     let baseuri = req#param "baseuri" in
76     let subs =
77       Pcre.extract ~rex:parse_ls_RE
78         (Pcre.replace ~rex:trailing_slash_RE  baseuri)
79     in
80     match (subs.(1), subs.(2)) with
81     | "cic", uri -> Cic uri
82     | "theory", uri -> Theory uri
83     | _ -> raise (Http_getter_bad_request ("Invalid /ls baseuri: " ^ baseuri))
84 ;;
85
86   (* global maps, shared by all threads *)
87
88 let cic_map = new Http_getter_map.map Http_getter_env.cic_dbm in
89 let nuprl_map = new Http_getter_map.map Http_getter_env.nuprl_dbm in
90 let rdf_map = new Http_getter_map.map Http_getter_env.rdf_dbm in
91 let xsl_map = new Http_getter_map.map Http_getter_env.xsl_dbm in
92
93 let save_maps () =
94  cic_map#close; nuprl_map#close; rdf_map#close; xsl_map#close in
95 let map_of_uri = function
96   | uri when is_cic_uri uri -> cic_map
97   | uri when is_nuprl_uri uri -> nuprl_map
98   | uri when is_rdf_uri uri -> rdf_map
99   | uri when is_xsl_uri uri -> xsl_map
100   | uri -> raise (Http_getter_unresolvable_URI uri)
101 in
102 let resolve uri =
103   try
104     (map_of_uri uri)#resolve uri
105   with Http_getter_map.Key_not_found _ ->
106     raise (Http_getter_unresolvable_URI uri)
107 in
108 let register uri =
109   (* Warning: this fail if uri is already registered *)
110   (map_of_uri uri)#add uri
111 in
112 let return_all_foo_uris map doctype filter outchan =
113   (** return all URIs contained in 'map' which satisfy predicate 'filter'; URIs
114   are written in an XMLish format ('doctype' is the XML doctype) onto 'outchan'
115   *)
116   Http_daemon.send_basic_headers ~code:200 outchan;
117   Http_daemon.send_header "Content-Type" "text/xml" outchan;
118   Http_daemon.send_headers common_headers outchan;
119   Http_daemon.send_CRLF outchan;
120   output_string
121     outchan
122     (sprintf
123 "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>
124 <!DOCTYPE %s SYSTEM \"%s/getdtd?uri=%s.dtd\">
125
126 <%s>
127 "
128       doctype
129       Http_getter_env.my_own_url
130       doctype
131       doctype);
132   map#iter
133     (fun uri _ ->
134       if filter uri then
135         output_string outchan (sprintf "\t<uri value=\"%s\" />\n" uri));
136   output_string outchan (sprintf "</%s>\n" doctype)
137 in
138 let return_all_xml_uris = return_all_foo_uris cic_map "alluris" in
139 let return_all_rdf_uris = return_all_foo_uris rdf_map "allrdfuris" in
140 let return_ls =
141   let (++) (oldann, oldtypes, oldbody) (newann, newtypes, newbody) =
142     ((if newann   > oldann    then newann   else oldann),
143      (if newtypes > oldtypes  then newtypes else oldtypes),
144      (if newbody  > oldbody   then newbody  else oldbody))
145   in
146   let basepart_RE =
147     Pcre.regexp "^([^.]*\\.[^.]*)((\\.body)|(\\.types))?(\\.ann)?"
148   in
149   let (types_RE, types_ann_RE, body_RE, body_ann_RE) =
150     (Pcre.regexp "\\.types", Pcre.regexp "\\.types.ann",
151      Pcre.regexp "\\.body", Pcre.regexp "\\.body.ann")
152   in
153   let (slash_RE, til_slash_RE, no_slashes_RE) =
154     (Pcre.regexp "/", Pcre.regexp "^.*/", Pcre.regexp "^[^/]*$")
155   in
156   fun lsuri fmt outchan ->
157     let pat =
158       "^" ^
159       (match lsuri with Cic p -> ("cic:" ^ p) | Theory p -> ("theory:" ^ p))
160     in
161     let (dir_RE, obj_RE) =
162       (Pcre.regexp (pat ^ "/"), Pcre.regexp (pat ^ "(\\.|$)"))
163     in
164     let dirs = ref StringSet.empty in
165     let objs = Hashtbl.create 17 in
166     let store_dir d =
167       dirs := StringSet.add (List.hd (Pcre.split ~rex:slash_RE d)) !dirs
168     in
169     let store_obj o =
170       let basepart = Pcre.replace ~rex:basepart_RE ~templ:"$1" o in
171       let oldflags =
172         try
173           Hashtbl.find objs basepart
174         with Not_found -> (false, No, No) (* no ann, no types, no body *)
175       in
176       let newflags =
177         match o with
178         | s when Pcre.pmatch ~rex:types_RE s     -> (false, Yes, No)
179         | s when Pcre.pmatch ~rex:types_ann_RE s -> (true,  Ann, No)
180         | s when Pcre.pmatch ~rex:body_RE s      -> (false, No,  Yes)
181         | s when Pcre.pmatch ~rex:body_ann_RE s  -> (true,  No,  Ann)
182         | s -> (false, No, No)
183       in
184       Hashtbl.replace objs basepart (oldflags ++ newflags)
185     in
186     cic_map#iter  (* BLEARGH Dbm module lacks support for fold-like functions *)
187       (fun key _ ->
188         match key with
189         | uri when Pcre.pmatch ~rex:dir_RE uri ->  (* directory hit *)
190             let localpart = Pcre.replace ~rex:dir_RE uri in
191             if Pcre.pmatch ~rex:no_slashes_RE localpart then
192               store_obj localpart
193             else
194               store_dir localpart
195         | uri when Pcre.pmatch ~rex:obj_RE  uri ->  (* file hit *)
196             store_obj (Pcre.replace ~rex:til_slash_RE uri)
197         | uri -> () (* miss *));
198     match fmt with
199     | Fmt_text ->
200         let body =
201           (List.fold_left
202             (fun s d -> sprintf "%sdir, %s\n" s d) ""
203             (StringSet.elements !dirs)) ^
204           (Http_getter_misc.hashtbl_sorted_fold
205             (fun uri (annflag, typesflag, bodyflag) cont ->
206               sprintf "%sobject, %s, <%s,%s,%s>\n"
207                 cont uri (if annflag then "YES" else "NO")
208                 (string_of_ls_flag typesflag) (string_of_ls_flag bodyflag))
209             objs "")
210         in
211         Http_daemon.respond
212           ~headers:(("Content-Type", "text/plain") :: common_headers)
213           ~body outchan
214     | Fmt_xml ->
215         let body =
216           sprintf
217 "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>
218 <!DOCTYPE ls SYSTEM \"%s/getdtd?uri=ls.dtd\">
219
220 <ls>
221 %s
222 </ls>
223 "
224             Http_getter_env.my_own_url
225             ("\n" ^
226             (String.concat
227               "\n"
228               (List.map
229                 (fun d -> "<section>" ^ d ^ "</section>")
230                 (StringSet.elements !dirs))) ^ "\n" ^
231             (Http_getter_misc.hashtbl_sorted_fold
232               (fun uri (annflag, typesflag, bodyflag) cont ->
233                 sprintf
234 "%s<object name=\"%s\">
235 \t<ann value=\"%s\" />
236 \t<types value=\"%s\" />
237 \t<body value=\"%s\" />
238 </object>
239 "
240                   cont uri (if annflag then "YES" else "NO")
241                   (string_of_ls_flag typesflag)
242                   (string_of_ls_flag bodyflag))
243               objs ""))
244         in
245         Http_daemon.respond
246           ~headers:(("Content-Type", "text/xml") :: common_headers)
247           ~body outchan
248 in
249 let (index_line_sep_RE, index_sep_RE, trailing_types_RE,
250     heading_cic_RE, heading_theory_RE, heading_nuprl_RE,
251     heading_rdf_cic_RE, heading_rdf_theory_RE) =
252   (Pcre.regexp "[ \t]+", Pcre.regexp "\r\n|\r|\n",
253   Pcre.regexp "\\.types$",
254   Pcre.regexp "^cic:", Pcre.regexp "^theory:", Pcre.regexp "^nuprl:",
255   Pcre.regexp "^helm:rdf.*//cic:", Pcre.regexp "^helm:rdf.*//theory:")
256 in
257 let update_from_server logmsg server_url = (* use global maps *)
258   debug_print ("Updating information from " ^ server_url);
259   let xml_url_of_uri = function
260       (* TODO missing sanity checks on server_url, e.g. it can contains $1 *)
261     | uri when (Pcre.pmatch ~rex:heading_cic_RE uri) ->
262         Pcre.replace ~rex:heading_cic_RE ~templ:server_url uri
263     | uri when (Pcre.pmatch ~rex:heading_theory_RE uri) ->
264         Pcre.replace ~rex:heading_theory_RE ~templ:server_url uri
265     | uri when (Pcre.pmatch ~rex:heading_nuprl_RE uri) ->
266         Pcre.replace ~rex:heading_nuprl_RE ~templ:server_url uri
267     | uri -> raise (Http_getter_invalid_URI uri)
268   in
269   let rdf_url_of_uri = function (* TODO as above *)
270     | uri when (Pcre.pmatch ~rex:heading_rdf_cic_RE uri) ->
271         Pcre.replace ~rex:heading_rdf_cic_RE ~templ:server_url uri
272     | uri when (Pcre.pmatch ~rex:heading_rdf_theory_RE uri) ->
273         Pcre.replace ~rex:heading_rdf_theory_RE ~templ:server_url uri
274     | uri -> raise (Http_getter_invalid_URI uri)
275   in
276   let log = ref (logmsg ^ "Processing server: " ^ server_url ^ "<br />\n") in
277   let (xml_index, rdf_index, xsl_index) =
278     (* TODO keeps index in memory, is better to keep them on temp files? *)
279     (http_get (server_url ^ "/" ^ Http_getter_env.xml_index),
280      http_get (server_url ^ "/" ^ Http_getter_env.rdf_index),
281      http_get (server_url ^ "/" ^ Http_getter_env.xsl_index))
282   in
283   if (xml_index = None && rdf_index = None && xsl_index = None) then
284     debug_print (sprintf "Warning: useless server %s" server_url);
285   (match xml_index with
286   | Some xml_index ->
287       (log := !log ^ "Updating XML db ...<br />\n";
288       List.iter
289         (function
290           | l when is_blank_line l -> ()  (* skip blank and commented lines *)
291           | l ->
292               try
293                 (match Pcre.split ~rex:index_line_sep_RE l with
294                 | [uri; "gz"] ->
295                    assert (is_cic_uri uri || is_nuprl_uri uri) ;
296                    (map_of_uri uri)#replace
297                     uri ((xml_url_of_uri uri) ^ ".xml.gz")
298                 | [uri] ->
299                    assert (is_cic_uri uri || is_nuprl_uri uri) ;
300                    (map_of_uri uri)#replace
301                     uri ((xml_url_of_uri uri) ^ ".xml")
302                 | _ ->
303                     log := !log ^ "Ignoring invalid line: '" ^ l ^ "'<br />\n")
304               with Http_getter_invalid_URI uri ->
305                 log := !log ^ "Ignoring invalid XML URI: '" ^ uri ^ "'<br />\n")
306             (Pcre.split ~rex:index_sep_RE xml_index)) (* xml_index lines *)
307   | None -> ());
308   (match rdf_index with
309   | Some rdf_index ->
310       (log := !log ^ "Updating RDF db ...<br />\n";
311       List.iter
312         (fun l ->
313           try
314             (match Pcre.split ~rex:index_line_sep_RE l with
315             | [uri; "gz"] ->
316                 rdf_map#replace uri ((rdf_url_of_uri uri) ^ ".xml.gz")
317             | [uri] -> rdf_map#replace uri ((rdf_url_of_uri uri) ^ ".xml")
318             | _ -> log := !log ^ "Ignoring invalid line: " ^ l ^ "<br />\n")
319           with Http_getter_invalid_URI uri ->
320             log := !log ^ "Ignoring invalid RDF URI: " ^ uri ^ "<br />\n")
321         (Pcre.split ~rex:index_sep_RE rdf_index)) (* rdf_index lines *)
322   | None -> ());
323   (match xsl_index with
324   | Some xsl_index ->
325       (log := !log ^ "Updating XSLT db ...<br />\n";
326       List.iter
327         (fun l -> xsl_map#replace l (server_url ^ "/" ^ l))
328         (Pcre.split ~rex:index_sep_RE xsl_index);
329       log := !log ^ "All done!<br />\n")
330   | None -> ());
331   debug_print "done with this server";
332   !log
333 in
334 let update_from_all_servers () =  (* use global maps *)
335   cic_map#clear; nuprl_map#clear; rdf_map#clear; xsl_map#clear;
336   let log =
337     List.fold_left
338       update_from_server
339       ""  (* initial logmsg: empty *)
340         (* reverse order: 1st server is the most important one *)
341       (List.rev !Http_getter_env.servers)
342   in
343   cic_map#sync; nuprl_map#sync; rdf_map#sync; xsl_map#sync;
344   log
345 in
346
347   (* thread action *)
348
349 let callback (req: Http_types.request) outchan =
350   try
351     debug_print ("Connection from " ^ req#clientAddr);
352     debug_print ("Received request: " ^ req#path);
353     (match req#path with
354     | "/help" ->
355         return_html_raw
356           (Http_getter_const.usage_string (Http_getter_env.env_to_string ()))
357           outchan
358     | "/getxml" | "/getxslt" | "/getdtd" | "/resolve" | "/register" ->
359         (let uri = req#param "uri" in  (* common parameter *)
360         match req#path with
361         | "/getxml" ->
362             let enc = parse_enc req in
363             let patch = parse_patch req in
364             Http_getter_cache.respond_xml
365               ~url:(resolve uri) ~uri ~enc ~patch outchan
366         | "/getxslt" ->
367             let patch = parse_patch req in
368             Http_getter_cache.respond_xsl ~url:(resolve uri) ~patch outchan
369         | "/getdtd" ->
370             let patch = parse_patch req in
371             Http_getter_cache.respond_dtd
372               ~patch ~url:(Http_getter_env.dtd_dir ^ "/" ^ uri) outchan
373         | "/resolve" ->
374             (try
375               return_xml_raw
376                 (sprintf "<url value=\"%s\" />\n" (resolve uri))
377                 outchan
378             with Http_getter_unresolvable_URI uri ->
379               return_xml_raw "<unresolved />\n" outchan)
380         | "/register" ->
381             let url = req#param "url" in
382             register uri url;
383             return_html_msg "Register done" outchan
384         | _ -> assert false)
385     | "/update" ->
386         Http_getter_env.reload (); (* reload servers list from servers file *)
387         let log = update_from_all_servers () in
388         return_html_msg log outchan
389     | "/add_server" ->
390         let name = req#param "url" in
391         (try
392           let position =
393             try
394               let res = int_of_string (req#param "position") in
395               if res < 0 then
396                 raise (Failure "int_of_string");
397               res
398             with Failure "int_of_string" ->
399               raise (Http_getter_bad_request
400                 (sprintf "position must be a non negative integer (%s given)"
401                   (req#param "position")))
402           in
403           if position = 0 then  (* fallback to default value *)
404             raise (Http_types.Param_not_found "foo")
405           else if position > 0 then begin (* add server and update all *)
406             Http_getter_env.add_server ~position name;
407             let log = update_from_all_servers () in
408             return_html_msg
409               (sprintf "Added server %s in position %d)<br />\n%s"
410                 name position log)
411               outchan
412           end else (* position < 0 *) (* error! *)
413             assert false (* already checked above *)
414         with Http_types.Param_not_found _ ->  (* add as 1st server by default *)
415           Http_getter_env.add_server ~position:0 name;
416           let log = update_from_server  (* quick update (new server only) *)
417             (sprintf "Added server %s in head position<br />\n" name) name
418           in
419           return_html_msg log outchan)
420     | "/remove_server" ->
421         let position =
422           try
423             let res = int_of_string (req#param "position") in
424             if res < 0 then
425               raise (Failure "int_of_string");
426             res
427           with Failure "int_of_string" ->
428             raise (Http_getter_bad_request
429               (sprintf "position must be a non negative integer (%s given)"
430                 (req#param "position")))
431         in
432         let server_name =
433           try
434             List.nth !Http_getter_env.servers position
435           with Failure "nth" ->
436             raise (Http_getter_bad_request
437               (sprintf "no server with position %d" position))
438         in
439         Http_getter_env.remove_server position;
440         let log = update_from_all_servers () in
441         return_html_msg
442           (sprintf "Removed server %s (position %d)<br />\n%s"
443             server_name position log)
444           outchan
445     | "/getalluris" ->
446         return_all_xml_uris
447           (fun uri ->
448             (Pcre.pmatch ~rex:heading_cic_RE uri) &&
449             not (Pcre.pmatch ~rex:trailing_types_RE uri))
450           outchan
451     | "/getallrdfuris" ->
452         (let classs = req#param "class" in
453         try
454           let filter =
455             let base = "^helm:rdf:www\\.cs\\.unibo\\.it/helm/rdf/" in
456             match classs with
457             | ("forward" as c) | ("backward" as c) ->
458                 (fun uri -> Pcre.pmatch ~pat:(base ^ c) uri)
459             | c -> raise (Http_getter_invalid_RDF_class c)
460           in
461           return_all_rdf_uris filter outchan
462         with Http_getter_invalid_RDF_class c ->
463           raise (Http_getter_bad_request ("Invalid RDF class: " ^ c)))
464     | "/ls" -> return_ls (parse_ls_uri req) (parse_output_format req) outchan
465     | "/getempty" ->
466         Http_daemon.respond ~body:Http_getter_const.empty_xml outchan
467     | invalid_request ->
468         Http_daemon.respond_error ~status:(`Client_error `Bad_request) outchan);
469     debug_print "Done!\n"
470   with
471   | Http_types.Param_not_found attr_name ->
472       return_400 (sprintf "Parameter '%s' is missing" attr_name) outchan
473   | Http_getter_bad_request msg -> return_html_error msg outchan
474   | Http_getter_internal_error msg -> return_html_internal_error msg outchan
475   | Shell.Subprocess_error l ->
476       return_html_internal_error
477         (String.concat "<br />\n"
478           (List.map
479             (fun (cmd, code) ->
480               sprintf "Command '%s' returned %s"
481                 cmd (string_of_proc_status code))
482             l))
483         outchan
484   | exc ->
485       return_html_error
486         ("Uncaught exception: " ^ (Printexc.to_string exc))
487         outchan
488 in
489
490     (* daemon initialization *)
491
492 let main () =
493   print_string (Http_getter_env.env_to_string ());
494   flush stdout;
495   Unix.putenv "http_proxy" "";
496   at_exit save_maps;
497   Sys.catch_break true;
498   try
499     Http_daemon.start'
500       ~timeout:(Some 600) ~port:Http_getter_env.port ~mode:`Thread callback
501   with Sys.Break -> ()  (* 'save_maps' already registered with 'at_exit' *)
502 in
503
504 main ()
505