]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/getter/http_getter_storage.ml
new getter implementation: no more DBM maps
[helm.git] / helm / ocaml / getter / http_getter_storage.ml
1 (* Copyright (C) 2004-2005, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 open Printf
27
28 open Http_getter_misc
29 open Http_getter_types
30
31 exception Not_found'
32 exception Resource_not_found of string  (** uri *)
33
34 let index_fname = "INDEX"
35
36 let trailing_slash_RE = Pcre.regexp "/$"
37 let relative_RE_raw = "(^[^/]+(/[^/]+)*/?$)"
38 let relative_RE = Pcre.regexp relative_RE_raw
39 let file_scheme_RE_raw = "(^file://)"
40 let extended_file_scheme_RE = Pcre.regexp "(^file:/+)"
41 let file_scheme_RE = Pcre.regexp (relative_RE_raw ^ "|" ^ file_scheme_RE_raw)
42 let http_scheme_RE = Pcre.regexp "^http://"
43 let newline_RE = Pcre.regexp "\\n"
44 let cic_scheme_sep_RE = Pcre.regexp ":/"
45 let gz_suffix = ".gz"
46
47 let path_of_file_url url =
48   assert (Pcre.pmatch ~rex:file_scheme_RE url);
49   if Pcre.pmatch ~rex:relative_RE url then
50     url
51   else  (* absolute path, add heading "/" if missing *)
52     "/" ^ (Pcre.replace ~rex:extended_file_scheme_RE url)
53
54   (** associative list regular expressions -> url prefixes
55    * sorted with longest prefixes first *)
56 let prefix_map = lazy (
57   let map_w_length =
58     List.map
59       (fun (uri_prefix, url_prefix) ->
60         let uri_prefix = normalize_dir uri_prefix in
61         let url_prefix = normalize_dir url_prefix in
62         let regexp = Pcre.regexp ("^(" ^ Pcre.quote uri_prefix ^ ")") in
63         (regexp, String.length uri_prefix, uri_prefix, url_prefix))
64       (Lazy.force Http_getter_env.prefixes)
65   in
66   let decreasing_length (_, len1, _, _) (_, len2, _, _) = compare len2 len1 in
67   List.map
68     (fun (regexp, len, uri_prefix, url_prefix) ->
69       (regexp, strip_trailing_slash uri_prefix, url_prefix))
70     (List.fast_sort decreasing_length map_w_length))
71
72 let resolve_prefix uri =
73   let matches =
74     List.filter (fun (rex, _, _) -> Pcre.pmatch ~rex uri)
75       (Lazy.force prefix_map)
76   in
77   match matches with
78   | (rex, _, url_prefix) :: _ -> Pcre.replace_first ~rex ~templ:url_prefix uri
79   | [] -> raise (Unresolvable_URI uri)
80
81 let exists_http _ url =
82   Http_getter_wget.exists (url ^ gz_suffix) || Http_getter_wget.exists url
83
84 let exists_file _ fname =
85   Sys.file_exists (fname ^ gz_suffix) || Sys.file_exists fname
86
87 let resolve_http _ url =
88   try
89     List.find Http_getter_wget.exists [ url ^ gz_suffix; url ]
90   with Not_found -> raise Not_found'
91
92 let resolve_file _ fname =
93   try
94     List.find Sys.file_exists [ fname ^ gz_suffix; fname ]
95   with Not_found -> raise Not_found'
96
97 let strip_gz_suffix fname =
98   if extension fname = ".gz" then
99     String.sub fname 0 (String.length fname - 3)
100   else
101     fname
102
103 let remove_duplicates l =
104   Http_getter_misc.list_uniq (List.fast_sort Pervasives.compare l)
105
106 let ls_file_single _ path_prefix =
107   let is_dir fname = (Unix.stat fname).Unix.st_kind = Unix.S_DIR in
108   let is_useless dir = try dir.[0] = '.' with _ -> false in
109   let entries = ref [] in
110   try
111     let dir_handle = Unix.opendir path_prefix in
112     (try
113       while true do
114         let entry = Unix.readdir dir_handle in
115         if is_useless entry then
116           ()
117         else if is_dir (path_prefix ^ "/" ^ entry) then
118           entries := normalize_dir entry :: !entries
119         else
120           entries := strip_gz_suffix entry :: !entries
121       done
122     with End_of_file -> Unix.closedir dir_handle);
123     remove_duplicates !entries
124   with Unix.Unix_error (_, "opendir", _) -> []
125
126 let ls_http_single _ url_prefix =
127   let index = Http_getter_wget.get (normalize_dir url_prefix ^ index_fname) in
128   Pcre.split ~rex:newline_RE index
129
130 let get_file _ path =
131   if Sys.file_exists (path ^ gz_suffix) then
132     path ^ gz_suffix
133   else if Sys.file_exists path then
134     path
135   else
136     raise Not_found'
137
138 let get_http uri url =
139   let scheme, path =
140     match Pcre.split ~rex:cic_scheme_sep_RE uri with
141     | [scheme; path] -> scheme, path
142     | _ -> assert false
143   in
144   let cache_dest =
145     sprintf "%s%s/%s" (Lazy.force Http_getter_env.cache_dir) scheme path
146   in
147   if not (Sys.file_exists cache_dest) then begin  (* fill cache *)
148     Http_getter_misc.mkdir ~parents:true (Filename.dirname cache_dest);
149     (try
150       Http_getter_wget.get_and_save (url ^ gz_suffix) (cache_dest ^ gz_suffix)
151     with Http_user_agent.Http_error _ ->
152       (try
153         Http_getter_wget.get_and_save url cache_dest
154       with Http_user_agent.Http_error _ ->
155         raise Not_found'))
156   end;
157   cache_dest
158
159 let remove_file _ path =
160   if Sys.file_exists (path ^ gz_suffix) then Sys.remove (path ^ gz_suffix);
161   if Sys.file_exists path then Sys.remove path
162
163 let remove_http _ _ =
164   prerr_endline "Http_getter_storage.remove: not implemented for HTTP scheme";
165   assert false
166
167 type 'a storage_method = {
168   name: string;
169   file: string -> string -> 'a; (* unresolved uri, resolved uri *)
170   http: string -> string -> 'a; (* unresolved uri, resolved uri *)
171 }
172
173 let dispatch storage_method uri =
174   assert (extension uri <> ".gz");
175   let uri = (* add trailing slash to roots *)
176     try
177       if uri.[String.length uri - 1] = ':' then uri ^ "/"
178       else uri
179     with Invalid_argument _ -> uri
180   in
181   let url = resolve_prefix uri in
182   try
183     if Pcre.pmatch ~rex:file_scheme_RE url then
184       storage_method.file uri (path_of_file_url url)
185     else if Pcre.pmatch ~rex:http_scheme_RE url then
186       storage_method.http uri url
187     else
188       raise (Unsupported_scheme url)
189   with Not_found' -> raise (Resource_not_found uri)
190
191 let exists =
192   dispatch { name = "exists"; file = exists_file; http = exists_http }
193 let resolve =
194   dispatch { name = "resolve"; file = resolve_file; http = resolve_http }
195 let ls_single =
196   dispatch { name = "ls"; file = ls_file_single; http = ls_http_single }
197 let get = dispatch { name = "get"; file = get_file; http = get_http }
198 let remove =
199   dispatch { name = "remove"; file = remove_file; http = remove_http }
200
201 let filename = get
202
203   (* ls_single performs ls only below a single prefix, but prefixes which have
204    * common prefix (sorry) with a given one may need to be considered as well
205    * for example: when doing "ls cic:/" we would like to see the "cic:/matita"
206    * directory *)
207 let ls uri_prefix =
208   let direct_results = ls_single uri_prefix in
209   List.fold_left
210     (fun results (_, uri_prefix', _) ->
211       if Filename.dirname uri_prefix' = strip_trailing_slash uri_prefix then
212         (Filename.basename uri_prefix' ^ "/") :: results
213       else
214         results)
215     direct_results
216     (Lazy.force prefix_map)
217
218 let clean_cache () =
219   ignore (Sys.command
220     (sprintf "rm -rf %s/" (Lazy.force Http_getter_env.cache_dir)))
221