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