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