]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/getter/http_getter_misc.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / getter / http_getter_misc.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 open Printf
30
31 let file_scheme_prefix = "file://"
32
33 let trailing_dot_gz_RE = Pcre.regexp "\\.gz$"   (* for g{,un}zip *)
34 let url_RE = Pcre.regexp "^([\\w.-]+)(:(\\d+))?(/.*)?$"
35 let http_scheme_RE = Pcre.regexp ~flags:[`CASELESS] "^http://"
36 let file_scheme_RE = Pcre.regexp ~flags:[`CASELESS] ("^" ^ file_scheme_prefix)
37 let dir_sep_RE = Pcre.regexp "/"
38 let heading_slash_RE = Pcre.regexp "^/"
39
40 let local_url =
41   let rex = Pcre.regexp ("^(" ^ file_scheme_prefix ^ ")(.*)(.gz)$") in
42   fun s ->
43     try
44       Some ((Pcre.extract ~rex s).(2))
45     with Not_found -> None
46
47 let bufsiz = 16384  (* for file system I/O *)
48 let tcp_bufsiz = 4096 (* for TCP I/O *)
49
50 let fold_file f init fname =
51   let ic = open_in fname in
52   let rec aux acc =
53     let line = try Some (input_line ic) with End_of_file -> None in
54     match line with
55     | None -> acc
56     | Some line -> aux (f line acc)
57   in
58   let res = try aux init with e -> close_in ic; raise e in
59   close_in ic;
60   res
61
62 let iter_file f = fold_file (fun line _ -> f line) ()
63
64 let iter_buf_size = 10240
65
66 let iter_file_data f fname =
67   let ic = open_in fname in
68   let buf = String.create iter_buf_size in
69   try
70     while true do
71       let bytes = input ic buf 0 iter_buf_size in
72       if bytes = 0 then raise End_of_file;
73       f (String.sub buf 0 bytes)
74     done
75   with End_of_file -> close_in ic
76
77 let hashtbl_sorted_fold f tbl init =
78   let sorted_keys =
79     List.sort compare (Hashtbl.fold (fun key _ keys -> key::keys) tbl [])
80   in
81   List.fold_left (fun acc k -> f k (Hashtbl.find tbl k) acc) init sorted_keys
82
83 let hashtbl_sorted_iter f tbl =
84   let sorted_keys =
85     List.sort compare (Hashtbl.fold (fun key _ keys -> key::keys) tbl [])
86   in
87     List.iter (fun k -> f k (Hashtbl.find tbl k)) sorted_keys
88
89 let cp src dst =
90   try 
91     let ic = open_in src in
92       try
93         let oc = open_out dst in
94         let buf = String.create bufsiz in
95           (try
96              while true do
97                let bytes = input ic buf 0 bufsiz in
98                  if bytes = 0 then raise End_of_file else output oc buf 0 bytes
99              done
100            with 
101                End_of_file -> ()
102           );
103           close_in ic; close_out oc
104       with 
105           Sys_error s -> 
106             Http_getter_logger.log s;
107             close_in ic
108         | e -> 
109             Http_getter_logger.log (Printexc.to_string e);
110             close_in ic;
111             raise e
112   with 
113       Sys_error s -> 
114         Http_getter_logger.log s
115     | e -> 
116         Http_getter_logger.log (Printexc.to_string e);
117         raise e
118
119 let wget ?output url =
120   Http_getter_logger.log
121     (sprintf "wgetting %s (output: %s)" url
122       (match output with None -> "default" | Some f -> f));
123   match url with
124   | url when Pcre.pmatch ~rex:file_scheme_RE url -> (* file:// *)
125       (let src_fname = Pcre.replace ~rex:file_scheme_RE url in
126       match output with
127       | Some dst_fname -> cp src_fname dst_fname
128       | None ->
129           let dst_fname = Filename.basename src_fname in
130           if src_fname <> dst_fname then
131             cp src_fname dst_fname
132           else  (* src and dst are the same: do nothing *)
133             ())
134   | url when Pcre.pmatch ~rex:http_scheme_RE url -> (* http:// *)
135       (let oc = 
136         open_out (match output with Some f -> f | None -> Filename.basename url)
137       in
138       Http_user_agent.get_iter (fun data -> output_string oc data) url;
139       close_out oc)
140   | scheme -> (* unsupported scheme *)
141       failwith ("Http_getter_misc.wget: unsupported scheme: " ^ scheme)
142
143 let gzip ?(keep = false) ?output fname =
144   let output = match output with None -> fname ^ ".gz" | Some fname -> fname in
145   Http_getter_logger.log ~level:3
146     (sprintf "gzipping %s (keep: %b, output: %s)" fname keep output);
147   let (ic, oc) = (open_in fname, Gzip.open_out output) in
148   let buf = String.create bufsiz in
149   (try
150     while true do
151       let bytes = input ic buf 0 bufsiz in
152       if bytes = 0 then raise End_of_file else Gzip.output oc buf 0 bytes
153     done
154   with End_of_file -> ());
155   close_in ic; Gzip.close_out oc;
156   if not keep then Sys.remove fname
157 ;;
158
159 let gunzip ?(keep = false) ?output fname =
160     (* assumption: given file name ends with ".gz" or output is set *)
161   let output =
162     match output with
163     | None ->
164         if (Pcre.pmatch ~rex:trailing_dot_gz_RE fname) then
165           Pcre.replace ~rex:trailing_dot_gz_RE fname
166         else
167           failwith
168             "Http_getter_misc.gunzip: unable to determine output file name"
169     | Some fname -> fname
170   in
171   Http_getter_logger.log ~level:3
172     (sprintf "gunzipping %s (keep: %b, output: %s)" fname keep output);
173   (* Open the zipped file manually since Gzip.open_in may
174    * leak the descriptor if it raises an exception *)
175   let zic = open_in fname in
176   begin
177     try
178       let ic = Gzip.open_in_chan zic in
179       let oc = open_out output in
180       let buf = String.create bufsiz in
181       (try
182         while true do
183           let bytes = Gzip.input ic buf 0 bufsiz in
184           if bytes = 0 then raise End_of_file else Pervasives.output oc buf 0 bytes
185         done
186       with End_of_file -> ());
187         close_out oc;
188         Gzip.close_in ic
189     with
190       e -> close_in zic ; raise e
191   end ;
192   if not keep then Sys.remove fname
193 ;;
194
195 let tempfile () = Filename.temp_file "http_getter_" ""
196
197 exception Mkdir_failure of string * string;;  (* dirname, failure reason *)
198 let dir_perm = 0o755
199
200 let mkdir ?(parents = false) dirname =
201   let mkdirhier () =
202     let (pieces, hd) =
203       let split = Pcre.split ~rex:dir_sep_RE dirname in
204       if Pcre.pmatch ~rex:heading_slash_RE dirname then
205         (List.tl split, "/")
206       else
207         (split, "")
208     in
209     ignore
210       (List.fold_left
211         (fun pre dir ->
212           let next_dir =
213             sprintf "%s%s%s" pre (match pre with "/" | "" -> "" | _ -> "/") dir
214           in
215           (try
216             (match (Unix.stat next_dir).Unix.st_kind with
217             | Unix.S_DIR -> ()  (* dir component already exists, go on! *)
218             | _ ->  (* dir component already exists but isn't a dir, abort! *)
219                 raise
220                   (Mkdir_failure (dirname,
221                     sprintf "'%s' already exists but is not a dir" next_dir)))
222           with Unix.Unix_error (Unix.ENOENT, "stat", _) ->
223             (* dir component doesn't exists, create it and go on! *)
224             Unix.mkdir next_dir dir_perm);
225           next_dir)
226         hd pieces)
227   in
228   if parents then mkdirhier () else Unix.mkdir dirname dir_perm
229
230 let string_of_proc_status = function
231   | Unix.WEXITED code -> sprintf "[Exited: %d]" code
232   | Unix.WSIGNALED sg -> sprintf "[Killed: %d]" sg
233   | Unix.WSTOPPED sg -> sprintf "[Stopped: %d]" sg
234
235 let http_get url =
236   if Pcre.pmatch ~rex:file_scheme_RE url then begin
237       (* file:// URL. Read data from file system *)
238     let fname = Pcre.replace ~rex:file_scheme_RE url in
239     try
240       let size = (Unix.stat fname).Unix.st_size in
241       let buf = String.create size in
242       let ic = open_in fname in
243       really_input ic buf 0 size ;
244       close_in ic;
245       Some buf
246     with Unix.Unix_error (Unix.ENOENT, "stat", _) -> None
247   end else  (* other URL, pass it to Http_user_agent *)
248     try
249       Some (Http_user_agent.get url)
250     with e ->
251       Http_getter_logger.log (sprintf
252         "Warning: Http_user_agent failed on url %s with exception: %s"
253         url (Printexc.to_string e));
254       None
255
256 let is_blank_line =
257   let blank_line_RE = Pcre.regexp "(^#)|(^\\s*$)" in
258   fun line ->
259     Pcre.pmatch ~rex:blank_line_RE line
260
261 let normalize_dir s =  (* append "/" if missing *)
262   let len = String.length s in
263   try
264     if s.[len - 1] = '/' then s
265     else s ^ "/"
266   with Invalid_argument _ -> (* string is empty *) "/"
267
268 let strip_trailing_slash s =
269   try
270     let len = String.length s in
271     if s.[len - 1] = '/' then String.sub s 0 (len - 1)
272     else s
273   with Invalid_argument _ -> s
274
275 let strip_suffix ~suffix s =
276   try
277     let s_len = String.length s in
278     let suffix_len = String.length suffix in
279     let suffix_sub = String.sub s (s_len - suffix_len) suffix_len in
280     if suffix_sub <> suffix then raise (Invalid_argument "");
281     String.sub s 0 (s_len - suffix_len)
282   with Invalid_argument _ ->
283     raise (Invalid_argument "Http_getter_misc.strip_suffix")
284
285 let rec list_uniq = function 
286   | [] -> []
287   | h::[] -> [h]
288   | h1::h2::tl when h1 = h2 -> list_uniq (h2 :: tl) 
289   | h1::tl (* when h1 <> h2 *) -> h1 :: list_uniq tl
290
291 let extension s =
292   try
293     let idx = String.rindex s '.' in
294     String.sub s idx (String.length s - idx)
295   with Not_found -> ""
296
297 let temp_file_of_uri uri =
298   let flat_string s s' c =
299     let cs = String.copy s in
300     for i = 0 to (String.length s) - 1 do
301       if String.contains s' s.[i] then cs.[i] <- c
302     done;
303     cs
304   in
305   let user = try Unix.getlogin () with _ -> "" in
306   Filename.open_temp_file (user ^ flat_string uri ".-=:;!?/&" '_') ""
307
308 let backtick cmd =
309   let ic = Unix.open_process_in cmd in
310   let res = input_line ic in
311   ignore (Unix.close_process_in ic);
312   res
313