]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/hbugs/hbugs_misc.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / hbugs / hbugs_misc.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 Printf;;
30
31 let rec hashtbl_remove_all tbl key =
32   if Hashtbl.mem tbl key then begin
33     Hashtbl.remove tbl key;
34     hashtbl_remove_all tbl key
35   end else
36     ()
37
38   (** follows cut and paste from zack's Http_client_smart module *)
39
40 exception Malformed_URL of string;;
41 exception Malformed_HTTP_response of string;;
42
43 let bufsiz = 16384;;
44 let tcp_bufsiz = 4096;;
45
46 let body_sep_RE = Pcre.regexp "\r\n\r\n";;
47 let http_scheme_RE = Pcre.regexp ~flags:[`CASELESS] "^http://";;
48 let url_RE = Pcre.regexp "^([\\w.]+)(:(\\d+))?(/.*)?$";;
49 let parse_url url =
50   try
51     let subs =
52       Pcre.extract ~rex:url_RE (Pcre.replace ~rex:http_scheme_RE url)
53     in
54     (subs.(1),
55     (if subs.(2) = "" then 80 else int_of_string subs.(3)),
56     (if subs.(4) = "" then "/" else subs.(4)))
57   with exc -> raise (Malformed_URL url)
58 ;;
59 let get_body answer =
60   match Pcre.split ~rex:body_sep_RE answer with
61   | [_; body] -> body
62   | _ -> raise (Malformed_HTTP_response answer)
63 ;;
64
65 let init_socket addr port =
66   let inet_addr = (Unix.gethostbyname addr).Unix.h_addr_list.(0) in
67   let sockaddr = Unix.ADDR_INET (inet_addr, port) in
68   let suck = Unix.socket Unix.PF_INET Unix.SOCK_STREAM 0 in
69   Unix.connect suck sockaddr;
70   let outchan = Unix.out_channel_of_descr suck in
71   let inchan = Unix.in_channel_of_descr suck in
72   (inchan, outchan)
73 ;;
74 let rec retrieve inchan buf =
75   Buffer.add_string buf (input_line inchan ^ "\n");
76   retrieve inchan buf
77 ;;
78
79 let http_get_iter_buf ~callback url =
80   let (address, port, path) = parse_url url in
81   let buf = String.create tcp_bufsiz in
82   let (inchan, outchan) = init_socket address port in
83   output_string outchan (sprintf "GET %s\r\n" path);
84   flush outchan;
85   (try
86     while true do
87       match input inchan buf 0 tcp_bufsiz with
88       | 0 -> raise End_of_file
89       | bytes when bytes = tcp_bufsiz ->  (* buffer full, no need to slice it *)
90           callback buf
91       | bytes when bytes < tcp_bufsiz ->  (* buffer not full, slice it *)
92           callback (String.sub buf 0 bytes)
93       | _ -> (* ( bytes < 0 ) || ( bytes > tcp_bufsiz ) *)
94           assert false
95     done
96   with End_of_file -> ());
97   close_in inchan (* close also outchan, same fd *)
98 ;;
99
100 let http_get url =
101   let buf = Buffer.create (tcp_bufsiz * 10) in
102   http_get_iter_buf (fun data -> Buffer.add_string buf data) url;
103   get_body (Buffer.contents buf)
104 ;;
105
106 let http_post ?(body = "") url =
107   let (address, port, path) = parse_url url in
108   let (inchan, outchan) = init_socket address port in
109   output_string outchan (sprintf "POST %s HTTP/1.0\r\n" path);
110   output_string outchan (sprintf "Content-Length: %d\r\n" (String.length body));
111   output_string outchan "\r\n";
112   output_string outchan body;
113   flush outchan;
114   let buf = Buffer.create bufsiz in
115   (try
116     retrieve inchan buf
117   with End_of_file -> close_in inchan); (* close also outchan, same fd *)
118   get_body (Buffer.contents buf)
119 ;;
120