]> matita.cs.unibo.it Git - helm.git/blob - helm/DEVEL/ocaml-http/http_daemon.ml
first moogle template checkin
[helm.git] / helm / DEVEL / ocaml-http / http_daemon.ml
1
2 (*
3   OCaml HTTP - do it yourself (fully OCaml) HTTP daemon
4
5   Copyright (C) <2002> Stefano Zacchiroli <zack@cs.unibo.it>
6
7   This program is free software; you can redistribute it and/or modify
8   it under the terms of the GNU General Public License as published by
9   the Free Software Foundation; either version 2 of the License, or
10   (at your option) any later version.
11
12   This program 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 this program; if not, write to the Free Software
19   Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
20 *)
21
22 open Printf;;
23
24 open Http_common;;
25 open Http_types;;
26 open Http_constants;;
27 open Http_parser;;
28
29   (** send raw data on outchan, flushing it afterwards *)
30 let send_raw ~data outchan =
31   output_string outchan data;
32   flush outchan
33
34 let send_CRLF = send_raw ~data:crlf
35
36 let send_header ~header ~value =
37   Http_parser_sanity.heal_header (header, value);
38   send_raw ~data:(header ^ ": " ^ value ^ crlf)
39
40 let send_headers ~headers outchan =
41   List.iter (fun (header, value) -> send_header ~header ~value outchan) headers
42
43   (** internal: parse a code argument from a function which have two optional
44   arguments "code" and "status" *)
45 let get_code_argument func_name =
46   fun ~code ~status ->
47     (match code, status with
48     | Some c, None -> c
49     | None, Some s -> code_of_status s
50     | Some _, Some _ -> (* TODO use some static type checking *)
51         failwith (func_name ^ " you must give 'code' or 'status', not both")
52     | None, None -> (* TODO use some static type checking *)
53         failwith (func_name ^ " you must give 'code' or 'status', not none"))
54
55   (** internal: low level for send_status_line *)
56 let send_status_line' ~version ~code =
57   let status_line =
58     String.concat
59       " "
60       [ string_of_version version;
61       string_of_int code;
62       Http_misc.reason_phrase_of_code code ]
63   in
64   send_raw ~data:(status_line ^ crlf)
65
66 let send_status_line ?(version = http_version) ?code ?status outchan =
67   send_status_line'
68     ~version
69     ~code:(get_code_argument "Daemon.send_status_line" ~code ~status)
70     outchan
71
72   (* FIXME duplication of code between this and response#addBasicHeaders *)
73 let send_basic_headers ?(version = http_version) ?code ?status outchan =
74   send_status_line'
75     ~version ~code:(get_code_argument "Daemon.send_basic_headers" ~code ~status)
76     outchan;
77   send_headers
78     ~headers:["Date", Http_misc.date_822 (); "Server", server_string]
79     outchan
80
81   (** internal: given a status code and an additional body return a string
82   representing an HTML document that explains the meaning of given status code.
83   Additional data can be added to the body via 'body' argument *)
84 let foo_body code body =
85   let reason_phrase = Http_misc.reason_phrase_of_code code in
86   sprintf
87 "<!DOCTYPE HTML PUBLIC \"-//IETF//DTD HTML 2.0//EN\">
88 <HTML><HEAD>
89 <TITLE>%d %s</TITLE>
90 </HEAD><BODY>
91 <H1>%d - %s</H1>%s
92 </BODY></HTML>"
93     code reason_phrase code reason_phrase body
94
95   (** internal: send a fooish body explaining in HTML form the 'reason phrase'
96   of an HTTP response; body, if given, will be appended to the body *)
97 let send_foo_body code body = send_raw ~data:(foo_body code body)
98
99 let respond
100   (* Warning: keep default values in sync with Http_response.response class *)
101   ?(body = "") ?(headers = [])
102   ?(version = http_version) ?(code = 200) ?status outchan
103   =
104   let code =
105     match status with
106     | None -> code
107     | Some s -> code_of_status s
108   in
109   send_basic_headers ~version ~code outchan;
110   send_headers ~headers outchan;
111   send_header "Content-Length" (string_of_int (String.length body)) outchan;
112   send_CRLF outchan;
113   send_raw ~data:body outchan
114
115   (** internal: low level for respond_redirect, respond_error, ...
116   This function send a status line corresponding to a given code, some basic
117   headers, the additional headers (if given) and an HTML page containing the
118   reason phrase; if body is given it will be included in the body of the HTML
119   page *)
120 let send_empty_response
121   func_name ?(is_valid_status = fun _ -> true) ?(headers = []) ~body () =
122     fun ?(version = http_version) ?code ?status outchan ->
123       let code = get_code_argument func_name ~code ~status in
124       if not (is_valid_status code) then
125         failwith
126           (sprintf "'%d' isn't a valid status code for %s" code func_name)
127       else begin  (* status code suitable for answering *)
128         let headers =
129           [
130             "Connection", "close";
131             "Content-Type", "text/html; charset=iso-8859-1"
132           ] @ headers
133         in
134         let body = (foo_body code body) ^ body in
135         respond ~version ~code ~headers ~body outchan
136 (*
137         (* OLD VERSION, now use 'respond' function *)
138         send_basic_headers ~version ~code outchan;
139         send_header ~header:"Connection" ~value:"close" outchan;
140         send_header
141           ~header:"Content-Type"
142           ~value:"text/html; charset=iso-8859-1"
143           outchan;
144         send_headers ~headers outchan;
145         send_CRLF outchan;
146         send_foo_body ~code ~body outchan
147 *)
148       end
149
150 let respond_redirect
151   ~location ?(body = "") ?(version = http_version) ?(code = 301) ?status outchan
152   =
153   let code = 
154     match status with
155     | None -> code
156     | Some (s: Http_types.redirection_status) -> code_of_status s
157   in
158   send_empty_response
159     "Daemon.respond_redirect" ~is_valid_status:is_redirection
160     ~headers:["Location", location] ~body ()
161     ~version ~code outchan
162
163 let respond_error
164   ?(body = "") ?(version = http_version) ?(code = 400) ?status outchan =
165     let code =
166       match status with
167       | None -> code
168       | Some s -> code_of_status s
169     in
170     send_empty_response
171       "Daemon.respond_error" ~is_valid_status:is_error ~body ()
172       ~version ~code outchan
173
174 let respond_not_found ~url ?(version = http_version) outchan =
175   send_empty_response
176     "Daemon.respond_not_found" ~body:"" () ~version ~code:404 outchan
177
178 let respond_forbidden ~url ?(version = http_version) outchan =
179   send_empty_response
180     "Daemon.respond_permission_denied" ~body:"" () ~version ~code:403 outchan
181
182 (* let send_file ?name ?file outchan = *)
183 let send_file ~src outchan =
184   let buflen = 1024 in
185   let buf = String.make buflen ' ' in
186 (*
187   let (file, cleanup) =
188     (match (name, file) with
189     | Some n, None -> (* if we open the file, we close it before returning *)
190         let f = open_in n in
191         f, (fun () -> close_in f)
192     | None, Some f -> (f, (fun () -> ()))
193     | _ ->  (* TODO use some static type checking *)
194         failwith "Daemon.send_file: either name or file must be given")
195   in
196 *)
197   let (file, cleanup) =
198     match src with
199     | FileSrc fname -> (* if we open the file, we close it before returning *)
200         let f = open_in fname in
201         f, (fun () -> close_in f)
202     | InChanSrc inchan -> inchan, ignore
203   in
204   try
205     while true do
206       let bytes = input file buf 0 buflen in
207       if bytes = 0 then
208         raise End_of_file
209       else
210         output outchan buf 0 bytes
211     done;
212     assert false
213   with End_of_file ->
214     begin
215       flush outchan;
216       cleanup ()
217     end
218
219   (* TODO interface is too ugly to advertise this function in .mli *)
220   (** create a minimal HTML directory listing of a given directory and send it
221   over an out_channel, directory is passed as a dir_handle; name is the
222   directory name, used for pretty printing purposes; path is the opened dir
223   path, used to test its contents with stat *)
224 let send_dir_listing ~dir ~name ~path outchan =
225   fprintf outchan "<html>\n<head><title>%s</title></head>\n<body>\n" name;
226   let (dirs, files) =
227     List.partition (fun e -> Http_misc.is_directory (path ^ e)) (Http_misc.ls dir)
228   in
229   List.iter
230     (fun d -> fprintf outchan "<a href=\"%s/\">%s/</a><br />\n" d d)
231     (List.sort compare dirs);
232   List.iter
233     (fun f -> fprintf outchan "<a href=\"%s\">%s</a><br />\n" f f)
234     (List.sort compare files);
235   fprintf outchan "</body>\n</html>";
236   flush outchan
237
238 let respond_file ~fname ?(version = http_version) outchan =
239   (** ASSUMPTION: 'fname' doesn't begin with a "/"; it's relative to the current
240   document root (usually the daemon's cwd) *)
241   let droot = Sys.getcwd () in  (* document root *)
242   let path = droot ^ "/" ^ fname in (* full path to the desired file *)
243   if not (Sys.file_exists path) then (* file not found *)
244     respond_not_found ~url:fname outchan
245   else begin
246     try
247       if Http_misc.is_directory path then begin (* file found, is a dir *)
248         let dir = Unix.opendir path in
249         send_basic_headers ~version ~code:200 outchan;
250         send_header "Content-Type" "text/html" outchan;
251         send_CRLF outchan;
252         send_dir_listing ~dir ~name:fname ~path outchan;
253         Unix.closedir dir
254       end else begin  (* file found, is something else *)
255         let file = open_in fname in
256         send_basic_headers ~version ~code:200 outchan;
257         send_header
258           ~header:"Content-Length"
259           ~value:(string_of_int (Http_misc.filesize fname))
260           outchan;
261         send_CRLF outchan;
262         send_file ~src:(InChanSrc file) outchan;
263         close_in file
264       end
265     with
266     | Unix.Unix_error (Unix.EACCES, s, _) when (s = fname) ->
267         respond_forbidden ~url:fname ~version outchan
268     | Sys_error s when
269         (Pcre.pmatch ~rex:(Pcre.regexp (fname ^ ": Permission denied")) s) ->
270           respond_forbidden ~url:fname ~version outchan
271   end
272
273 let respond_with (res: Http_types.response) outchan =
274   res#serialize outchan;
275   flush outchan
276
277   (** internal: this exception is raised after a malformed request has been read
278   by a serving process to signal main server (or itself if mode = `Single) to
279   skip to next request *)
280 exception Again;;
281
282 let pp_parse_exc e =
283   sprintf "HTTP request parse error: %s" (Printexc.to_string e)
284
285   (* given a Http_parser.parse_request like function, wrap it in a function that
286   do the same and additionally catch parsing exception sending HTTP error
287   messages back to client as needed. Returned function raises Again when it
288   encounter a parse error (name 'Again' is intended for future versions that
289   will support http keep alive signaling that a new request has to be parsed
290   from client) *)
291 let rec wrap_parse_request_w_safety parse_function inchan outchan =
292 (*   try *)
293   (try
294     parse_function inchan
295   with
296   | (End_of_file) as e ->
297       debug_print (pp_parse_exc e);
298       respond_error ~code:400 ~body:"Unexpected End Of File" outchan;
299       raise Again
300   | (Malformed_request req) as e ->
301       debug_print (pp_parse_exc e);
302       respond_error
303         ~code:400
304         ~body:(
305           "request 1st line format should be: '<method> <url> <version>'" ^
306           "<br />\nwhile received request 1st line was:<br />\n" ^ req)
307         outchan;
308       raise Again
309   | (Invalid_HTTP_method meth) as e ->
310       debug_print (pp_parse_exc e);
311       respond_error
312         ~code:501
313         ~body:("Method '" ^ meth ^ "' isn't supported (yet)")
314         outchan;
315       raise Again
316   | (Malformed_request_URI uri) as e ->
317       debug_print (pp_parse_exc e);
318       respond_error ~code:400 ~body:("Malformed URL: '" ^ uri ^ "'") outchan;
319       raise Again
320   | (Invalid_HTTP_version version) as e ->
321       debug_print (pp_parse_exc e);
322       respond_error
323         ~code:505
324         ~body:("HTTP version '" ^ version ^ "' isn't supported (yet)")
325         outchan;
326       raise Again
327   | (Malformed_query query) as e ->
328       debug_print (pp_parse_exc e);
329       respond_error
330         ~code:400 ~body:(sprintf "Malformed query string '%s'" query) outchan;
331       raise Again
332   | (Malformed_query_part (binding, query)) as e ->
333       debug_print (pp_parse_exc e);
334       respond_error
335         ~code:400
336         ~body:(
337           sprintf "Malformed query part '%s' in query '%s'" binding query)
338         outchan;
339       raise Again)
340 (*  (* preliminary support for HTTP keep alive connections ... *)
341   with Again ->
342     wrap_parse_request_w_safety parse_function inchan outchan
343 *)
344
345   (* wrapper around Http_parser.parse_request which catch parsing exceptions and
346   return error messages to client as needed
347   @param inchan in_channel from which read incoming requests
348   @param outchan out_channl on which respond with error messages if needed
349   *)
350 let safe_parse_request = wrap_parse_request_w_safety parse_request
351
352   (* as above but for OO version (Http_parser.parse_request') *)
353 let safe_parse_request' = wrap_parse_request_w_safety (new Http_request.request)
354
355 let chdir_to_document_root = function (* chdir to document root *)
356   | Some dir -> Sys.chdir dir
357   | None -> ()
358
359 let server_of_mode = function
360   | `Single -> Http_tcp_server.simple
361   | `Fork   -> Http_tcp_server.fork
362   | `Thread -> Http_tcp_server.thread
363
364   (* TODO what happens when a Quit exception is raised by a callback? Do other
365   callbacks keep on living until the end or are them all killed immediatly?
366   The right semantics should obviously be the first one *)
367
368   (* TODO support also chroot to 'root', not only chdir *)
369   (* curried request *)
370 let start
371   ?(addr = default_addr) ?(port = default_port)
372   ?(timeout = Some default_timeout) ?(mode = default_mode) ?root callback
373   =
374   chdir_to_document_root root;
375   let sockaddr = Http_misc.build_sockaddr (addr, port) in
376   let daemon_callback inchan outchan =
377     try
378       let (path, parameters) = safe_parse_request inchan outchan in
379       callback path parameters outchan;
380       flush outchan
381     with Again -> ()
382   in
383   try
384     (server_of_mode mode) ~sockaddr ~timeout daemon_callback 
385   with Quit -> ()
386
387   (* OO request *)
388 let start'
389   ?(addr = default_addr) ?(port = default_port)
390   ?(timeout = Some default_timeout) ?(mode = default_mode) ?root callback
391   =
392   chdir_to_document_root root;
393   let sockaddr = Http_misc.build_sockaddr (addr, port) in
394   let daemon_callback inchan outchan =
395     try
396       let req = safe_parse_request' inchan outchan in
397       callback req outchan;
398       flush outchan
399     with Again -> ()
400   in
401   try
402     (server_of_mode mode) ~sockaddr ~timeout daemon_callback 
403   with Quit -> ()
404
405 module Trivial =
406   struct
407     let callback path _ outchan =
408       if not (Pcre.pmatch ~rex:(Pcre.regexp "^/") path) then
409         respond_error ~code:400 outchan
410       else
411         respond_file ~fname:(Http_misc.strip_heading_slash path) outchan
412     let start ?(addr = default_addr) ?(port = default_port) () =
413       start ~addr ~port callback
414   end
415
416   (* @param inchan input channel connected to client
417      @param outchan output channel connected to client
418      @param sockaddr client socket address *)
419 class connection inchan outchan sockaddr =
420   (* ASSUMPTION: inchan and outchan are channels built on top of the same
421   Unix.file_descr thus closing one of them will close also the other *)
422   let close' o = o#close in
423   object (self)
424
425     initializer Gc.finalise close' self
426
427     val mutable closed = false
428
429     method private assertNotClosed =
430       if closed then
431         failwith "Http_daemon.connection: connection is closed"
432
433     method getRequest =
434       self#assertNotClosed;
435       try
436         Some (safe_parse_request' inchan outchan)
437       with Again -> None
438
439     method respond_with res =
440       self#assertNotClosed;
441       respond_with res outchan
442
443     method close =
444       self#assertNotClosed;
445       close_in inchan;  (* this close also outchan *)
446       closed <- true
447
448   end
449
450 class daemon ?(addr = "0.0.0.0") ?(port = 80) () =
451   object (self)
452
453     val suck =
454       Http_tcp_server.init_socket (Http_misc.build_sockaddr (addr, port))
455
456     method accept =
457       let (cli_suck, cli_sockaddr) = Unix.accept suck in  (* may block *)
458       let (inchan, outchan) =
459         (Unix.in_channel_of_descr cli_suck, Unix.out_channel_of_descr cli_suck)
460       in
461       new connection inchan outchan cli_sockaddr
462
463     method getRequest =
464       let conn = self#accept in
465       match conn#getRequest with
466       | None ->
467           conn#close;
468           self#getRequest
469       | Some req -> (req, conn)
470
471   end
472