]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/getter/http_getter_cache.ml
Added support for xml base(s) URL and URI. The getter now adds these two
[helm.git] / helm / ocaml / getter / http_getter_cache.ml
1 (*
2  * Copyright (C) 2003-2004:
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 (* TODO cache expires control!!! *)
30 (* TODO uwobo loop:
31     if two large proof (already in cache) are requested at the same time by two
32     clients, uwobo (java implementation, not yet tested with the OCaml one)
33     starts looping sending output to one of the client *)
34
35 open Http_getter_common
36 open Http_getter_misc
37 open Http_getter_types
38 open Printf
39
40   (* expose ThreadSafe.threadSafe methods *)
41 class threadSafe =
42   object
43     inherit ThreadSafe.threadSafe
44     method virtual doCritical : 'a. 'a lazy_t -> 'a
45     method virtual doReader : 'a. 'a lazy_t -> 'a
46     method virtual doWriter : 'a. 'a lazy_t -> 'a
47   end
48
49 let threadSafe = new threadSafe
50
51 let finally cleanup f =
52   try
53     let res = Lazy.force f in
54     cleanup ();
55     res
56   with e ->
57     cleanup ();
58     raise (Http_getter_types.Cache_failure (Printexc.to_string e))
59
60 let resource_type_of_url = function
61   | url when Pcre.pmatch ~pat:"\\.xml\\.gz$" url -> `Gzipped
62   | url when Pcre.pmatch ~pat:"\\.xml$" url -> `Normal
63   | url -> raise (Invalid_URL url)
64
65 let extension_of_resource_type = function
66   | `Normal -> "xml"
67   | `Gzipped -> "xml.gz"
68
69   (* basename = resource name without trailing ".gz", if any *)
70 let is_in_cache basename =
71   Sys.file_exists
72     (match Lazy.force Http_getter_env.cache_mode with
73     | `Normal -> basename
74     | `Gzipped -> basename ^ ".gz")
75
76 let respond_xml
77   ?(via_http = true) ?(enc = `Normal) ?(patch = true) ~url ~uri outchan
78   =
79   let resource_type = resource_type_of_url url in
80   let extension = extension_of_resource_type resource_type in
81   let downloadname =
82     match uri_of_string uri with  (* parse uri *)
83     | Cic_uri (Cic baseuri) | Cic_uri (Theory baseuri) ->
84           (* assumption: baseuri starts with "/" *)
85         sprintf "%s%s.%s" (Lazy.force Http_getter_env.cic_dir) baseuri extension
86     | Nuprl_uri baseuri ->
87           (* assumption: baseuri starts with "/" *)
88         sprintf "%s%s.%s" (Lazy.force Http_getter_env.nuprl_dir) baseuri
89           extension
90     | Rdf_uri (prefix, ((Cic baseuri) as qbaseuri))
91     | Rdf_uri (prefix, ((Theory baseuri) as qbaseuri)) ->
92         let escaped_prefix =
93           (Pcre.replace ~pat:"/" ~templ:"_"
94             (Pcre.replace ~pat:"_" ~templ:"__"
95               (prefix ^
96               (match qbaseuri with
97               | Cic _ -> "//cic:"
98               | Theory _ -> "//theory:"))))
99         in
100         sprintf "%s/%s%s.%s"
101           (Lazy.force Http_getter_env.rdf_dir) escaped_prefix baseuri extension
102   in
103   let patch_fun =
104     if patch then
105       Http_getter_common.patch_xml ~xmlbases:(uri, url) ~via_http ()
106     else
107       (fun x -> x)
108   in
109   let basename = Pcre.replace ~pat:"\\.gz$" downloadname in
110   let contype = "text/xml" in
111     (* Fill cache if needed and return a short circuit file.
112       Short circuit is needed in situations like:
113         resource type = normal, cache type = gzipped, required encoding = normal
114       we would like to avoid normal -> gzipped -> normal conversions. To avoid
115       this tmp_short_circuit is used to remember the name of the intermediate
116       file name *)
117   let fill_cache () =
118     threadSafe#doWriter (lazy(
119       if not (is_in_cache basename) then begin  (* cache MISS *)
120         Http_getter_logger.log ~level:2 "Cache MISS :-(";
121         mkdir ~parents:true (Filename.dirname downloadname);
122         match (resource_type, Lazy.force Http_getter_env.cache_mode) with
123         | `Normal, `Normal | `Gzipped, `Gzipped ->
124             wget ~output:downloadname url;
125             None
126         | `Normal, `Gzipped ->  (* resource normal, cache gzipped *)
127             let tmp = tempfile () in
128             let (res, cleanup) =
129               if enc = `Normal then (* user wants normal: don't delete it! *)
130                 (Some (tmp, enc), (fun () -> ()))
131               else
132                 (None, (fun () -> Sys.remove tmp))
133             in
134             finally cleanup (lazy (
135               wget ~output:tmp url;
136               gzip ~output:(basename ^ ".gz") ~keep:true tmp; (* fill cache *)
137               res
138             ));
139         | `Gzipped, `Normal ->  (* resource gzipped, cache normal *)
140             let tmp = tempfile () in
141             let (res, cleanup) =
142               if enc = `Gzipped then (* user wants .gz: don't delete it! *)
143                 (Some (tmp, enc), (fun () -> ()))
144               else
145                 (None, (fun () -> Sys.remove tmp))
146             in
147             finally cleanup (lazy (
148               wget ~output:tmp url;
149               gunzip ~output:basename ~keep:true tmp; (* fill cache *)
150               res
151             ));
152       end else begin
153         Http_getter_logger.log ~level:2 "Cache HIT :-)";
154         None
155       end
156     )) in
157   let tmp_short_circuit = fill_cache () in
158   threadSafe#doReader (lazy(
159     assert (is_in_cache basename);
160     match (enc, Lazy.force Http_getter_env.cache_mode) with
161     | `Normal, `Normal | `Gzipped, `Gzipped ->
162         (* resource in cache is already in the required format *)
163         (match enc with
164         | `Normal ->
165             Http_getter_logger.log ~level:2
166               "No format mangling required (encoding = normal)";
167             return_file ~via_http ~fname:basename ~contype ~patch_fun outchan
168         | `Gzipped ->
169             Http_getter_logger.log ~level:2
170               "No format mangling required (encoding = gzipped)";
171             return_file
172               ~via_http ~fname:(basename ^ ".gz") ~contype ~contenc:"x-gzip"
173               ~patch_fun ~gunzip:true
174               outchan)
175     | `Normal, `Gzipped | `Gzipped, `Normal ->
176         (match tmp_short_circuit with
177         | None -> (* no short circuit possible, use cache *)
178           Http_getter_logger.log ~level:2
179             "No short circuit available, use cache";
180           let tmp = tempfile () in
181           finally (fun () -> Sys.remove tmp) (lazy (
182             (match enc with
183             | `Normal ->
184               (* required format is normal, cached version is gzipped *)
185               gunzip  (* gunzip to tmp *)
186                 ~output:tmp ~keep:true (basename ^ ".gz");
187               return_file ~via_http ~fname:tmp ~contype ~patch_fun outchan;
188             | `Gzipped ->
189               (* required format is gzipped, cached version is normal *)
190               gzip ~output:tmp ~keep:true basename;  (* gzip to tmp *)
191               return_file
192                 ~via_http ~fname:tmp ~contype ~contenc:"x-gzip"
193                 ~patch_fun ~gunzip:true
194                 outchan)
195           ))
196         | Some (fname, `Normal) ->  (* short circuit available, use it! *)
197             Http_getter_logger.log ~level:2
198               "Using short circuit (encoding = normal)";
199             finally (fun () -> Sys.remove fname) (lazy (
200               return_file ~via_http ~fname ~contype ~patch_fun outchan
201             ))
202         | Some (fname, `Gzipped) -> (* short circuit available, use it! *)
203             Http_getter_logger.log ~level:2
204               "Using short circuit (encoding = gzipped)";
205             finally (fun () -> Sys.remove fname) (lazy (
206               return_file ~via_http ~fname ~contype ~contenc:"x-gzip" ~patch_fun
207                 ~gunzip:true outchan
208             )))
209   ))
210
211   (* TODO enc is not yet supported *)
212 let respond_xsl
213   ?(via_http = true) ?(enc = `Normal) ?(patch = true) ~url outchan
214   =
215   let patch_fun =
216     if patch then Http_getter_common.patch_xsl ~via_http () else (fun x -> x)
217   in
218   let fname = tempfile () in
219   finally (fun () -> Sys.remove fname) (lazy (
220     wget ~output:fname url;
221     return_file ~via_http ~fname ~contype:"text/xml" ~patch_fun outchan
222   ))
223
224   (* TODO enc is not yet supported *)
225 let respond_dtd
226   ?(via_http = true) ?(enc = `Normal) ?(patch = true) ~url outchan
227   =
228   let patch_fun =
229     if patch then Http_getter_common.patch_dtd ~via_http () else (fun x -> x)
230   in
231   if Sys.file_exists url then
232     (* TODO check this: old getter here used text/xml *)
233     return_file ~via_http ~fname:url ~contype:"text/plain" ~patch_fun outchan
234   else
235     raise (Dtd_not_found url)
236
237 let clean () =
238  let module E = Http_getter_env in
239   List.iter
240    (function dir -> ignore (Unix.system ("rm -rf " ^ dir ^ "/*")))
241    [ Lazy.force E.cic_dir; Lazy.force E.nuprl_dir; Lazy.force E.rdf_dir ]
242