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