]> matita.cs.unibo.it Git - helm.git/blob - helm/http_getter/http_getter.ml
ec6564249270e627d40facb4a9af47c9670bfa95
[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   let wrong_uri uri =
75     raise (Http_getter_bad_request ("Invalid /ls baseuri: " ^ uri))
76   in
77   fun (req: Http_types.request) ->
78     let baseuri = req#param "baseuri" in
79     try
80       let subs =
81         Pcre.extract ~rex:parse_ls_RE
82           (Pcre.replace ~rex:trailing_slash_RE  baseuri)
83       in
84       (match (subs.(1), subs.(2)) with
85       | "cic", uri -> Cic uri
86       | "theory", uri -> Theory uri
87       | _ -> wrong_uri baseuri)
88     with Not_found -> wrong_uri baseuri
89 ;;
90
91   (* global maps, shared by all threads *)
92
93 let cic_map = new Http_getter_map.map Http_getter_env.cic_dbm in
94 let nuprl_map = new Http_getter_map.map Http_getter_env.nuprl_dbm in
95 let rdf_map = new Http_getter_map.map Http_getter_env.rdf_dbm in
96 let xsl_map = new Http_getter_map.map Http_getter_env.xsl_dbm in
97
98 let maps = [ cic_map; nuprl_map; rdf_map; xsl_map ] in
99 let close_maps () = List.iter (fun m -> m#close) maps in
100 let clear_maps () = List.iter (fun m -> m#clear) maps in
101 let sync_maps () = List.iter (fun m -> m#sync) maps in
102
103 let map_of_uri = function
104   | uri when is_cic_uri uri -> cic_map
105   | uri when is_nuprl_uri uri -> nuprl_map
106   | uri when is_rdf_uri uri -> rdf_map
107   | uri when is_xsl_uri uri -> xsl_map
108   | uri -> raise (Http_getter_unresolvable_URI uri)
109 in
110 let resolve uri =
111   try
112     (map_of_uri uri)#resolve uri
113   with Http_getter_map.Key_not_found _ ->
114     raise (Http_getter_unresolvable_URI uri)
115 in
116 let register uri =
117   (* Warning: this fail if uri is already registered *)
118   (map_of_uri uri)#add uri
119 in
120 let return_all_foo_uris map doctype filter outchan =
121   (** return all URIs contained in 'map' which satisfy predicate 'filter'; URIs
122   are written in an XMLish format ('doctype' is the XML doctype) onto 'outchan'
123   *)
124   Http_daemon.send_basic_headers ~code:200 outchan;
125   Http_daemon.send_header "Content-Type" "text/xml" outchan;
126   Http_daemon.send_headers common_headers outchan;
127   Http_daemon.send_CRLF outchan;
128   output_string
129     outchan
130     (sprintf
131 "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>
132 <!DOCTYPE %s SYSTEM \"%s/getdtd?uri=%s.dtd\">
133
134 <%s>
135 "
136       doctype
137       Http_getter_env.my_own_url
138       doctype
139       doctype);
140   map#iter
141     (fun uri _ ->
142       if filter uri then
143         output_string outchan (sprintf "\t<uri value=\"%s\" />\n" uri));
144   output_string outchan (sprintf "</%s>\n" doctype)
145 in
146 let return_all_xml_uris = return_all_foo_uris cic_map "alluris" in
147 let return_all_rdf_uris = return_all_foo_uris rdf_map "allrdfuris" in
148 let return_ls =
149   let (++) (oldann, oldtypes, oldbody, oldtree)
150            (newann, newtypes, newbody, newtree) =
151     ((if newann   > oldann    then newann   else oldann),
152      (if newtypes > oldtypes  then newtypes else oldtypes),
153      (if newbody  > oldbody   then newbody  else oldbody),
154      (if newtree  > oldtree   then newtree  else oldtree))
155   in
156   let basepart_RE =
157     Pcre.regexp
158       "^([^.]*\\.[^.]*)((\\.body)|(\\.proof_tree)|(\\.types))?(\\.ann)?$"
159   in
160   let (types_RE, types_ann_RE, body_RE, body_ann_RE,
161        proof_tree_RE, proof_tree_ann_RE) =
162     (Pcre.regexp "\\.types$", Pcre.regexp "\\.types\\.ann$",
163      Pcre.regexp "\\.body$", Pcre.regexp "\\.body\\.ann$",
164      Pcre.regexp "\\.proof_tree$", Pcre.regexp "\\.proof_tree\\.ann$")
165   in
166   let (slash_RE, til_slash_RE, no_slashes_RE) =
167     (Pcre.regexp "/", Pcre.regexp "^.*/", Pcre.regexp "^[^/]*$")
168   in
169   fun lsuri fmt outchan ->
170     let pat =
171       "^" ^
172       (match lsuri with Cic p -> ("cic:" ^ p) | Theory p -> ("theory:" ^ p))
173     in
174     let (dir_RE, obj_RE) =
175       (Pcre.regexp (pat ^ "/"), Pcre.regexp (pat ^ "(\\.|$)"))
176     in
177     let dirs = ref StringSet.empty in
178     let objs = Hashtbl.create 17 in
179     let store_dir d =
180       dirs := StringSet.add (List.hd (Pcre.split ~rex:slash_RE d)) !dirs
181     in
182     let store_obj o =
183       let basepart = Pcre.replace ~rex:basepart_RE ~templ:"$1" o in
184       let no_flags = false, No, No, No in
185       let oldflags =
186         try
187           Hashtbl.find objs basepart
188         with Not_found -> (* no ann, no types, no body, no proof tree *)
189           no_flags
190       in
191       let newflags =
192         match o with
193         | s when Pcre.pmatch ~rex:types_RE s          -> (false, Yes, No, No)
194         | s when Pcre.pmatch ~rex:types_ann_RE s      -> (true,  Ann, No, No)
195         | s when Pcre.pmatch ~rex:body_RE s           -> (false, No, Yes, No)
196         | s when Pcre.pmatch ~rex:body_ann_RE s       -> (true,  No, Ann, No)
197         | s when Pcre.pmatch ~rex:proof_tree_RE s     -> (false, No, No, Yes)
198         | s when Pcre.pmatch ~rex:proof_tree_ann_RE s -> (true,  No, No, Ann)
199         | s -> no_flags
200       in
201       Hashtbl.replace objs basepart (oldflags ++ newflags)
202     in
203     cic_map#iter  (* BLEARGH Dbm module lacks support for fold-like functions *)
204       (fun key _ ->
205         match key with
206         | uri when Pcre.pmatch ~rex:dir_RE uri ->  (* directory hit *)
207             let localpart = Pcre.replace ~rex:dir_RE uri in
208             if Pcre.pmatch ~rex:no_slashes_RE localpart then
209               store_obj localpart
210             else
211               store_dir localpart
212         | uri when Pcre.pmatch ~rex:obj_RE  uri ->  (* file hit *)
213             store_obj (Pcre.replace ~rex:til_slash_RE uri)
214         | uri -> () (* miss *));
215     match fmt with
216     | Fmt_text ->
217         let body =
218           (List.fold_left
219             (fun s d -> sprintf "%sdir, %s\n" s d) ""
220             (StringSet.elements !dirs)) ^
221           (Http_getter_misc.hashtbl_sorted_fold
222             (fun uri (annflag, typesflag, bodyflag, treeflag) cont ->
223               sprintf "%sobject, %s, <%s,%s,%s,%s>\n"
224                 cont uri (if annflag then "YES" else "NO")
225                 (string_of_ls_flag typesflag)
226                 (string_of_ls_flag bodyflag)
227                 (string_of_ls_flag treeflag))
228             objs "")
229         in
230         Http_daemon.respond
231           ~headers:(("Content-Type", "text/plain") :: common_headers)
232           ~body outchan
233     | Fmt_xml ->
234         let body =
235           sprintf
236 "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>
237 <!DOCTYPE ls SYSTEM \"%s/getdtd?uri=ls.dtd\">
238
239 <ls>
240 %s
241 </ls>
242 "
243             Http_getter_env.my_own_url
244             ("\n" ^
245             (String.concat
246               "\n"
247               (List.map
248                 (fun d -> "<section>" ^ d ^ "</section>")
249                 (StringSet.elements !dirs))) ^ "\n" ^
250             (Http_getter_misc.hashtbl_sorted_fold
251               (fun uri (annflag, typesflag, bodyflag, treeflag) cont ->
252                 sprintf
253 "%s<object name=\"%s\">
254 \t<ann value=\"%s\" />
255 \t<types value=\"%s\" />
256 \t<body value=\"%s\" />
257 \t<proof_tree value=\"%s\" />
258 </object>
259 "
260                   cont uri (if annflag then "YES" else "NO")
261                   (string_of_ls_flag typesflag)
262                   (string_of_ls_flag bodyflag)
263                   (string_of_ls_flag treeflag))
264               objs ""))
265         in
266         Http_daemon.respond
267           ~headers:(("Content-Type", "text/xml") :: common_headers)
268           ~body outchan
269 in
270 let (index_line_sep_RE, index_sep_RE, trailing_types_RE,
271     heading_cic_RE, heading_theory_RE, heading_nuprl_RE,
272     heading_rdf_cic_RE, heading_rdf_theory_RE) =
273   (Pcre.regexp "[ \t]+", Pcre.regexp "\r\n|\r|\n",
274   Pcre.regexp "\\.types$",
275   Pcre.regexp "^cic:", Pcre.regexp "^theory:", Pcre.regexp "^nuprl:",
276   Pcre.regexp "^helm:rdf.*//cic:", Pcre.regexp "^helm:rdf.*//theory:")
277 in
278 let update_from_server logmsg server_url = (* use global maps *)
279   debug_print ("Updating information from " ^ server_url);
280   let xml_url_of_uri = function
281       (* TODO missing sanity checks on server_url, e.g. it can contains $1 *)
282     | uri when (Pcre.pmatch ~rex:heading_cic_RE uri) ->
283         Pcre.replace ~rex:heading_cic_RE ~templ:server_url uri
284     | uri when (Pcre.pmatch ~rex:heading_theory_RE uri) ->
285         Pcre.replace ~rex:heading_theory_RE ~templ:server_url uri
286     | uri when (Pcre.pmatch ~rex:heading_nuprl_RE uri) ->
287         Pcre.replace ~rex:heading_nuprl_RE ~templ:server_url uri
288     | uri -> raise (Http_getter_invalid_URI uri)
289   in
290   let rdf_url_of_uri = function (* TODO as above *)
291     | uri when (Pcre.pmatch ~rex:heading_rdf_cic_RE uri) ->
292         Pcre.replace ~rex:heading_rdf_cic_RE ~templ:server_url uri
293     | uri when (Pcre.pmatch ~rex:heading_rdf_theory_RE uri) ->
294         Pcre.replace ~rex:heading_rdf_theory_RE ~templ:server_url uri
295     | uri -> raise (Http_getter_invalid_URI uri)
296   in
297   let log = ref (logmsg ^ "Processing server: " ^ server_url ^ "<br />\n") in
298   let (xml_index, rdf_index, xsl_index) =
299     (* TODO keeps index in memory, is better to keep them on temp files? *)
300     (http_get (server_url ^ "/" ^ Http_getter_env.xml_index),
301      http_get (server_url ^ "/" ^ Http_getter_env.rdf_index),
302      http_get (server_url ^ "/" ^ Http_getter_env.xsl_index))
303   in
304   if (xml_index = None && rdf_index = None && xsl_index = None) then
305     debug_print (sprintf "Warning: useless server %s" server_url);
306   (match xml_index with
307   | Some xml_index ->
308       (log := !log ^ "Updating XML db ...<br />\n";
309       List.iter
310         (function
311           | l when is_blank_line l -> ()  (* skip blank and commented lines *)
312           | l ->
313               try
314                 (match Pcre.split ~rex:index_line_sep_RE l with
315                 | [uri; "gz"] ->
316                    assert (is_cic_uri uri || is_nuprl_uri uri) ;
317                    (map_of_uri uri)#replace
318                     uri ((xml_url_of_uri uri) ^ ".xml.gz")
319                 | [uri] ->
320                    assert (is_cic_uri uri || is_nuprl_uri uri) ;
321                    (map_of_uri uri)#replace
322                     uri ((xml_url_of_uri uri) ^ ".xml")
323                 | _ ->
324                     log := !log ^ "Ignoring invalid line: '" ^ l ^ "'<br />\n")
325               with Http_getter_invalid_URI uri ->
326                 log := !log ^ "Ignoring invalid XML URI: '" ^ uri ^ "'<br />\n")
327             (Pcre.split ~rex:index_sep_RE xml_index)) (* xml_index lines *)
328   | None -> ());
329   (match rdf_index with
330   | Some rdf_index ->
331       (log := !log ^ "Updating RDF db ...<br />\n";
332       List.iter
333         (fun l ->
334           try
335             (match Pcre.split ~rex:index_line_sep_RE l with
336             | [uri; "gz"] ->
337                 rdf_map#replace uri ((rdf_url_of_uri uri) ^ ".xml.gz")
338             | [uri] -> rdf_map#replace uri ((rdf_url_of_uri uri) ^ ".xml")
339             | _ -> log := !log ^ "Ignoring invalid line: " ^ l ^ "<br />\n")
340           with Http_getter_invalid_URI uri ->
341             log := !log ^ "Ignoring invalid RDF URI: " ^ uri ^ "<br />\n")
342         (Pcre.split ~rex:index_sep_RE rdf_index)) (* rdf_index lines *)
343   | None -> ());
344   (match xsl_index with
345   | Some xsl_index ->
346       (log := !log ^ "Updating XSLT db ...<br />\n";
347       List.iter
348         (fun l -> xsl_map#replace l (server_url ^ "/" ^ l))
349         (Pcre.split ~rex:index_sep_RE xsl_index);
350       log := !log ^ "All done!<br />\n")
351   | None -> ());
352   debug_print "done with this server";
353   !log
354 in
355 let update_from_all_servers () =  (* use global maps *)
356   clear_maps ();
357   let log =
358     List.fold_left
359       update_from_server
360       ""  (* initial logmsg: empty *)
361         (* reverse order: 1st server is the most important one *)
362       (List.rev !Http_getter_env.servers)
363   in
364   sync_maps ();
365   log
366 in
367
368   (* thread action *)
369
370 let callback (req: Http_types.request) outchan =
371   try
372     debug_print ("Connection from " ^ req#clientAddr);
373     debug_print ("Received request: " ^ req#path);
374     (match req#path with
375     | "/help" ->
376         return_html_raw
377           (Http_getter_const.usage_string (Http_getter_env.env_to_string ()))
378           outchan
379     | "/getxml" | "/getxslt" | "/getdtd" | "/resolve" | "/register" ->
380         (let uri = req#param "uri" in  (* common parameter *)
381         match req#path with
382         | "/getxml" ->
383             let enc = parse_enc req in
384             let patch = parse_patch req in
385             Http_getter_cache.respond_xml
386               ~url:(resolve uri) ~uri ~enc ~patch outchan
387         | "/getxslt" ->
388             let patch = parse_patch req in
389             Http_getter_cache.respond_xsl ~url:(resolve uri) ~patch outchan
390         | "/getdtd" ->
391             let patch = parse_patch req in
392             Http_getter_cache.respond_dtd
393               ~patch ~url:(Http_getter_env.dtd_dir ^ "/" ^ uri) outchan
394         | "/resolve" ->
395             (try
396               return_xml_raw
397                 (sprintf "<url value=\"%s\" />\n" (resolve uri))
398                 outchan
399             with Http_getter_unresolvable_URI uri ->
400               return_xml_raw "<unresolved />\n" outchan)
401         | "/register" ->
402             let url = req#param "url" in
403             register uri url;
404             return_html_msg "Register done" outchan
405         | _ -> assert false)
406     | "/clean_cache" ->
407         Http_getter_cache.clean ();
408         return_html_msg "Done." outchan
409     | "/update" ->
410         Http_getter_env.reload (); (* reload servers list from servers file *)
411         let log = update_from_all_servers () in
412         return_html_msg log outchan
413     | "/list_servers" ->
414         return_html_raw
415           (sprintf "<html><body><table>\n%s\n</table></body></html>"
416             (String.concat "\n"
417               (List.map
418                 (let i = ref ~-1 in
419                 fun s -> incr i; sprintf "<tr><td>%d</td><td>%s</td></tr>" !i s)
420                 !Http_getter_env.servers)))
421           outchan
422     | "/add_server" ->
423         let name = req#param "url" in
424         (try
425           let position =
426             try
427               let res = int_of_string (req#param "position") in
428               if res < 0 then
429                 raise (Failure "int_of_string");
430               res
431             with Failure "int_of_string" ->
432               raise (Http_getter_bad_request
433                 (sprintf "position must be a non negative integer (%s given)"
434                   (req#param "position")))
435           in
436           if position = 0 then  (* fallback to default value *)
437             raise (Http_types.Param_not_found "foo")
438           else if position > 0 then begin (* add server and update all *)
439             Http_getter_env.add_server ~position name;
440             let log = update_from_all_servers () in
441             return_html_msg
442               (sprintf "Added server %s in position %d)<br />\n%s"
443                 name position log)
444               outchan
445           end else (* position < 0 *) (* error! *)
446             assert false (* already checked above *)
447         with Http_types.Param_not_found _ ->  (* add as 1st server by default *)
448           Http_getter_env.add_server ~position:0 name;
449           let log = update_from_server  (* quick update (new server only) *)
450             (sprintf "Added server %s in head position<br />\n" name) name
451           in
452           return_html_msg log outchan)
453     | "/remove_server" ->
454         let position =
455           try
456             let res = int_of_string (req#param "position") in
457             if res < 0 then
458               raise (Failure "int_of_string");
459             res
460           with Failure "int_of_string" ->
461             raise (Http_getter_bad_request
462               (sprintf "position must be a non negative integer (%s given)"
463                 (req#param "position")))
464         in
465         let server_name =
466           try
467             List.nth !Http_getter_env.servers position
468           with Failure "nth" ->
469             raise (Http_getter_bad_request
470               (sprintf "no server with position %d" position))
471         in
472         Http_getter_env.remove_server position;
473         let log = update_from_all_servers () in
474         return_html_msg
475           (sprintf "Removed server %s (position %d)<br />\n%s"
476             server_name position log)
477           outchan
478     | "/getalluris" ->
479         return_all_xml_uris
480           (fun uri ->
481             (Pcre.pmatch ~rex:heading_cic_RE uri) &&
482             not (Pcre.pmatch ~rex:trailing_types_RE uri))
483           outchan
484     | "/getallrdfuris" ->
485         (let classs = req#param "class" in
486         try
487           let filter =
488             let base = "^helm:rdf:www\\.cs\\.unibo\\.it/helm/rdf/" in
489             match classs with
490             | ("forward" as c) | ("backward" as c) ->
491                 (fun uri -> Pcre.pmatch ~pat:(base ^ c) uri)
492             | c -> raise (Http_getter_invalid_RDF_class c)
493           in
494           return_all_rdf_uris filter outchan
495         with Http_getter_invalid_RDF_class c ->
496           raise (Http_getter_bad_request ("Invalid RDF class: " ^ c)))
497     | "/ls" -> return_ls (parse_ls_uri req) (parse_output_format req) outchan
498     | "/getempty" ->
499         Http_daemon.respond ~body:Http_getter_const.empty_xml outchan
500     | invalid_request ->
501         Http_daemon.respond_error ~status:(`Client_error `Bad_request) outchan);
502     debug_print "Done!\n"
503   with
504   | Http_types.Param_not_found attr_name ->
505       return_400 (sprintf "Parameter '%s' is missing" attr_name) outchan
506   | Http_getter_bad_request msg -> return_html_error msg outchan
507   | Http_getter_internal_error msg -> return_html_internal_error msg outchan
508   | Shell.Subprocess_error l ->
509       return_html_internal_error
510         (String.concat "<br />\n"
511           (List.map
512             (fun (cmd, code) ->
513               sprintf "Command '%s' returned %s"
514                 cmd (string_of_proc_status code))
515             l))
516         outchan
517   | exc ->
518       return_html_error
519         ("Uncaught exception: " ^ (Printexc.to_string exc))
520         outchan
521 in
522
523     (* daemon initialization *)
524
525 let main () =
526   print_string (Http_getter_env.env_to_string ());
527   flush stdout;
528   Unix.putenv "http_proxy" "";
529   at_exit close_maps;
530   Sys.catch_break true;
531   try
532     Http_daemon.start'
533       ~timeout:(Some 600) ~port:Http_getter_env.port ~mode:`Thread callback
534   with Sys.Break -> ()  (* 'close_maps' already registered with 'at_exit' *)
535 in
536
537 main ()
538