]> matita.cs.unibo.it Git - helm.git/blob - helm/searchEngine/searchEngine.ml
Reindentation.
[helm.git] / helm / searchEngine / searchEngine.ml
1 (* Copyright (C) 2002, 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://cs.unibo.it/helm/.
24  *)
25
26 module T = MQGTypes
27 module U = MQGUtil
28 module G = MQueryGenerator
29 module C = MQIConn
30
31 open Http_types ;;
32
33 let debug = false;;
34 let debug_print s = if debug then prerr_endline s;;
35 Http_common.debug := true;;
36 (* Http_common.debug := true;; *)
37
38 let mqi_flags = [] (* default MathQL interpreter options *)
39
40 open Printf;;
41
42 let daemon_name = "Search Engine";;
43
44   (* First of all we load the configuration *)
45 let _ =
46  let configuration_file = "/projects/helm/etc/searchEngine.conf.xml" in
47   Helm_registry.load_from configuration_file
48 ;;
49
50 let pages_dir = Helm_registry.get "search_engine.html_dir";;
51
52   (** accepted HTTP servers for ask_uwobo method forwarding *)
53 let valid_servers= Helm_registry.get_string_list "search_engine.valid_servers";;
54
55
56 let interactive_user_uri_choice_TPL = pages_dir ^ "/templateambigpdq1.html";;
57 let interactive_interpretation_choice_TPL =
58   pages_dir ^ "/templateambigpdq2.html";;
59 let constraints_choice_TPL = pages_dir ^ "/constraints_choice_template.html";;
60 let final_results_TPL = pages_dir ^ "/templateambigpdq3.html";;
61
62 exception Chat_unfinished
63
64   (* build a bool from a 1-character-string *)
65 let bool_of_string' = function
66   | "0" -> false
67   | "1" -> true
68   | s -> failwith ("Can't parse a boolean from string: " ^ s)
69 ;;
70
71   (* build an int option from a string *)
72 let int_of_string' = function
73   | "_" -> None
74   | s ->
75       try
76         Some (int_of_string s)
77       with Failure "int_of_string" ->
78         failwith ("Can't parse an int option from string: " ^ s)
79 ;;
80
81   (* HTML pretty printers for mquery_generator types *)
82
83 let html_of_r_obj (pos, uri) =
84   sprintf
85     "<tr><td><input type='checkbox' name='constr_obj' checked='on'/></td><td>%s</td><td>%s</td><td>%s</td></tr>"
86     uri (U.text_of_position pos)
87     (if U.is_main_position pos then
88       sprintf "<input name='obj_depth' size='2' type='text' value='%s' />"
89         (U.text_of_depth pos "")
90     else
91       "<input type=\"hidden\" name=\"obj_depth\" />")
92 ;;
93
94 let html_of_r_rel pos =
95   sprintf
96     "<tr><td><input type='checkbox' name='constr_rel' checked='on'/></td><td>%s</td><td><input name='rel_depth' size='2' type='text' value='%s' /></td></tr>"
97     (U.text_of_position (pos:>T.full_position)) (U.text_of_depth (pos:>T.full_position) "")
98 ;;
99
100 let html_of_r_sort (pos, sort) =
101   sprintf
102     "<tr><td><input type='checkbox' name='constr_sort' checked='on'/></td><td>%s</td><td>%s</td><td><input name='sort_depth' size='2' type='text' value='%s'/></td></tr>"
103     (U.text_of_sort sort) (U.text_of_position (pos:>T.full_position)) (U.text_of_depth (pos:>T.full_position) "")
104 ;;
105
106   (** pretty print a MathQL query result to an HELM theory file *)
107 let theory_of_result result =
108  let results_no = List.length result in
109   if results_no > 0 then
110    let mode = if results_no > 10 then "linkonly" else "typeonly" in
111    let results =
112     let idx = ref (results_no + 1) in
113      List.fold_right
114       (fun (uri,attrs) i ->
115         decr idx ;
116         "<tr><td valign=\"top\">" ^ string_of_int !idx ^ ".</td><td><ht:OBJECT uri=\"" ^ uri ^ "\" mode=\"" ^ mode ^ "\"/></td></tr>" ^  i
117       ) result ""
118    in
119     "<h1>Query Results:</h1><table xmlns:ht=\"http://www.cs.unibo.it/helm/namespaces/helm-theory\">" ^ results ^ "</table>"
120   else
121     "<h1>Query Results:</h1><p>No results found!</p>"
122 ;;
123
124 let pp_result result =
125  "<html xmlns:ht=\"http://www.cs.unibo.it/helm/namespaces/helm-theory\">\n<head><title>Query Results</title><style> A { text-decoration: none } </style></head>\n<body>" ^ theory_of_result result ^ "</body></html>"
126 ;;
127
128   (** chain application of Pcre substitutions *)
129 let rec apply_substs substs line =
130   match substs with
131   | [] -> line
132   | (rex, templ) :: rest -> apply_substs rest (Pcre.replace ~rex ~templ line)
133   (** fold like function on files *)
134 let fold_file f init fname =
135   let inchan = open_in fname in
136   let rec fold_lines' value =
137     try 
138       let line = input_line inchan in 
139       fold_lines' (f value line)
140     with End_of_file -> value
141   in
142   let res = (try fold_lines' init with e -> (close_in inchan; raise e)) in
143   close_in inchan;
144   res
145   (** iter like function on files *)
146 let iter_file f = fold_file (fun _ line -> f line) ()
147
148 let (title_tag_RE, choices_tag_RE, msg_tag_RE, id_to_uris_RE, id_RE,
149     interpretations_RE, interpretations_labels_RE, results_RE, new_aliases_RE,
150     form_RE, variables_initialization_RE)
151   =
152   (Pcre.regexp "@TITLE@", Pcre.regexp "@CHOICES@", Pcre.regexp "@MSG@",
153   Pcre.regexp "@ID_TO_URIS@", Pcre.regexp "@ID@",
154   Pcre.regexp "@INTERPRETATIONS@", Pcre.regexp "@INTERPRETATIONS_LABELS@",
155   Pcre.regexp "@RESULTS@", Pcre.regexp "@NEW_ALIASES@", Pcre.regexp "@FORM@",
156   Pcre.regexp "@VARIABLES_INITIALIZATION@")
157 let server_and_port_url_RE = Pcre.regexp "^http://([^/]+)/.*$"
158
159 let port = Helm_registry.get_int "search_engine.port";;
160
161 let pp_error = sprintf "<html><body><h1>Error: %s</h1></body></html>";;
162
163 let bad_request body outchan =
164   Http_daemon.respond_error ~status:(`Client_error `Bad_request) ~body outchan
165 ;;
166
167 let contype = "Content-Type", "text/html";;
168
169 (* SEARCH ENGINE functions *)
170
171 let get_constraints term =
172  function
173     | "/locateInductivePrinciple" ->
174       None,
175       (CGLocateInductive.get_constraints term),
176       (None,None,None)
177     | "/searchPattern" ->
178      let constr_obj, constr_rel, constr_sort =
179        CGSearchPattern.get_constraints term in
180      (Some CGSearchPattern.universe),
181      (constr_obj, constr_rel, constr_sort),
182      (Some constr_obj, Some constr_rel, Some constr_sort)
183     | "/matchConclusion" ->
184      let list_of_must, only = CGMatchConclusion.get_constraints [] [] term in
185 (* FG: there is no way to choose the block number ***************************)
186      let block = pred (List.length list_of_must) in 
187       (Some CGMatchConclusion.universe), 
188       (List.nth list_of_must block, [], []), (Some only, None, None)
189     | _ -> assert false
190 ;;
191
192 (*
193   format:
194     <must_obj> ':' <must_rel> ':' <must_sort> ':' <only_obj> ':' <only_rel> ':' <only_sort>
195
196     <must_*> ::= ('0'|'1') ('_'|<int>) (',' ('0'|'1') ('_'|<int>))*
197     <only> ::= '0'|'1'
198 *)
199 let add_user_constraints ~constraints
200  ((obj, rel, sort), (only_obj, only_rel, only_sort))
201 =
202   let parse_must s =
203     let l = Pcre.split ~pat:"," s in
204     (try
205       List.map
206         (fun s ->
207           let subs = Pcre.extract ~pat:"^(.)(\\d+|_)$" s in
208           (bool_of_string' subs.(1), int_of_string' subs.(2)))
209         l
210      with
211       Not_found -> failwith ("Can't parse constraint string: " ^ constraints)
212     )
213   in
214     (* to be used on "obj" *)
215   let add_user_must33 user_must must =
216     List.map2
217      (fun (b, i) (p, u) ->
218        if b then Some (U.set_full_position p i, u) else None)
219      user_must must
220   in
221     (* to be used on "rel" *)
222   let add_user_must22 user_must must =
223     List.map2
224      (fun (b, i) p -> if b then Some (U.set_main_position p i) else None)
225      user_must must
226   in
227     (* to be used on "sort" *)
228   let add_user_must32 user_must must =
229     List.map2
230      (fun (b, i) (p, s)-> if b then Some (U.set_main_position p i, s) else None)
231      user_must must
232   in
233   match Pcre.split ~pat:":" constraints with
234   | [user_obj;user_rel;user_sort;user_only_obj;user_only_rel;user_only_sort] ->
235       let
236        (user_obj,user_rel,user_sort,user_only_obj,user_only_rel,user_only_sort)
237       =
238         (parse_must user_obj,
239         parse_must user_rel,
240         parse_must user_sort,
241         bool_of_string' user_only_obj,
242         bool_of_string' user_only_rel,
243         bool_of_string' user_only_sort)
244       in
245       let only' =
246        (if user_only_obj  then only_obj else None),
247        (if user_only_rel  then only_rel else None),
248        (if user_only_sort then only_sort else None)
249       in
250       let must' =
251        let rec filter_some =
252         function
253            [] -> []
254          | None::tl -> filter_some tl
255          | (Some x)::tl -> x::(filter_some tl) 
256        in
257         filter_some (add_user_must33 user_obj obj),
258         filter_some (add_user_must22 user_rel rel),
259         filter_some (add_user_must32 user_sort sort)
260       in
261       (must', only')
262   | _ -> failwith ("Can't parse constraint string: " ^ constraints)
263 in
264
265 (* HTTP DAEMON CALLBACK *)
266
267 let callback (req: Http_types.request) outchan =
268   try
269     debug_print (sprintf "Received request: %s" req#path);
270     (match req#path with
271     | "/execute" ->
272         let mqi_handle = C.init mqi_flags debug_print in 
273         let query_string = req#param "query" in
274         let lexbuf = Lexing.from_string query_string in
275         let query = MQueryUtil.query_of_text lexbuf in
276         let result = MQueryInterpreter.execute mqi_handle query in
277         let result_string = pp_result result in
278               C.close mqi_handle;
279         Http_daemon.respond ~body:result_string ~headers:[contype] outchan
280     | "/locate" ->
281         let mqi_handle = C.init mqi_flags debug_print in
282         let id = req#param "id" in
283         let query = G.locate id in
284         let result = MQueryInterpreter.execute mqi_handle query in
285               C.close mqi_handle;
286         Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan
287     | "/unreferred" ->
288         let mqi_handle = C.init mqi_flags debug_print in
289         let target = req#param "target" in
290         let source = req#param "source" in
291         let query = G.unreferred target source in
292         let result = MQueryInterpreter.execute mqi_handle query in
293               C.close mqi_handle;
294         Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan
295     | "/getpage" ->
296         (* TODO implement "is_permitted" *)
297         (let is_permitted _ = true in
298         let remove_fragment uri = Pcre.replace ~pat:"#.*" uri in
299         let page = remove_fragment (req#param "url") in
300         let preprocess =
301           (try
302             bool_of_string (req#param "preprocess")
303           with Invalid_argument _ | Http_types.Param_not_found _ -> false)
304         in
305         (match page with
306         | page when is_permitted page ->
307             (let fname = sprintf "%s/%s" pages_dir (remove_fragment page) in
308             Http_daemon.send_basic_headers ~code:200 outchan;
309             Http_daemon.send_header "Content-Type" "text/html" outchan;
310             Http_daemon.send_CRLF outchan;
311             if preprocess then begin
312               iter_file
313                 (fun line ->
314                   output_string outchan
315                     ((apply_substs
316                        (List.map
317                          (function (key,value) ->
318                            let key' =
319                             (Pcre.extract ~pat:"param\\.(.*)" key).(1)
320                            in
321                             Pcre.regexp ("@" ^ key' ^ "@"), value
322                          )
323                          (List.filter
324                            (fun (key,_) as p-> Pcre.pmatch ~pat:"^param\\." key)
325                            req#params)
326                        )
327                        line) ^
328                     "\n"))
329                 fname
330             end else
331               Http_daemon.send_file ~src:(FileSrc fname) outchan)
332         | page -> Http_daemon.respond_forbidden ~url:page outchan))
333     | "/ask_uwobo" ->
334       let url = req#param "url" in
335       let server_and_port =
336         (Pcre.extract ~rex:server_and_port_url_RE url).(1)
337       in
338       if List.mem server_and_port valid_servers then
339         Http_daemon.respond
340           ~headers:["Content-Type", "text/html"]
341           ~body:(Http_client.http_get url)
342           outchan
343       else
344         Http_daemon.respond
345           ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port))
346           outchan
347     | "/searchPattern"
348     | "/matchConclusion"
349     | "/locateInductivePrinciple" ->
350         let mqi_handle = C.init mqi_flags debug_print in
351         let term_string = req#param "term" in
352         let (context, metasenv) = ([], []) in
353         let id_to_uris_raw = req#param "aliases" in
354 (*XXX
355         let tokens = Pcre.split ~pat:"\\s" id_to_uris_raw in
356         let rec parse_tokens keys lookup = function (* TODO spostarla fuori *)
357           | [] -> keys, lookup
358           | "alias" :: key :: value :: rest ->
359               let key' = CicTextualParser0.Id key in
360                parse_tokens
361                  (key'::keys)
362                  (fun id ->
363                    if id = key' then
364                      Some
365                       (CicTextualParser0.Uri (MQueryMisc.cic_textual_parser_uri_of_string value))
366                    else lookup id)
367                  rest
368           | _ -> failwith "Can't parse aliases"
369         in
370 *)
371         let parse_choices choices_raw =
372           let choices = Pcre.split ~pat:";" choices_raw in
373           List.fold_left
374             (fun f x ->
375               match Pcre.split ~pat:"\\s" x with
376               | ""::id::tail
377               | id::tail when id<>"" ->
378                   (fun id' ->
379                     if id = id' then
380                       Some (List.map (fun u -> Netencoding.Url.decode u) tail)
381                     else
382                       f id')
383               | _ -> failwith "Can't parse choices")
384             (fun _ -> None)
385             choices
386         in
387         let id_to_uris =
388          DisambiguatingParser.EnvironmentP3.of_string id_to_uris_raw in
389 print_endline ("id_to_uris_raw: " ^ id_to_uris_raw) ;
390 print_endline ("id_to_uris: " ^ (DisambiguatingParser.EnvironmentP3.to_string id_to_uris)) ;
391         let id_to_choices =
392           try
393             let choices_raw = req#param "choices" in
394             parse_choices choices_raw
395           with Http_types.Param_not_found _ -> (fun _ -> None)
396         in
397         let module Chat: DisambiguateTypes.Callbacks =
398           struct
399
400             let interactive_user_uri_choice
401               ~selection_mode ?ok
402               ?enable_button_for_non_vars ~(title: string) ~(msg: string)
403               ~(id: string) (choices: string list)
404               =
405                 (match id_to_choices id with
406                 | Some choices -> choices
407                 | None ->
408                   let msg = Pcre.replace ~pat:"\'" ~templ:"\\\'" msg in
409                   (match selection_mode with
410                   | `SINGLE -> assert false
411                   | `MULTIPLE ->
412                       Http_daemon.send_basic_headers ~code:200 outchan ;
413                       Http_daemon.send_CRLF outchan ;
414                       iter_file
415                         (fun line ->
416                           let formatted_choices =
417                             String.concat ","
418                               (List.map (fun uri -> sprintf "\'%s\'" uri) choices)
419                           in
420                           let processed_line =
421                             apply_substs
422                               [title_tag_RE, title;
423                                choices_tag_RE, formatted_choices;
424                                msg_tag_RE, msg;
425                                id_to_uris_RE, id_to_uris_raw;
426                                id_RE, id]
427                               line
428                           in
429                           output_string outchan (processed_line ^ "\n"))
430                         interactive_user_uri_choice_TPL;
431                       raise Chat_unfinished))
432
433             let interactive_interpretation_choice interpretations =
434               let html_interpretations_labels =
435                 String.concat ", "
436                   (List.map
437                     (fun l ->
438                       "\'" ^
439                       (String.concat "<br />"
440                         (List.map
441                           (fun (id, value) ->
442                             (sprintf "alias id %s = %s" id value))
443                           l)) ^
444                       "\'")
445                   interpretations)
446               in
447               let html_interpretations =
448                 String.concat ", "
449                   (List.map
450                     (fun l ->
451                       "\'" ^
452                       (String.concat " "
453                         (List.map
454                           (fun (id, value) ->
455                             (sprintf "alias id %s = %s"
456                               id
457                               (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
458                                 value)))
459                           l)) ^
460                       "\'")
461                     interpretations)
462               in
463               Http_daemon.send_basic_headers ~code:200 outchan ;
464               Http_daemon.send_CRLF outchan ;
465               iter_file
466                 (fun line ->
467                   let processed_line =
468                     apply_substs
469                       [interpretations_RE, html_interpretations;
470                        interpretations_labels_RE, html_interpretations_labels]
471                       line
472                   in
473                   output_string outchan (processed_line ^ "\n"))
474                 interactive_interpretation_choice_TPL;
475               raise Chat_unfinished
476
477             let input_or_locate_uri ~title =
478               UriManager.uri_of_string "cic:/Coq/Init/DataTypes/nat_ind.con"
479
480           end
481         in
482         let module Disambiguate' = DisambiguatingParser.Make(Chat) in
483         let (id_to_uris', metasenv', term') =
484           Disambiguate'.disambiguate_term mqi_handle
485             context metasenv term_string id_to_uris
486         in
487         (match metasenv' with
488         | [] ->
489             let universe,
490                 ((must_obj, must_rel, must_sort) as must'),
491                 ((only_obj, only_rel, only_sort) as only) =
492               get_constraints term' req#path
493             in
494             let must'', only' =
495               (try
496                 add_user_constraints
497                   ~constraints:(req#param "constraints")
498                   (must', only)
499               with Http_types.Param_not_found _ ->
500                 let variables =
501                  "var aliases = '" ^ id_to_uris_raw ^ "';\n" ^
502                  "var constr_obj_len = " ^
503                   string_of_int (List.length must_obj) ^ ";\n" ^
504                  "var constr_rel_len = " ^
505                   string_of_int (List.length must_rel) ^ ";\n" ^
506                  "var constr_sort_len = " ^
507                   string_of_int (List.length must_sort) ^ ";\n" in
508                 let form =
509                   (if must_obj = [] then "" else
510                     "<h4>Obj constraints</h4>" ^
511                     "<table>" ^
512                     (String.concat "\n" (List.map html_of_r_obj must_obj)) ^
513                     "</table>" ^
514                     (* The following three lines to make Javascript create *)
515                     (* the constr_obj[] and obj_depth[] arrays even if we  *)
516                     (* have only one real entry.                           *)
517                     "<input type=\"hidden\" name=\"constr_obj\" />" ^
518                     "<input type=\"hidden\" name=\"obj_depth\" />") ^
519                   (if must_rel = [] then "" else
520                    "<h4>Rel constraints</h4>" ^
521                    "<table>" ^
522                    (String.concat "\n" (List.map html_of_r_rel must_rel)) ^
523                    "</table>" ^
524                     (* The following two lines to make Javascript create *)
525                     (* the constr_rel[] and rel_depth[] arrays even if   *)
526                     (* we have only one real entry.                      *)
527                     "<input type=\"hidden\" name=\"constr_rel\" />" ^
528                     "<input type=\"hidden\" name=\"rel_depth\" />") ^
529                   (if must_sort = [] then "" else
530                     "<h4>Sort constraints</h4>" ^
531                     "<table>" ^
532                     (String.concat "\n" (List.map html_of_r_sort must_sort)) ^
533                     "</table>" ^
534                     (* The following two lines to make Javascript create *)
535                     (* the constr_sort[] and sort_depth[] arrays even if *)
536                     (* we have only one real entry.                      *)
537                     "<input type=\"hidden\" name=\"constr_sort\" />" ^
538                     "<input type=\"hidden\" name=\"sort_depth\" />") ^
539                     "<h4>Only constraints</h4>" ^
540                     "Enforce Only constraints for objects: " ^
541                       "<input type='checkbox' name='only_obj'" ^
542                       (if only_obj = None then "" else " checked='yes'") ^ " /><br />" ^
543                     "Enforce Rel constraints for objects: " ^
544                       "<input type='checkbox' name='only_rel'" ^
545                       (if only_rel = None then "" else " checked='yes'") ^ " /><br />" ^
546                     "Enforce Sort constraints for objects: " ^
547                       "<input type='checkbox' name='only_sort'" ^
548                       (if only_sort = None then "" else " checked='yes'") ^ " /><br />"
549                 in
550                 Http_daemon.send_basic_headers ~code:200 outchan ;
551                 Http_daemon.send_CRLF outchan ;
552                 iter_file
553                   (fun line ->
554                     let processed_line =
555                       apply_substs
556                        [form_RE, form ;
557                         variables_initialization_RE, variables] line
558                     in
559                     output_string outchan (processed_line ^ "\n"))
560                   constraints_choice_TPL;
561                   raise Chat_unfinished)
562             in
563             let query =
564              G.query_of_constraints universe must'' only'
565             in
566                   let results = MQueryInterpreter.execute mqi_handle query in 
567              Http_daemon.send_basic_headers ~code:200 outchan ;
568              Http_daemon.send_CRLF outchan ;
569              iter_file
570                (fun line ->
571                  let new_aliases =
572                   DisambiguatingParser.EnvironmentP3.to_string id_to_uris' in
573 (*XXX
574                    match id_to_uris' with
575                    | (domain, f) ->
576                        String.concat ", "
577                          (List.map
578                            (fun name ->
579                              sprintf "\'alias %s cic:%s\'"
580                                (match name with
581                                    CicTextualParser0.Id name -> name
582                                  | _ -> assert false (*CSC: completare *))
583                                (match f name with
584                                | None -> assert false
585                                | Some (CicTextualParser0.Uri t) ->
586                                    MQueryMisc.string_of_cic_textual_parser_uri
587                                      t
588                                | _ -> assert false (*CSC: completare *)))
589                            domain)
590                  in
591 *)
592                  let processed_line =
593                    apply_substs
594                      [results_RE, theory_of_result results ;
595                       new_aliases_RE, new_aliases]
596                      line
597                  in
598                  output_string outchan (processed_line ^ "\n"))
599                final_results_TPL
600         | _ -> (* unable to instantiate some implicit variable *)
601             Http_daemon.respond
602               ~headers:[contype]
603               ~body:"some implicit variables are still unistantiated :-("
604               outchan);
605             C.close mqi_handle
606     | invalid_request ->
607         Http_daemon.respond_error ~status:(`Client_error `Bad_request) outchan);
608     debug_print (sprintf "%s done!" req#path)
609   with
610   | Chat_unfinished -> prerr_endline "Chat unfinished, Try again!"
611   | Http_types.Param_not_found attr_name ->
612       bad_request (sprintf "Parameter '%s' is missing" attr_name) outchan
613   | exc ->
614       Http_daemon.respond
615         ~body:(pp_error ("Uncaught exception: " ^ (Printexc.to_string exc)))
616         outchan
617 in
618 printf "%s started and listening on port %d\n" daemon_name port;
619 printf "Current directory is %s\n" (Sys.getcwd ());
620 printf "HTML directory is %s\n" pages_dir;
621 flush stdout;
622 Unix.putenv "http_proxy" "";
623 Http_daemon.start' ~port callback;
624 printf "%s is terminating, bye!\n" daemon_name
625