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