]> matita.cs.unibo.it Git - helm.git/blob - helm/searchEngine/searchEngine.ml
in the particular case of simple searches, Andrea atmost/atleast/exactly
[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 let string_tail s =
43   let len = String.length s in
44   String.sub s 1 (len-1)
45
46   (* First of all we load the configuration *)
47 let _ =
48  let configuration_file = "searchEngine.conf.xml" in
49   Helm_registry.load_from configuration_file
50 ;;
51
52 let port = Helm_registry.get_int "search_engine.port";;
53
54 let pages_dir = Helm_registry.get "search_engine.html_dir";;
55
56   (** accepted HTTP servers for ask_uwobo method forwarding *)
57 let valid_servers= Helm_registry.get_string_list "search_engine.valid_servers";;
58
59 let interactive_user_uri_choice_TPL = pages_dir ^ "/moogle_chat1.html";;
60 let interactive_interpretation_choice_TPL = pages_dir ^ "/moogle_chat2.html";;
61 let constraints_choice_TPL = pages_dir ^ "/moogle_constraints_choice.html";;
62 (* let final_results_TPL = pages_dir ^ "/templateambigpdq3.html";; *)
63 let start_TPL = pages_dir ^ "/moogle.html";; 
64 let final_results_TPL = pages_dir ^ "/moogle.html";;  
65
66 let my_own_url =
67  let ic = Unix.open_process_in "hostname -f" in
68  let hostname = input_line ic in
69  ignore (Unix.close_process_in ic);
70  sprintf "http://%s:%d" hostname port
71 ;;
72
73 exception Chat_unfinished
74 exception Invalid_action of string  (* invalid action for "/search" method *)
75
76 let javascript_quote s =
77  let rex = Pcre.regexp "'" in
78  let rex' = Pcre.regexp "\"" in
79   Pcre.replace ~rex ~templ:"\\'"
80    (Pcre.replace ~rex:rex' ~templ:"\\\"" s)
81 ;;
82
83   (* build a bool from a 1-character-string *)
84 let bool_of_string' = function
85   | "0" -> false
86   | "1" -> true
87   | s -> failwith ("Can't parse a boolean from string: " ^ s)
88 ;;
89
90   (* build an int option from a string *)
91 let int_of_string' = function
92   | "_" -> None
93   | s ->
94       try
95         Some (int_of_string s)
96       with Failure "int_of_string" ->
97         failwith ("Can't parse an int option from string: " ^ s)
98 ;;
99
100   (* HTML pretty printers for mquery_generator types *)
101
102 let html_of_r_obj (pos, uri) =
103   sprintf
104     "<tr><td><input type='checkbox' name='constr_obj' checked='on'/></td><td>%s</td><td>%s</td><td>%s</td></tr>"
105     uri (U.text_of_position pos)
106     (if U.is_main_position pos then
107       sprintf "<input name='obj_depth' size='2' type='text' value='%s' />"
108         (U.text_of_depth pos "")
109     else
110       "<input type=\"hidden\" name=\"obj_depth\" />")
111 ;;
112
113 let html_of_r_rel pos =
114   sprintf
115     "<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>"
116     (U.text_of_position (pos:>T.full_position)) (U.text_of_depth (pos:>T.full_position) "")
117 ;;
118
119 let html_of_r_sort (pos, sort) =
120   sprintf
121     "<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>"
122     (U.text_of_sort sort) (U.text_of_position (pos:>T.full_position)) (U.text_of_depth (pos:>T.full_position) "")
123 ;;
124
125   (** pretty print a MathQL query result to an HELM theory file *)
126 let theory_of_result result =
127  let results_no = List.length result in
128   if results_no > 0 then
129    let mode = if results_no > 10 then "linkonly" else "typeonly" in
130    let results =
131     let idx = ref (results_no + 1) in
132      List.fold_right
133       (fun uri i ->
134         decr idx ;
135         "<tr><td valign=\"top\">" ^ string_of_int !idx ^ ".</td><td><ht:OBJECT uri=\"" ^ uri ^ "\" mode=\"" ^ mode ^ "\"/></td></tr>" ^  i
136       ) result ""
137    in
138     "<b><font size=\"+1\">Query Results:</font></b><table xmlns:ht=\"http://www.cs.unibo.it/helm/namespaces/helm-theory\">" ^ results ^ "</table>"
139   else
140     "<b><font size=\"+1\">Query Results:</font></b><p>No results found!</p>"
141 ;;
142
143 let pp_result result =
144  "<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>"
145 ;;
146
147   (** chain application of Pcre substitutions *)
148 let rec apply_substs substs line =
149   match substs with
150   | [] -> line
151   | (rex, templ) :: rest -> apply_substs rest (Pcre.replace ~rex ~templ line)
152   (** fold like function on files *)
153 let fold_file f init fname =
154   let inchan = open_in fname in
155   let rec fold_lines' value =
156     try 
157       let line = input_line inchan in 
158       fold_lines' (f value line)
159     with End_of_file -> value
160   in
161   let res = (try fold_lines' init with e -> (close_in inchan; raise e)) in
162   close_in inchan;
163   res
164   (** iter like function on files *)
165 let iter_file f = fold_file (fun _ line -> f line) ()
166
167 let (expression_tag_RE,
168      action_tag_RE,
169      advanced_tag_RE,
170      title_tag_RE, no_choices_tag_RE, current_choices_tag_RE,  
171      choices_tag_RE, msg_tag_RE, id_to_uris_RE, id_RE, iden_tag_RE,
172      interpretations_RE, interpretations_labels_RE, results_RE, new_aliases_RE,
173      form_RE, variables_initialization_RE, search_engine_url_RE)
174   =
175   (Pcre.regexp "@EXPRESSION@", 
176    Pcre.regexp "@ACTION@", 
177    Pcre.regexp "@ADVANCED@",
178    Pcre.regexp "@TITLE@", Pcre.regexp "@NO_CHOICES@",  
179    Pcre.regexp "@CURRENT_CHOICES@",
180    Pcre.regexp "@CHOICES@", Pcre.regexp "@MSG@",
181    Pcre.regexp "@ID_TO_URIS@", Pcre.regexp "@ID@", Pcre.regexp "@IDEN@",
182    Pcre.regexp "@INTERPRETATIONS@", Pcre.regexp "@INTERPRETATIONS_LABELS@",
183    Pcre.regexp "@RESULTS@", Pcre.regexp "@NEW_ALIASES@", Pcre.regexp "@FORM@",
184    Pcre.regexp "@VARIABLES_INITIALIZATION@", Pcre.regexp "@SEARCH_ENGINE_URL@")
185 let server_and_port_url_RE = Pcre.regexp "^http://([^/]+)/.*$"
186
187 let pp_error = sprintf "<html><body><h1>Error: %s</h1></body></html>";;
188
189 let bad_request body outchan =
190   Http_daemon.respond_error ~code:(`Status (`Client_error `Bad_request)) ~body
191     outchan
192 ;;
193
194 let contype = "Content-Type", "text/html";;
195
196 (* SEARCH ENGINE functions *)
197
198 let get_constraints term =
199  function
200     | "/elim" ->
201       None,
202       (CGLocateInductive.get_constraints term),
203       (None,None,None)
204     | "/match" ->
205      let constr_obj, constr_rel, constr_sort =
206        CGSearchPattern.get_constraints term in
207      (Some CGSearchPattern.universe),
208      (constr_obj, constr_rel, constr_sort),
209      (Some constr_obj, Some constr_rel, Some constr_sort)
210     | "/hint" ->
211      let list_of_must, only = CGMatchConclusion.get_constraints [] [] term in
212 (* FG: there is no way to choose the block number ***************************)
213      let block = pred (List.length list_of_must) in 
214       (Some CGMatchConclusion.universe), 
215       (List.nth list_of_must block, [], []), (Some only, None, None)
216     | _ -> assert false
217 ;;
218
219 (*
220   format:
221     <must_obj> ':' <must_rel> ':' <must_sort> ':' <only_obj> ':' <only_rel> ':' <only_sort>
222
223     <must_*> ::= ('0'|'1') ('_'|<int>) (',' ('0'|'1') ('_'|<int>))*
224     <only> ::= '0'|'1'
225 *)
226 let add_user_constraints ~constraints
227  ((obj, rel, sort), (only_obj, only_rel, only_sort))
228 =
229   let parse_must s =
230     let l = Pcre.split ~pat:"," s in
231     (try
232       List.map
233         (fun s ->
234           let subs = Pcre.extract ~pat:"^(.)(\\d+|_)$" s in
235           (bool_of_string' subs.(1), int_of_string' subs.(2)))
236         l
237      with
238       Not_found -> failwith ("Can't parse constraint string: " ^ constraints)
239     )
240   in
241     (* to be used on "obj" *)
242   let add_user_must33 user_must must =
243     List.map2
244      (fun (b, i) (p, u) ->
245        if b then Some (U.set_full_position p i, u) else None)
246      user_must must
247   in
248     (* to be used on "rel" *)
249   let add_user_must22 user_must must =
250     List.map2
251      (fun (b, i) p -> if b then Some (U.set_main_position p i) else None)
252      user_must must
253   in
254     (* to be used on "sort" *)
255   let add_user_must32 user_must must =
256     List.map2
257      (fun (b, i) (p, s)-> if b then Some (U.set_main_position p i, s) else None)
258      user_must must
259   in
260   match Pcre.split ~pat:":" constraints with
261   | [user_obj;user_rel;user_sort;user_only_obj;user_only_rel;user_only_sort] ->
262       let
263        (user_obj,user_rel,user_sort,user_only_obj,user_only_rel,user_only_sort)
264       =
265         (parse_must user_obj,
266         parse_must user_rel,
267         parse_must user_sort,
268         bool_of_string' user_only_obj,
269         bool_of_string' user_only_rel,
270         bool_of_string' user_only_sort)
271       in
272       let only' =
273        (if user_only_obj  then only_obj else None),
274        (if user_only_rel  then only_rel else None),
275        (if user_only_sort then only_sort else None)
276       in
277       let must' =
278        let rec filter_some =
279         function
280            [] -> []
281          | None::tl -> filter_some tl
282          | (Some x)::tl -> x::(filter_some tl) 
283        in
284         filter_some (add_user_must33 user_obj obj),
285         filter_some (add_user_must22 user_rel rel),
286         filter_some (add_user_must32 user_sort sort)
287       in
288       (must', only')
289   | _ -> failwith ("Can't parse constraint string: " ^ constraints)
290 in
291
292 let send_results results
293   ?(id_to_uris = DisambiguatingParser.EnvironmentP3.of_string "") 
294    (req: Http_types.request) outchan
295   =
296   Http_daemon.send_basic_headers ~code:(`Code 200) outchan ;
297   Http_daemon.send_header "Content-Type" "text/xml" outchan;
298   Http_daemon.send_CRLF outchan ;
299   let subst =
300     (search_engine_url_RE, my_own_url) ::
301     (results_RE, theory_of_result results)::
302     (advanced_tag_RE, req#param "advanced")::
303     (expression_tag_RE, req#param "expression")::
304     (List.map
305       (function (key,value) ->
306         let key' = (Pcre.extract ~pat:"param\\.(.*)" key).(1) in
307         Pcre.regexp ("@" ^ key' ^ "@"), value)
308       (List.filter
309               (fun (key,_) as p-> Pcre.pmatch ~pat:"^param\\." key)
310               req#params))
311     in
312     iter_file
313       (fun line ->
314         let new_aliases =
315           DisambiguatingParser.EnvironmentP3.to_string id_to_uris
316         in
317         let processed_line =
318           apply_substs
319             (* CSC: Bug here: this is a string, not an array! *)
320             ((new_aliases_RE, "'" ^ javascript_quote new_aliases ^ "'")::subst) 
321             line
322         in
323         output_string outchan (processed_line ^ "\n"))
324       final_results_TPL
325 in
326
327 let exec_action mqi_handle (req: Http_types.request) outchan =
328   let term_string = req#param "expression" in
329   let (context, metasenv) = ([], []) in
330   let id_to_uris_raw = 
331     try req#param "aliases" 
332     with Http_types.Param_not_found _ -> ""
333   in
334   let parse_interpretation_choices choices =
335     List.map int_of_string (Pcre.split ~pat:" " choices) in
336   let parse_choices choices_raw =
337     let choices = Pcre.split ~pat:";" choices_raw in
338       List.fold_left
339         (fun f x ->
340            match Pcre.split ~pat:"\\s" x with
341              | ""::id::tail
342              | id::tail when id<>"" ->
343                  (fun id' ->
344                     if id = id' then
345                       Some (List.map (fun u -> Netencoding.Url.decode u) tail)
346                     else
347                       f id')
348              | _ -> failwith "Can't parse choices")
349         (fun _ -> None)
350         choices
351   in
352   let id_to_uris =
353     DisambiguatingParser.EnvironmentP3.of_string id_to_uris_raw in
354   let id_to_choices =
355     try
356       let choices_raw = req#param "choices" in
357         parse_choices choices_raw
358     with Http_types.Param_not_found _ -> (fun _ -> None)
359   in
360   let interpretation_choices =
361     try
362       let choices_raw = req#param "interpretation_choices" in
363       if choices_raw = "" then None 
364       else Some (parse_interpretation_choices choices_raw)
365     with Http_types.Param_not_found _ -> None
366   in 
367   let module Chat: DisambiguateTypes.Callbacks =
368     struct
369
370       let interactive_user_uri_choice
371         ~selection_mode ?ok
372         ?enable_button_for_non_vars ~(title: string) ~(msg: string)
373         ~(id: string) (choices: string list)
374         =
375         (match id_to_choices id with
376            | Some choices -> choices
377            | None ->
378               if req#param "advanced" = "no" then
379                 let isvar s =
380                   let len = String.length s in
381                   let suffix = String.sub s (len-4) 4 in
382                     not (suffix  = ".var") in
383                 List.filter isvar choices
384               else 
385                let msg = Pcre.replace ~pat:"\'" ~templ:"\\\'" msg in
386                (match selection_mode with
387                   | `SINGLE -> assert false
388                   | `MULTIPLE ->
389                       Http_daemon.send_basic_headers ~code:(`Code 200) outchan;
390                       Http_daemon.send_CRLF outchan ;
391                       let check_box uri =
392                         "<input type=\"checkbox\" name=\"param.choices\" 
393                         value=\"" ^
394                         uri ^ "\" />" ^ "<b>" ^ uri ^ "</b>" in
395 (* aggiungere gli hyperlinks? *)
396                       let check_boxes = 
397                         String.concat "<br />" 
398                           (List.map check_box choices) in
399                       iter_file
400                         (fun line ->
401                            let processed_line =
402                              apply_substs
403                                [advanced_tag_RE, req#param "advanced";
404                                 choices_tag_RE, check_boxes;
405                                 no_choices_tag_RE, 
406                                    string_of_int (List.length choices);
407                                 iden_tag_RE, id;
408                                 current_choices_tag_RE, req#param "choices";  
409                                 expression_tag_RE, req#param "expression";
410                                 action_tag_RE, string_tail req#path ]
411                                line
412                            in
413                              output_string outchan (processed_line ^ "\n"))
414                         interactive_user_uri_choice_TPL;
415                         raise Chat_unfinished))
416
417       let interactive_interpretation_choice interpretations =
418         match interpretation_choices with
419             Some l -> prerr_endline "CARRAMBA" ; l
420           | None ->
421               let html_interpretations =
422                 let radio_button n = 
423                   "<input type=\"radio\" name=\"param.interp\" value=\"" ^
424                   (string_of_int n) ^ "\" />" in
425                 let text interp =
426                   String.concat "<br />" 
427                     (List.map
428                        (fun (id, value) -> 
429                           sprintf "<span>%s = %s</span>" id value) 
430                        interp) in
431                 let rec aux n = 
432                   function
433                       [] -> []
434                     | interp::tl ->
435                         ((radio_button n)^(text interp))::(aux (n+1) tl) in
436                 String.concat "<br />" (aux 0 interpretations)
437               in
438               Http_daemon.send_basic_headers ~code:(`Code 200) outchan ;
439               Http_daemon.send_CRLF outchan ;
440               iter_file
441                 (fun line ->
442                    let processed_line =
443                      apply_substs
444                        [advanced_tag_RE, req#param "advanced";
445                         interpretations_RE, html_interpretations;
446                         current_choices_tag_RE, req#param "choices";
447                         expression_tag_RE, req#param "expression";
448                         action_tag_RE, string_tail req#path ]
449                         line
450                    in
451                    output_string outchan (processed_line ^ "\n"))
452                 interactive_interpretation_choice_TPL;
453               raise Chat_unfinished
454
455       let input_or_locate_uri ~title ?id () =
456         assert false
457
458     end
459   in
460   let module Disambiguate' = DisambiguatingParser.Make(Chat) in
461   let (id_to_uris', metasenv', term') =
462     match
463       Disambiguate'.disambiguate_term mqi_handle
464         context metasenv term_string id_to_uris
465     with
466         [id_to_uris',metasenv',term'] -> id_to_uris',metasenv',term'
467       | _ -> assert false
468         in
469   let universe,
470   ((must_obj, must_rel, must_sort) as must'),
471   ((only_obj, only_rel, only_sort) as only) =
472     get_constraints term' req#path
473   in
474   if
475     (try ignore (req#param "constraints"); false
476     with Http_types.Param_not_found _ -> true) &&
477     (req#param "advanced" = "no")
478   then
479     let dbd =
480       match mqi_handle.MQIConn.pgc with
481       |   MQIConn.MySQL_C conn -> conn
482       | _ -> assert false
483     in
484     let results = List.map snd (Match_concl.cmatch dbd term') in
485     send_results results ~id_to_uris:id_to_uris' req outchan
486   else
487   let must'', only' =
488     (try
489        add_user_constraints
490          ~constraints:(req#param "constraints")
491          (must', only)
492      with Http_types.Param_not_found _ ->
493        if req#param "advanced" = "no" then
494          (must',only)
495        else
496        let variables =
497          "var aliases = '" ^ id_to_uris_raw ^ "';\n" ^
498          "var constr_obj_len = " ^
499          string_of_int (List.length must_obj) ^ ";\n" ^
500          "var constr_rel_len = " ^
501          string_of_int (List.length must_rel) ^ ";\n" ^
502          "var constr_sort_len = " ^
503          string_of_int (List.length must_sort) ^ ";\n" in
504        let form =
505          (if must_obj = [] then "" else
506             "<h4>Obj constraints</h4>" ^
507             "<table>" ^
508             (String.concat "\n" (List.map html_of_r_obj must_obj)) ^
509             "</table>" ^
510             (* The following three lines to make Javascript create *)
511             (* the constr_obj[] and obj_depth[] arrays even if we  *)
512             (* have only one real entry.                           *)
513             "<input type=\"hidden\" name=\"constr_obj\" />" ^
514             "<input type=\"hidden\" name=\"obj_depth\" />") ^
515          (if must_rel = [] then "" else
516             "<h4>Rel constraints</h4>" ^
517             "<table>" ^
518             (String.concat "\n" (List.map html_of_r_rel must_rel)) ^
519             "</table>" ^
520             (* The following two lines to make Javascript create *)
521             (* the constr_rel[] and rel_depth[] arrays even if   *)
522             (* we have only one real entry.                      *)
523             "<input type=\"hidden\" name=\"constr_rel\" />" ^
524             "<input type=\"hidden\" name=\"rel_depth\" />") ^
525          (if must_sort = [] then "" else
526             "<h4>Sort constraints</h4>" ^
527             "<table>" ^
528             (String.concat "\n" (List.map html_of_r_sort must_sort)) ^
529             "</table>" ^
530             (* The following two lines to make Javascript create *)
531             (* the constr_sort[] and sort_depth[] arrays even if *)
532             (* we have only one real entry.                      *)
533             "<input type=\"hidden\" name=\"constr_sort\" />" ^
534             "<input type=\"hidden\" name=\"sort_depth\" />") ^
535          "<h4>Only constraints</h4>" ^
536          "Enforce Only constraints for objects: " ^
537          "<input type='checkbox' name='only_obj'" ^
538          (if only_obj = None then "" else " checked='yes'") ^
539          " /><br />" ^
540          "Enforce Rel constraints for objects: " ^
541          "<input type='checkbox' name='only_rel'" ^
542          (if only_rel = None then "" else " checked='yes'") ^
543          " /><br />" ^
544          "Enforce Sort constraints for objects: " ^
545          "<input type='checkbox' name='only_sort'" ^
546          (if only_sort = None then "" else " checked='yes'") ^
547          " /><br />"
548        in
549        Http_daemon.send_basic_headers ~code:(`Code 200) outchan ;
550        Http_daemon.send_CRLF outchan ;
551        iter_file
552          (fun line ->
553             let processed_line =
554               apply_substs
555                 [form_RE, form ;
556                  variables_initialization_RE, variables;
557                  advanced_tag_RE, req#param "advanced";
558                  current_choices_tag_RE, req#param "choices";
559                  interpretations_RE, req#param "interpretation_choices"; 
560                  expression_tag_RE, req#param "expression";
561                  action_tag_RE, string_tail req#path]  line
562             in
563               output_string outchan (processed_line ^ "\n"))
564          constraints_choice_TPL; 
565        raise Chat_unfinished)
566   in
567   let query =
568     G.query_of_constraints universe must'' only'
569   in
570   let results = MQueryInterpreter.execute mqi_handle query in 
571   send_results (List.map fst results) ~id_to_uris:id_to_uris' req outchan
572 in
573
574 (* HTTP DAEMON CALLBACK *)
575
576 let build_dynamic_uri url params =
577   let p = 
578     String.concat "&" (List.map  (fun (key,value) -> (key ^ "=" ^ (Netencoding.Url.encode value))) params) in
579   url ^ "?" ^ p
580 in
581
582 let build_uwobo_request (req: Http_types.request) outchan =
583   prerr_endline ("ECCOLO: " ^ req#param "param.SEARCH_ENGINE_URL");
584   let xmluri = build_dynamic_uri ((req#param "param.SEARCH_ENGINE_URL") ^ "/search") req#params in
585   prerr_endline ("xmluri: " ^ xmluri);
586   (*let xmluri = Netencoding.Url.encode xmluri in*)
587   let server_and_port = req#param "param.processorURL" in
588   let newreq = 
589     build_dynamic_uri 
590       (server_and_port ^ "apply") 
591       (("xmluri",xmluri)::("keys",(req#param "param.thkeys"))::req#params) in
592   (* if List.mem server_and_port valid_servers then *)
593   prerr_endline newreq;
594   if true then 
595     Http_daemon.respond
596       ~headers:["Content-Type", "text/html"]
597       ~body:(Http_client.http_get newreq)
598       outchan
599   else
600     Http_daemon.respond
601       ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port ^
602       (String.concat "\n" valid_servers)))
603       outchan
604 in
605
606 let proxy url outchan =
607   let server_and_port =
608     (Pcre.extract ~rex:server_and_port_url_RE url).(1)
609   in
610   if List.mem server_and_port valid_servers then
611     Http_daemon.respond
612       ~headers:["Content-Type", "text/html"]
613       ~body:(Http_client.http_get url)
614       outchan
615   else
616     Http_daemon.respond
617       ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port))
618       outchan
619 in
620
621 let callback mqi_handle (req: Http_types.request) outchan =
622   try
623     debug_print (sprintf "Received request: %s" req#path);
624     (match req#path with
625     | "/help" -> Http_daemon.respond ~body:"HELM Search Engine" outchan
626     | "/locate" ->
627         let initial_expression =
628           try req#param "expression" with Http_types.Param_not_found _ -> ""
629         in
630         let expression =
631           Pcre.replace ~pat:"\\s*$"
632             (Pcre.replace ~pat:"^\\s*" initial_expression)
633         in
634         if expression = "" then
635           send_results [] req outchan
636         else
637           let results =
638             let query = G.locate expression in
639              MQueryInterpreter.execute mqi_handle query
640           in
641           send_results (List.map fst results) req outchan
642     | "/execute" ->
643         let query_string = req#param "query" in
644         let lexbuf = Lexing.from_string query_string in
645         let query = MQueryUtil.query_of_text lexbuf in
646         let result = MQueryInterpreter.execute mqi_handle query in
647         let result_string = pp_result (List.map fst result) in
648         Http_daemon.respond ~body:result_string ~headers:[contype] outchan
649 (*  Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan *)
650     | "/unreferred" ->
651         let target = req#param "target" in
652         let source = req#param "source" in
653         let query = G.unreferred target source in
654         let result = MQueryInterpreter.execute mqi_handle query in
655         Http_daemon.respond ~headers:[contype]
656           ~body:(pp_result (List.map fst result)) outchan
657     | "/getpage" ->
658         (* TODO implement "is_permitted" *)
659         let _ = prerr_endline 
660           (Netencoding.Url.encode "http://mowgli.cs.unibo.it:38080/") in 
661         (let is_permitted _ = true in
662         let remove_fragment uri = Pcre.replace ~pat:"#.*" uri in
663         let page = remove_fragment (req#param "url") in
664         let preprocess =
665           (try
666             bool_of_string (req#param "preprocess")
667           with Invalid_argument _ | Http_types.Param_not_found _ -> false)
668         in
669         (match page with
670         | page when is_permitted page ->
671             (let fname = sprintf "%s/%s" pages_dir (remove_fragment page) in
672             Http_daemon.send_basic_headers ~code:(`Code 200) outchan;
673             Http_daemon.send_header "Content-Type" "text/html" outchan;
674             Http_daemon.send_CRLF outchan;
675             if preprocess then begin
676               iter_file
677                 (fun line ->
678                   output_string outchan
679                     ((apply_substs
680                        ((search_engine_url_RE, my_own_url) ::
681                         (advanced_tag_RE, "no") ::
682                         (results_RE, "") ::
683                        (List.map
684                          (function (key,value) ->
685                            let key' =
686                             (Pcre.extract ~pat:"param\\.(.*)" key).(1)
687                            in
688                             Pcre.regexp ("@" ^ key' ^ "@"), value
689                          )
690                          (List.filter
691                            (fun (key,_) as p-> Pcre.pmatch ~pat:"^param\\." key)
692                            req#params)
693                        ))
694                        line) ^
695                     "\n"))
696                 fname
697             end else
698               Http_daemon.send_file ~src:(FileSrc fname) outchan)
699         | page -> Http_daemon.respond_forbidden ~url:page outchan))
700     (* OLD | "/ask_uwobo" -> proxy (req#param "url") outchan *)
701     | "/ask_uwobo" -> build_uwobo_request req outchan
702     | "/hint"
703     | "/match"
704     | "/elim" ->
705         exec_action mqi_handle req outchan
706     | invalid_request ->
707         Http_daemon.respond_error ~code:(`Status (`Client_error `Bad_request))
708           outchan);
709     debug_print (sprintf "%s done!" req#path)
710   with
711   | Chat_unfinished -> prerr_endline "Chat unfinished, Try again!"
712   | Http_types.Param_not_found attr_name ->
713       bad_request (sprintf "Parameter '%s' is missing" attr_name) outchan
714   | exc ->
715       let msg = sprintf "Uncaught exception: %s" (Printexc.to_string exc) in
716        debug_print msg ;
717        Http_daemon.respond ~body:(pp_error msg) outchan
718 in
719 printf "%s started and listening on port %d\n" daemon_name port;
720 printf "Current directory is %s\n" (Sys.getcwd ());
721 printf "HTML directory is %s\n" pages_dir;
722 flush stdout;
723 Unix.putenv "http_proxy" "";
724 let mqi_handle = C.init ~log:debug_print () in
725 Http_daemon.start' ~port (callback mqi_handle);
726 C.close mqi_handle;
727 printf "%s is terminating, bye!\n" daemon_name