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